Changeset 420


Ignore:
Timestamp:
Nov 24, 2011, 9:54:55 AM (13 years ago)
Author:
tnavarro
Message:

24/11/11 == TN

corrected minor bug in updatereffrad.F : reffdust was not saved

ccn_factor as not correctly used in sedimentation.

It is now initialized in inifis.F, declared in tracer.h and
used in both simpleclouds.F & callsedim.F to update ice radius.

Commented diagfi outputs in aeropacity.F & improvedclouds.F for non scavenging users.

Location:
trunk/LMDZ.MARS
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/README

    r414 r420  
    12861286
    12871287>> Small changes to the molecular diffusion scheme to fix the number of species considered, to avoid problems when compiling with more than 15 tracers (for example, when CH4 is included). Modified subroutines: aeronomars/moldiff.F and aeronomars/moldiffcoeff.F
     1288
     1289== 24/11/11 == TN
     1290
     1291>> corrected minor bug in updatereffrad.F : reffdust was not saved
     1292
     1293>> ccn_factor as not correctly used in sedimentation.
     1294It is now initialized in inifis.F, declared in tracer.h and
     1295used in both simpleclouds.F & callsedim.F to update ice radius.
     1296
     1297>> Commented diagfi outputs in aeropacity.F & improvedclouds.F for
     1298non scavenging users.
     1299
     1300
     1301
     1302
     1303
  • trunk/LMDZ.MARS/libf/phymars/aeropacity.F

    r411 r420  
    442442     
    443443c output for debug
    444         IF (ngrid.NE.1) THEN
    445              CALL WRITEDIAGFI(ngridmx,'taudusttmp','virtual tau dust',
    446      &      '#',2,taudusttmp)
    447              CALL WRITEDIAGFI(ngridmx,'tausca','tauscaling',
    448      &      '#',2,tauscaling)
    449         ELSE
    450              CALL WRITEDIAGFI(ngridmx,'taudusttmp','virtual tau dust',
    451      &      '#',0,taudusttmp)
    452              CALL WRITEDIAGFI(ngridmx,'tausca','tauscaling',
    453      &      '#',0,tauscaling)
    454         ENDIF
     444c        IF (ngrid.NE.1) THEN
     445c             CALL WRITEDIAGFI(ngridmx,'taudusttmp','virtual tau dust',
     446c     &      '#',2,taudusttmp)
     447c             CALL WRITEDIAGFI(ngridmx,'tausca','tauscaling',
     448c     &      '#',2,tauscaling)
     449c        ELSE
     450c             CALL WRITEDIAGFI(ngridmx,'taudusttmp','virtual tau dust',
     451c     &      '#',0,taudusttmp)
     452c             CALL WRITEDIAGFI(ngridmx,'tausca','tauscaling',
     453c     &      '#',0,tauscaling)
     454c        ENDIF
    455455c -----------------------------------------------------------------
    456456c Column integrated visible optical depth in each point
     
    466466c Density scaled opacity and column opacity output
    467467c -----------------------------------------------------------------
    468       dsodust(1:ngrid,1:nlayer) = 0.
    469       DO iaer=1,naerdust
    470         DO l=1,nlayermx
    471           DO ig=1,ngrid
    472             dsodust(ig,l) = dsodust(ig,l) +
    473      &                      aerosol(ig,l,iaerdust(iaer)) * g /
    474      &                      (pplev(ig,l) - pplev(ig,l+1))
    475           ENDDO
    476         ENDDO
    477         IF (ngrid.NE.1) THEN
    478           write(txt2,'(i1.1)') iaer
    479           call WRITEDIAGFI(ngridmx,'taudust'//txt2,
    480      &                    'Dust col opacity',
    481      &                    ' ',2,tau(1,iaerdust(iaer)))
    482           IF (callstats) THEN
    483             CALL wstats(ngridmx,'taudust'//txt2,
    484      &                 'Dust col opacity',
    485      &                 ' ',2,tau(1,iaerdust(iaer)))
    486           ENDIF
    487         ENDIF
    488       ENDDO
    489 
    490       IF (ngrid.NE.1) THEN
     468c      dsodust(1:ngrid,1:nlayer) = 0.
     469c      DO iaer=1,naerdust
     470c        DO l=1,nlayermx
     471c          DO ig=1,ngrid
     472c            dsodust(ig,l) = dsodust(ig,l) +
     473c     &                      aerosol(ig,l,iaerdust(iaer)) * g /
     474c     &                      (pplev(ig,l) - pplev(ig,l+1))
     475c          ENDDO
     476c        ENDDO
     477c        IF (ngrid.NE.1) THEN
     478c          write(txt2,'(i1.1)') iaer
     479c          call WRITEDIAGFI(ngridmx,'taudust'//txt2,
     480c     &                    'Dust col opacity',
     481c     &                    ' ',2,tau(1,iaerdust(iaer)))
     482c          IF (callstats) THEN
     483c            CALL wstats(ngridmx,'taudust'//txt2,
     484c     &                 'Dust col opacity',
     485c     &                 ' ',2,tau(1,iaerdust(iaer)))
     486c          ENDIF
     487c        ENDIF
     488c      ENDDO
     489
     490c      IF (ngrid.NE.1) THEN
    491491c       CALL WRITEDIAGFI(ngridmx,'dsodust','tau*g/dp',
    492492c    &                    'm2.kg-1',3,dsodust)
    493         IF (callstats) THEN
    494           CALL wstats(ngridmx,'dsodust',
    495      &               'tau*g/dp',
    496      &               'm2.kg-1',3,dsodust)
    497         ENDIF
    498       ELSE
    499         CALL WRITEDIAGFI(ngrid,"dsodust","dsodust","m2.kg-1",1,
    500      &                   dsodust)
    501       ENDIF ! of IF (ngrid.NE.1)
     493c        IF (callstats) THEN
     494c          CALL wstats(ngridmx,'dsodust',
     495c     &               'tau*g/dp',
     496c     &               'm2.kg-1',3,dsodust)
     497c        ENDIF
     498c      ELSE
     499c        CALL WRITEDIAGFI(ngrid,"dsodust","dsodust","m2.kg-1",1,
     500c     &                   dsodust)
     501c      ENDIF ! of IF (ngrid.NE.1)
    502502c -----------------------------------------------------------------
    503503      return
  • trunk/LMDZ.MARS/libf/phymars/callsedim.F

    r411 r420  
    7373     
    7474c     for ice radius computation
    75       REAL ccn_factor
    7675      REAL Mo,No
    7776      REAL tau(ngrid,nlay), tauscaling(ngrid)
     
    200199            stop
    201200          endif
    202         ELSE
    203           write(*,*) "water_param CCN reduc. fac. ", ccn_factor
    204           write(*,*) "Careful: only used when microphys=F, otherwise"
    205           write(*,*) "  the contact parameter is used instead;"
    206201        ENDIF !of if (scavenging)
    207202
     
    461456            rice(ig,l)=max( CBRT ( (zqi(ig,l,igcm_h2o_ice)/rho_ice
    462457     &      +ccntyp*(4./3.)*pi*rdust(ig,l)**3.)
    463      &      /(ccntyp*4./3.*pi) ), rdust(ig,l))     
     458     &      /(ccntyp*4./3.*pi) ), rdust(ig,l))
    464459          ENDDO
    465460        ENDDO
  • trunk/LMDZ.MARS/libf/phymars/improvedclouds.F

    r411 r420  
    111111      REAL sigma_ice ! Variance of the ice and CCN distributions
    112112      SAVE sigma_ice
    113      
    114 c some outputs for 1D     
     113
     114c----------------------------------     
     115c some outputs for 1D -- TEMPORARY
    115116      REAL satu_out(ngridmx,nlayermx) ! satu ratio for output
    116117      REAL dN_out(ngridmx,nlayermx)  ! mass variation for output
     
    125126      REAL Mccn_col(ngridmx)         ! total column ccn mass
    126127      REAL Nccn_col(ngridmx)         ! total column ccn mass
    127       REAL count
    128 
     128      INTEGER count
     129     
     130      LOGICAL output_sca     ! scavenging outputs flag for tests
     131      output_sca = .false.
     132c----------------------------------     
     133c----------------------------------     
    129134
    130135c------------------------------------------------------------------
     
    428433          satu_out(ig,l) = satu
    429434          Mcon_out(ig,l) = 0
    430           newvap_out(ig,l) = zq(ig,l,igcm_h2o_ice)
    431           gr_out(ig,l) = gr
    432           dN_out(ig,l) = dN
    433           dM_out(ig,l) = dM
     435          newvap_out(ig,l) = zq(ig,l,igcm_h2o_vap)
     436          gr_out(ig,l) = 0
     437          dN_out(ig,l) = 0
     438          dM_out(ig,l) = 0
    434439         
    435440        ENDIF ! end if (saturation ratio > 1) or (there is h2o_ice)
     
    473478c------------------------------------------------------------------
    474479c     TESTS
     480
     481      IF (output_sca) then
    475482 
    476483      print*, 'count is ',count, ' i.e. ',
    477484     &     count*100/(nlay*ngrid), '% for microphys computation'     
    478485
    479 c      dM_col(:)    = 0
    480 c      dN_col(:)    = 0
    481 c      Mdust_col(:) = 0
    482 c      Ndust_col(:) = 0
    483 c      Mccn_col(:)  = 0
    484 c      Nccn_col(:)  = 0
    485 c      do l=1, nlay
    486 c        do ig=1,ngrid
    487 c          dM_col(ig) = dM_col(ig) +
    488 c     &       dM_out(ig,l)*(pplev(ig,l) - pplev(ig,l+1)) / g
    489 c          dN_col(ig) = dN_col(ig) +
    490 c     &       dN_out(ig,l)*(pplev(ig,l) - pplev(ig,l+1)) / g
    491 c          Mdust_col(ig) = Mdust_col(ig) +
    492 c     &       zq(ig,l,igcm_dust_mass)*tauscaling(ig)
    493 c     &       *(pplev(ig,l) - pplev(ig,l+1)) / g
    494 c          Ndust_col(ig) = Ndust_col(ig) +
    495 c     &       zq(ig,l,igcm_dust_number)*tauscaling(ig)
    496 c     &       *(pplev(ig,l) - pplev(ig,l+1)) / g
    497 c          Mccn_col(ig) = Mccn_col(ig) +
    498 c     &       zq(ig,l,igcm_ccn_mass)*tauscaling(ig)
    499 c     &       *(pplev(ig,l) - pplev(ig,l+1)) / g
    500 c          Nccn_col(ig) = Nccn_col(ig) +
    501 c     &       zq(ig,l,igcm_ccn_number)*tauscaling(ig)
    502 c     &       *(pplev(ig,l) - pplev(ig,l+1)) / g
    503 c        enddo ! of do ig=1,ngrid
    504 c      enddo ! of do l=1,nlay
    505 
    506 
    507       IF (ngrid.eq.0) THEN ! 3D
     486      dM_col(:)    = 0
     487      dN_col(:)    = 0
     488      Mdust_col(:) = 0
     489      Ndust_col(:) = 0
     490      Mccn_col(:)  = 0
     491      Nccn_col(:)  = 0
     492      do l=1, nlay
     493        do ig=1,ngrid
     494          dM_col(ig) = dM_col(ig) +
     495     &       dM_out(ig,l)*(pplev(ig,l) - pplev(ig,l+1)) / g
     496          dN_col(ig) = dN_col(ig) +
     497     &       dN_out(ig,l)*(pplev(ig,l) - pplev(ig,l+1)) / g
     498          Mdust_col(ig) = Mdust_col(ig) +
     499     &       zq(ig,l,igcm_dust_mass)*tauscaling(ig)
     500     &       *(pplev(ig,l) - pplev(ig,l+1)) / g
     501          Ndust_col(ig) = Ndust_col(ig) +
     502     &       zq(ig,l,igcm_dust_number)*tauscaling(ig)
     503     &       *(pplev(ig,l) - pplev(ig,l+1)) / g
     504          Mccn_col(ig) = Mccn_col(ig) +
     505     &       zq(ig,l,igcm_ccn_mass)*tauscaling(ig)
     506     &       *(pplev(ig,l) - pplev(ig,l+1)) / g
     507          Nccn_col(ig) = Nccn_col(ig) +
     508     &       zq(ig,l,igcm_ccn_number)*tauscaling(ig)
     509     &       *(pplev(ig,l) - pplev(ig,l+1)) / g
     510        enddo ! of do ig=1,ngrid
     511      enddo ! of do l=1,nlay
     512
     513
     514      IF (ngrid.ne.1) THEN ! 3D
    508515         call WRITEDIAGFI(ngrid,"satu","ratio saturation","",3,
    509516     &                    satu_out)
     
    544551         call WRITEDIAGFI(ngrid,"rice_sca","ice radius","m",1,
    545552     &                    rice)
    546          call WRITEDIAGFI(ngrid,"rdust","rdust","m",1,
     553         call WRITEDIAGFI(ngrid,"rdust_sca","rdust","m",1,
    547554     &                    rdust)
    548555         call WRITEDIAGFI(ngrid,"rsedcloud","rsedcloud","m",1,
     
    563570     &                    Mccn_col)
    564571      ENDIF
     572      ENDIF ! endif output_sca
    565573c------------------------------------------------------------------
    566574      return
  • trunk/LMDZ.MARS/libf/phymars/inifis.F

    r414 r420  
    6262#include "slope.h"
    6363#include "microphys.h"
     64#include "tracer.h"
    6465#ifdef MESOSCALE
    6566#include "comsoil.h"     !!MESOSCALE -- needed to fill volcapa
     
    417418           stop
    418419         endif
     420         
     421! ccn factor if no scavenging         
     422        write(*,*) "water param CCN reduc. factor ?", ccn_factor
     423        ccn_factor = 4.5
     424        call getin("ccn_factor",ccn_factor)
     425        write(*,*)" ccn_factor = ",ccn_factor
     426        write(*,*)"Careful: only used when microphys=F, otherwise"
     427        write(*,*)"the contact parameter is used instead;"
     428
    419429! microphys
    420430         write(*,*)"Microphysical scheme for water-ice clouds?"
  • trunk/LMDZ.MARS/libf/phymars/physiq.F

    r414 r420  
    318318c Test 1d/3d scavenging
    319319      real h2o_tot
    320       real ccndust_mass(nlayermx)
    321       real ccndust_number(nlayermx)
    322       real rescale                ! to rescale GCM dust quantities
    323320
    324321      REAL time_phys
     
    19941991           do l=1,nlayer
    19951992             h2o_tot = h2o_tot +
    1996      &           (zq(ig,l,igcm_h2o_vap) + zq(ig,l,igcm_h2o_ice))
    1997      &                     * (pplev(ig,l) - pplev(ig,l+1)) / g
    1998              ccndust_mass(l) =
    1999      &       pq(1,l,igcm_dust_mass)+pq(1,l,igcm_ccn_mass)
    2000              ccndust_number(l) =
    2001      &       pq(1,l,igcm_dust_number)+pq(1,l,igcm_ccn_number)
    2002      
     1993     &           (zq(1,l,igcm_h2o_vap) + zq(1,l,igcm_h2o_ice))
     1994     &                     * (pplev(1,l) - pplev(1,l+1)) / g
    20031995           end do
    20041996 
  • trunk/LMDZ.MARS/libf/phymars/simpleclouds.F

    r358 r420  
    8989                                      ! Typical dust number density (#/kg)
    9090c     CCN reduction factor
    91       REAL, PARAMETER :: ccn_factor = 4.5  !! comme TESTS_JB // 1. avant
     91c      REAL, PARAMETER :: ccn_factor = 4.5  !! comme TESTS_JB // 1. avant
    9292     
    9393      REAL Mcon_out(ngridmx,nlayermx) ! mass to be condensed (not dMice !!)
    94 
    95 
    96 c------------------------------------------------------------------
    97 
    98 c     Write ccn_factor;
    99       IF (firstcall) THEN
    100         write(*,*) "water_param CCN reduc. fac. ", ccn_factor
    101         write(*,*) "Careful: only used when microphys=F, otherwise"
    102         write(*,*) "  the contact parameter is used instead;"
    103         firstcall=.false.
    104       END IF
    10594
    10695c-----------------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/tracer.h

    r358 r420  
    1616      real nuice_sed   ! Sedimentation effective variance of the water ice dist.
    1717      real ref_r0        ! for computing reff=ref_r0*r0 (in log.n. distribution)
     18     
     19      real ccn_factor  ! ratio of nuclei for water ice particles
    1820
    1921      real dryness(ngridmx)!"Dryness coefficient" for grnd water ice sublimation
     
    7375      COMMON/tracer/radius,rho_q,alpha_lift,alpha_devil,mmol,           &
    7476     & varian,r3n_q,rho_dust,rho_ice,nuice_ref,nuice_sed,               &
    75      & ref_r0,dryness
     77     & ref_r0,ccn_factor,dryness
    7678      COMMON/tracer2/                                                   &
    7779     & igcm_dustbin,igcm_dust_mass,igcm_dust_number,                    &
  • trunk/LMDZ.MARS/libf/phymars/updatereffrad.F

    r358 r420  
    7676      EXTERNAL CBRT
    7777
    78       real nueffdust(ngridmx,nlayermx) ! Dust effective variance
     78      REAL,SAVE :: nueffdust(ngridmx,nlayermx) ! Dust effective variance
    7979
    8080c     Local saved variables:
Note: See TracChangeset for help on using the changeset viewer.