Changeset 1375 for trunk/LMDZ.MARS/libf


Ignore:
Timestamp:
Feb 11, 2015, 10:31:46 PM (10 years ago)
Author:
aslmd
Message:

modification to physiq for dust bomb simulation

Location:
trunk/LMDZ.MARS/libf/phymars
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/phymars/aeropacity.F

    r1353 r1375  
    99     &                      nqdust
    1010      use comgeomfi_h, only: lati, sinlat ! grid point latitudes (rad)
     11#ifdef DUSTSTORM
     12      use comgeomfi_h, only: long
     13      use tracer_mod, only: r3n_q, ref_r0, igcm_dust_number
     14#endif
    1115      use planete_h
    1216      USE comcstfi_h
     
    108112      REAL topdust0(ngrid)
    109113
     114#ifdef DUSTSTORM
     115!! Local dust storms
     116      logical localstorm        ! =true to create a local dust storm
     117      real taulocref,ztoploc,radloc,lonloc,latloc  ! local dust storm parameters
     118      real reffstorm, yeah
     119      REAL ray(ngrid) ! distance from dust storm center
     120      REAL tauuser(ngrid) ! opacity perturbation due to dust storm
     121      REAL more_dust(ngrid,nlayer,2) ! Mass mixing ratio perturbation due to the dust storm
     122      REAL int_factor(ngrid) ! useful factor to compute mmr perturbation
     123      real l_top ! layer of the storm's top
     124      REAL zalt(ngrid, nlayer) ! useful factor to compute l_top
     125      REAL zdqnorm(ngrid, nlayer,2)
     126#endif
     127
    110128c   local saved variables
    111129c   ---------------------
     
    189207
    190208
     209#ifndef DUSTSTORM
    191210        firstcall=.false.
     211#endif
    192212
    193213      END IF
     
    437457c -----------------------------------------------------------------
    438458
     459#ifdef DUSTSTORM
     460c -----------------------------------------------------------------
     461c the quantity of dust to add at the first time step is calculated
     462c to match a tunable opacity perturbation.
     463c -----------------------------------------------------------------
     464      IF (firstcall) THEN
     465        DO iaer=1,naerdust
     466          DO l=1,nlayer
     467            DO ig=1,ngrid
     468              tauref(ig) = tauref(ig) +
     469     &                    aerosol(ig,l,iaerdust(iaer))
     470            ENDDO
     471          ENDDO
     472        ENDDO
     473        tauref(:) = tauref(:) * odpref / pplev(:,1)
     474c--------------------------------------------------
     475c  Parameters of the opacity perturbation
     476c--------------------------------------------------
     477
     478      iaer=1  !!!! PROVISOIRE !!!!
     479
     480        write(*,*) "Add a local storm ?"
     481        localstorm=.true. ! default value
     482        call getin("localstorm",localstorm)
     483        write(*,*) " localstorm = ",localstorm
     484
     485        IF (localstorm) THEN
     486          WRITE(*,*) "********************"
     487          WRITE(*,*) "ADDING A LOCAL STORM"
     488          WRITE(*,*) "********************"
     489
     490          write(*,*) "ref opacity of local dust storm"
     491              taulocref = 4.25 ! default value
     492              call getin("taulocref",taulocref)
     493              write(*,*) " taulocref = ",taulocref
     494
     495          write(*,*) "target altitude of local storm (km)"
     496              ztoploc = 10.0 ! default value
     497              call getin("ztoploc",ztoploc)
     498              write(*,*) " ztoploc = ",ztoploc
     499
     500          write(*,*) "radius of dust storm (degree)"
     501              radloc = 0.5 ! default value
     502              call getin("radloc",radloc)
     503              write(*,*) " radloc = ",radloc
     504
     505          write(*,*) "center longitude of storm (deg)"
     506              lonloc = 25.0 ! default value
     507              call getin("lonloc",lonloc)
     508              write(*,*) " lonloc = ",lonloc
     509
     510          write(*,*) "center latitude of storm (deg)"
     511              latloc = -2.5 ! default value
     512              call getin("latloc",latloc)
     513              write(*,*) " latloc = ",latloc
     514       
     515          write(*,*) "reff storm (mic) 0. for background"
     516              reffstorm = 0.0 ! default value
     517              call getin("reffstorm",reffstorm)
     518              write(*,*) " reffstorm = ",reffstorm
     519
     520      DO ig=1,ngrid
     521
     522
     523c---------------------------------------
     524c        distance to the center:
     525c-----------------------------------------
     526
     527      ray(ig)=SQRT((lati(ig)*180./pi-latloc)**2 +
     528     &          (long(ig)*180./pi -lonloc)**2)
     529
     530
     531      !! transition factor for storm
     532      !! increase factor ray diff for steepness
     533      yeah = (TANH(2.+(radloc-ray(ig))*10.)+1.)/2.
     534
     535c-------------------------------------------------
     536c           Tau's new map:
     537c------------------------------------------
     538
     539      tauuser(ig)=max(tauref(ig) * pplev(ig,1) /odpref  ,
     540     &          taulocref * yeah)
     541
     542c---------------------------------------------------------
     543c           compute l_top
     544c----------------------------------------------------------
     545
     546          DO l=1,nlayer
     547            zalt(ig,l) = LOG( pplev(ig,1)/pplev(ig,l) )
     548     &                      / g / 44.01
     549     &                    * 8.31 * 210.
     550                IF (     (ztoploc .lt. zalt(ig,l)  )
     551     &          .and. (ztoploc .gt. zalt(ig,l-1)) ) l_top=l-1
     552          ENDDO
     553
     554c---------------------------------------------------------
     555c           change reffrad if ever needed
     556c----------------------------------------------------------
     557
     558      IF (reffstorm .gt. 0.) THEN
     559          DO l=1,nlayer
     560             IF (l .lt. l_top+1) THEN
     561                reffrad(ig,l,iaer) = max( reffrad(ig,l,iaer), reffstorm
     562     &          * 1.e-6 * yeah )
     563             ENDIF
     564          ENDDO
     565      ENDIF
     566
     567
     568c---------------------------------------------------------------------------
     569      ENDDO !! boucle sur ngridmx
     570c---------------------------------------------------------------------------
     571c----------------------------------------------------------------------------
     572c    compute int_factor
     573c---------------------------------------------------------------------------
     574
     575      DO ig=1,ngrid
     576          int_factor(ig)=0.
     577          DO l=1,nlayer
     578             IF (l .lt. l_top+1) THEN
     579                      int_factor(ig) =
     580     &                int_factor(ig) +
     581     &          (  0.75 * QREFvis3d(ig,l,iaer) /
     582     &          ( rho_dust * reffrad(ig,l,iaer) )  ) *
     583     &          ( pplev(ig,l) - pplev(ig,l+1) ) / g
     584             ENDIF
     585          ENDDO
     586          DO l=1, nlayer
     587
     588c-------------------------------------------------------------------------
     589c Mass mixing ratio perturbation due to the local dust storm in each
     590c layer
     591c-------------------------------------------------------------------------
     592          more_dust(ig,l,1)=
     593     &                     (tauuser(ig)-(tauref(ig)
     594     &                      * pplev(ig,1) /odpref)) /
     595     &                      int_factor(ig)
     596          more_dust(ig,l,2)=
     597     &                     (tauuser(ig)-(tauref(ig) *
     598     &                     pplev(ig,1) /odpref))
     599     &                      / int_factor(ig) *
     600     &                     ((ref_r0/reffrad(ig,l,iaer))**3)
     601     &                      * r3n_q
     602          ENDDO
     603      ENDDO
     604
     605c--------------------------------------------------------------------------------------
     606c   quantity of dust which is added at the first time step
     607c     in dynamical core.
     608c--------------------------------------------------------------------------------------
     609
     610        DO l=1, l_top
     611          zdqnorm(:,l,1) = more_dust(:,l,1)
     612          zdqnorm(:,l,2) = more_dust(:,l,2)
     613          pq(:,l,igcm_dust_mass)= pq(:,l,igcm_dust_mass)+ zdqnorm(:,l,1)
     614          pq(:,l,igcm_dust_number)= pq(:,l,igcm_dust_number)+ zdqnorm(:,l,2)
     615        ENDDO
     616        ENDIF
     617        tauref(:)=0.
     618      ENDIF  !firstcall
     619#endif
     620
    439621      IF (freedust) THEN
    440622          tauscaling(:) = 1.
     
    512694        end do
    513695      ENDDO
     696
     697#ifdef DUSTSTORM
     698      IF (firstcall) THEN
     699        firstcall=.false.
     700      ENDIF
     701#endif
     702
    514703c -----------------------------------------------------------------
    515704c Density scaled opacity and column opacity output
  • trunk/LMDZ.MARS/libf/phymars/physiq.F

    r1353 r1375  
    192192      INTEGER,SAVE :: day_ini ! Initial date of the run (sol since Ls=0)
    193193      INTEGER,SAVE :: icount     ! counter of calls to physiq during the run.
    194      
     194#ifdef DUSTSTORM
     195      REAL pq_tmp(ngrid, nlayer, 2) ! To compute tendencies due the dust bomb
     196#endif
    195197c     Variables used by the water ice microphysical scheme:
    196198      REAL rice(ngrid,nlayer)    ! Water ice geometric mean radius (m)
     
    516518      zdtsurf(:)=0
    517519      dqsurf(:,:)=0
     520      pq_tmp(:,:,:)=0
    518521      igout=ngrid/2+1
    519522
     
    667670c          Radiative transfer
    668671c          ------------------
     672
     673#ifdef DUSTSTORM
     674           pq_tmp(1:ngrid,1:nlayer,1)=
     675     & pq(1:ngrid,1:nlayer,igcm_dust_mass)
     676
     677           pq_tmp(1:ngrid,1:nlayer,2)=
     678     & pq(1:ngrid,1:nlayer,igcm_dust_number)
     679         
     680#endif
     681
    669682           CALL callradite(icount,ngrid,nlayer,nq,zday,zls,pq,albedo,
    670683     $     emis,mu0,zplev,zplay,pt,tsurf,fract,dist_sol,igout,
     
    672685     $     tauref,tau,aerosol,dsodust,tauscaling,taucloudtes,rdust,rice,
    673686     $     nuice,co2ice)
     687
     688#ifdef DUSTSTORM
     689           pdq(1:ngrid,1:nlayer,igcm_dust_mass)=
     690     & pdq(1:ngrid,1:nlayer,igcm_dust_mass)
     691     & - pq_tmp(1:ngrid,1:nlayer,1)
     692     & +pq(1:ngrid,1:nlayer,igcm_dust_mass)
     693
     694
     695           pdq(1:ngrid,1:nlayer,igcm_dust_number)=
     696     & pdq(1:ngrid,1:nlayer,igcm_dust_number)
     697     & - pq_tmp(1:ngrid,1:nlayer,2)
     698     & +pq(1:ngrid,1:nlayer,igcm_dust_number)
     699#endif
    674700
    675701c          Outputs for basic check (middle of domain)
Note: See TracChangeset for help on using the changeset viewer.