Changeset 2972 for trunk/LMDZ.GENERIC


Ignore:
Timestamp:
May 29, 2023, 12:41:48 PM (18 months ago)
Author:
emillour
Message:

Generic PCM:
Make number of scatterers fully dynamic (i.e. set in callphys.def
and no longer by compilation option "-s #").
One should now specify
naerkind = #
in callphys.def (default is 0).
EM

Location:
trunk/LMDZ.GENERIC
Files:
1 deleted
17 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/deftank/callphys.GJ581d

    r1784 r2972  
    9797## Tracer and aerosol options
    9898## ~~~~~~~~~~~~~~~~~~~~~~~~~~
     99# Number of radiatively active aerosols
     100naerkind=1
    99101# Radiatively active CO2 aerosol?
    100102aeroco2       = .true.
  • trunk/LMDZ.GENERIC/deftank/callphys.earlymars

    r1784 r2972  
    7575sedimentation = .false.
    7676
     77
    7778## Other physics options
    7879## ~~~~~~~~~~~~~~~~~~~~~
     
    9293## Tracer and aerosol options
    9394## ~~~~~~~~~~~~~~~~~~~~~~~~~~
     95# Number of radiatively active aerosols
     96naerkind=2
    9497# Radiatively active CO2 aerosol?
    9598aeroco2       = .true.
  • trunk/LMDZ.GENERIC/deftank/callphys.earth

    r1784 r2972  
    9191## Tracer and aerosol options
    9292## ~~~~~~~~~~~~~~~~~~~~~~~~~~
     93# Number of radiatively active aerosols
     94naerkind=1
    9395# Radiatively active CO2 aerosol?
    9496aeroco2       = .false.
  • trunk/LMDZ.GENERIC/deftank/callphys.kcm1d

    r1784 r2972  
    6464## Tracer and aerosol options
    6565## ~~~~~~~~~~~~~~~~~~~~~~~~~~
     66# Number of radiatively active aerosols
     67naerkind=0
    6668# Fixed aerosol distributions?
    6769aerofixed     = .true.
  • trunk/LMDZ.GENERIC/libf/phystd/aeroptproperties.F90

    r2899 r2972  
    4444
    4545!     =============================================================
    46       LOGICAL, PARAMETER :: varyingnueff(naerkind) = .false.
     46!      LOGICAL, PARAMETER :: varyingnueff(naerkind) = .false. ! not used!
    4747!     =============================================================
    4848
     
    105105      REAL,SAVE :: logvratgrid,vratgrid
    106106!     Grid used to remember which calculation is done
    107       LOGICAL,SAVE :: checkgrid(refftabsize,nuefftabsize,naerkind,2) = .false.
     107      LOGICAL,SAVE,ALLOCATABLE :: checkgrid(:,:,:,:)
    108108!$OMP THREADPRIVATE(refftab,nuefftab,logvratgrid,vratgrid,checkgrid)
    109109!     Optical properties of the grid (VISIBLE)
    110       REAL,SAVE :: qsqrefVISgrid(refftabsize,nuefftabsize,L_NSPECTV,naerkind)
    111       REAL,SAVE :: qextVISgrid(refftabsize,nuefftabsize,L_NSPECTV,naerkind)
    112       REAL,SAVE :: qscatVISgrid(refftabsize,nuefftabsize,L_NSPECTV,naerkind)
    113       REAL,SAVE :: omegVISgrid(refftabsize,nuefftabsize,L_NSPECTV,naerkind)
    114       REAL,SAVE :: gVISgrid(refftabsize,nuefftabsize,L_NSPECTV,naerkind)
     110      REAL,SAVE,ALLOCATABLE :: qsqrefVISgrid(:,:,:,:)
     111      REAL,SAVE,ALLOCATABLE :: qextVISgrid(:,:,:,:)
     112      REAL,SAVE,ALLOCATABLE :: qscatVISgrid(:,:,:,:)
     113      REAL,SAVE,ALLOCATABLE :: omegVISgrid(:,:,:,:)
     114      REAL,SAVE,ALLOCATABLE :: gVISgrid(:,:,:,:)
    115115!$OMP THREADPRIVATE(qsqrefVISgrid,qextVISgrid,qscatVISgrid,omegVISgrid,gVISgrid)
    116116!     Optical properties of the grid (INFRARED)
    117       REAL,SAVE :: qsqrefIRgrid(refftabsize,nuefftabsize,L_NSPECTI,naerkind)
    118       REAL,SAVE :: qextIRgrid(refftabsize,nuefftabsize,L_NSPECTI,naerkind)
    119       REAL,SAVE :: qscatIRgrid(refftabsize,nuefftabsize,L_NSPECTI,naerkind)
    120       REAL,SAVE :: omegIRgrid(refftabsize,nuefftabsize,L_NSPECTI,naerkind)
    121       REAL,SAVE :: gIRgrid(refftabsize,nuefftabsize,L_NSPECTI,naerkind)
     117      REAL,SAVE,ALLOCATABLE :: qsqrefIRgrid(:,:,:,:)
     118      REAL,SAVE,ALLOCATABLE :: qextIRgrid(:,:,:,:)
     119      REAL,SAVE,ALLOCATABLE :: qscatIRgrid(:,:,:,:)
     120      REAL,SAVE,ALLOCATABLE :: omegIRgrid(:,:,:,:)
     121      REAL,SAVE,ALLOCATABLE :: gIRgrid(:,:,:,:)
    122122!$OMP THREADPRIVATE(qsqrefIRgrid,qextIRgrid,qscatIRgrid,omegIRgrid,gIRgrid)
    123123!     Optical properties of the grid (REFERENCE WAVELENGTHS)
    124       REAL,SAVE :: qrefVISgrid(refftabsize,nuefftabsize,naerkind)
    125       REAL,SAVE :: qscatrefVISgrid(refftabsize,nuefftabsize,naerkind)
    126       REAL,SAVE :: qrefIRgrid(refftabsize,nuefftabsize,naerkind)
    127       REAL,SAVE :: qscatrefIRgrid(refftabsize,nuefftabsize,naerkind)
    128       REAL,SAVE :: omegrefVISgrid(refftabsize,nuefftabsize,naerkind)
    129       REAL,SAVE :: omegrefIRgrid(refftabsize,nuefftabsize,naerkind)
     124      REAL,SAVE,ALLOCATABLE :: qrefVISgrid(:,:,:)
     125      REAL,SAVE,ALLOCATABLE :: qscatrefVISgrid(:,:,:)
     126      REAL,SAVE,ALLOCATABLE :: qrefIRgrid(:,:,:)
     127      REAL,SAVE,ALLOCATABLE :: qscatrefIRgrid(:,:,:)
     128      REAL,SAVE,ALLOCATABLE :: omegrefVISgrid(:,:,:)
     129      REAL,SAVE,ALLOCATABLE :: omegrefIRgrid(:,:,:)
    130130!$OMP THREADPRIVATE(qrefVISgrid,qscatrefVISgrid,qrefIRgrid,qscatrefIRgrid,omegrefVISgrid,&
    131         !$OMP omegrefIRgrid)
     131!$OMP omegrefIRgrid)
    132132!     Firstcall
    133133      LOGICAL,SAVE :: firstcall = .true.
    134 !$OMP THREADPRIVATE(firstcall)
     134      LOGICAL,SAVE :: first_allocate=.true.
     135!$OMP THREADPRIVATE(firstcall,first_allocate)
    135136!     Variables used by the Gauss-Legendre integration:
    136       REAL,SAVE :: normd(refftabsize,nuefftabsize,naerkind,2)
    137       REAL,SAVE :: dista(refftabsize,nuefftabsize,naerkind,2,ngau)
    138       REAL,SAVE :: distb(refftabsize,nuefftabsize,naerkind,2,ngau)
     137      REAL,SAVE,ALLOCATABLE :: normd(:,:,:,:)
     138      REAL,SAVE,ALLOCATABLE :: dista(:,:,:,:,:)
     139      REAL,SAVE,ALLOCATABLE :: distb(:,:,:,:,:)
    139140!$OMP THREADPRIVATE(normd,dista,distb)
    140141
    141       REAL,SAVE :: radGAUSa(ngau,naerkind,2)
    142       REAL,SAVE :: radGAUSb(ngau,naerkind,2)
     142      REAL,SAVE,ALLOCATABLE :: radGAUSa(:,:,:)
     143      REAL,SAVE,ALLOCATABLE :: radGAUSb(:,:,:)
    143144!$OMP THREADPRIVATE(radGAUSa,radGAUSb)
    144145
    145       REAL,SAVE :: qsqrefVISa(L_NSPECTV,ngau,naerkind)
    146       REAL,SAVE :: qrefVISa(ngau,naerkind)
    147       REAL,SAVE :: qsqrefVISb(L_NSPECTV,ngau,naerkind)
    148       REAL,SAVE :: qrefVISb(ngau,naerkind)
    149       REAL,SAVE :: omegVISa(L_NSPECTV,ngau,naerkind)
    150       REAL,SAVE :: omegrefVISa(ngau,naerkind)
    151       REAL,SAVE :: omegVISb(L_NSPECTV,ngau,naerkind)
    152       REAL,SAVE :: omegrefVISb(ngau,naerkind)
    153       REAL,SAVE :: gVISa(L_NSPECTV,ngau,naerkind)
    154       REAL,SAVE :: gVISb(L_NSPECTV,ngau,naerkind)
    155 !$OMP THREADPRIVATE(qsqrefVISa,qrefVISa,qsqrefVISb,qrefVISb,omegVISa, &
    156         !$OMP omegrefVISa,omegVISb,omegrefVISb,gVISa,gVISb)
    157 
    158       REAL,SAVE :: qsqrefIRa(L_NSPECTI,ngau,naerkind)
    159       REAL,SAVE :: qrefIRa(ngau,naerkind)
    160       REAL,SAVE :: qsqrefIRb(L_NSPECTI,ngau,naerkind)
    161       REAL,SAVE :: qrefIRb(ngau,naerkind)
    162       REAL,SAVE :: omegIRa(L_NSPECTI,ngau,naerkind)
    163       REAL,SAVE :: omegrefIRa(ngau,naerkind)
    164       REAL,SAVE :: omegIRb(L_NSPECTI,ngau,naerkind)
    165       REAL,SAVE :: omegrefIRb(ngau,naerkind)
    166       REAL,SAVE :: gIRa(L_NSPECTI,ngau,naerkind)
    167       REAL,SAVE :: gIRb(L_NSPECTI,ngau,naerkind)
    168 !$OMP THREADPRIVATE(qsqrefIRa,qrefIRa,qsqrefIRb,qrefIRb,omegIRa,omegrefIRa,&
    169         !$OMP omegIRb,omegrefIRb,gIRa,gIRb)
     146      REAL,SAVE,ALLOCATABLE :: qsqrefVISa(:,:,:)
     147      REAL,SAVE,ALLOCATABLE :: qrefVISa(:,:)
     148      REAL,SAVE,ALLOCATABLE :: qsqrefVISb(:,:,:)
     149      REAL,SAVE,ALLOCATABLE :: qrefVISb(:,:)
     150!$OMP THREADPRIVATE(qsqrefVISa,qrefVISa,qsqrefVISb,qrefVISb)
     151      REAL,SAVE,ALLOCATABLE :: omegVISa(:,:,:)
     152      REAL,SAVE,ALLOCATABLE :: omegrefVISa(:,:)
     153      REAL,SAVE,ALLOCATABLE :: omegVISb(:,:,:)
     154      REAL,SAVE,ALLOCATABLE :: omegrefVISb(:,:)
     155      REAL,SAVE,ALLOCATABLE :: gVISa(:,:,:)
     156      REAL,SAVE,ALLOCATABLE :: gVISb(:,:,:)
     157!$OMP THREADPRIVATE(omegVISa,omegrefVISa,omegVISb,omegrefVISb,gVISa,gVISb)
     158
     159      REAL,SAVE,ALLOCATABLE :: qsqrefIRa(:,:,:)
     160      REAL,SAVE,ALLOCATABLE :: qrefIRa(:,:)
     161      REAL,SAVE,ALLOCATABLE :: qsqrefIRb(:,:,:)
     162      REAL,SAVE,ALLOCATABLE :: qrefIRb(:,:)
     163!$OMP THREADPRIVATE(qsqrefIRa,qrefIRa,qsqrefIRb,qrefIRb)
     164      REAL,SAVE,ALLOCATABLE :: omegIRa(:,:,:)
     165      REAL,SAVE,ALLOCATABLE :: omegrefIRa(:,:)
     166      REAL,SAVE,ALLOCATABLE :: omegIRb(:,:,:)
     167      REAL,SAVE,ALLOCATABLE :: omegrefIRb(:,:)
     168      REAL,SAVE,ALLOCATABLE :: gIRa(:,:,:)
     169      REAL,SAVE,ALLOCATABLE :: gIRb(:,:,:)
     170!$OMP THREADPRIVATE(omegIRa,omegrefIRa,omegIRb,omegrefIRb,gIRa,gIRb)
    170171
    171172      REAL :: radiusm
     
    197198!      REAL :: omegaREFvis3d(ngrid,nlayer,naerkind)
    198199!      REAL :: omegaREFir3d(ngrid,nlayer,naerkind)
     200
     201!     0. Allocate local saved arrays at firstcall
     202!     --------------------------------------------------
     203      IF (first_allocate) THEN
     204        ! Grid used to remember computations already done at previous calls
     205        ALLOCATE(checkgrid(refftabsize,nuefftabsize,naerkind,2))
     206        checkgrid(:,:,:,:)=.false.
     207        ! Optical properties of the grid (VISIBLE)
     208        ALLOCATE(qsqrefVISgrid(refftabsize,nuefftabsize,L_NSPECTV,naerkind))
     209        ALLOCATE(qextVISgrid(refftabsize,nuefftabsize,L_NSPECTV,naerkind))
     210        ALLOCATE(qscatVISgrid(refftabsize,nuefftabsize,L_NSPECTV,naerkind))
     211        ALLOCATE(omegVISgrid(refftabsize,nuefftabsize,L_NSPECTV,naerkind))
     212        ALLOCATE(gVISgrid(refftabsize,nuefftabsize,L_NSPECTV,naerkind))
     213        ! Optical properties of the grid (INFRARED)
     214        ALLOCATE(qsqrefIRgrid(refftabsize,nuefftabsize,L_NSPECTI,naerkind))
     215        ALLOCATE(qextIRgrid(refftabsize,nuefftabsize,L_NSPECTI,naerkind))
     216        ALLOCATE(qscatIRgrid(refftabsize,nuefftabsize,L_NSPECTI,naerkind))
     217        ALLOCATE(omegIRgrid(refftabsize,nuefftabsize,L_NSPECTI,naerkind))
     218        ALLOCATE(gIRgrid(refftabsize,nuefftabsize,L_NSPECTI,naerkind))
     219        ! Optical properties of the grid (REFERENCE WAVELENGTHS)
     220        ALLOCATE(qrefVISgrid(refftabsize,nuefftabsize,naerkind))
     221        ALLOCATE(qscatrefVISgrid(refftabsize,nuefftabsize,naerkind))
     222        ALLOCATE(qrefIRgrid(refftabsize,nuefftabsize,naerkind))
     223        ALLOCATE(qscatrefIRgrid(refftabsize,nuefftabsize,naerkind))
     224        ALLOCATE(omegrefVISgrid(refftabsize,nuefftabsize,naerkind))
     225        ALLOCATE(omegrefIRgrid(refftabsize,nuefftabsize,naerkind))
     226        ! Variables used by the Gauss-Legendre integration:
     227        ALLOCATE(normd(refftabsize,nuefftabsize,naerkind,2))
     228        ALLOCATE(dista(refftabsize,nuefftabsize,naerkind,2,ngau))
     229        ALLOCATE(distb(refftabsize,nuefftabsize,naerkind,2,ngau))
     230        ALLOCATE(radGAUSa(ngau,naerkind,2))
     231        ALLOCATE(radGAUSb(ngau,naerkind,2))
     232        !
     233        ALLOCATE(qsqrefVISa(L_NSPECTV,ngau,naerkind))
     234        ALLOCATE(qrefVISa(ngau,naerkind))
     235        ALLOCATE(qsqrefVISb(L_NSPECTV,ngau,naerkind))
     236        ALLOCATE(qrefVISb(ngau,naerkind))
     237        ALLOCATE(omegVISa(L_NSPECTV,ngau,naerkind))
     238        ALLOCATE(omegrefVISa(ngau,naerkind))
     239        ALLOCATE(omegVISb(L_NSPECTV,ngau,naerkind))
     240        ALLOCATE(omegrefVISb(ngau,naerkind))
     241        ALLOCATE(gVISa(L_NSPECTV,ngau,naerkind))
     242        ALLOCATE(gVISb(L_NSPECTV,ngau,naerkind))
     243        !
     244        ALLOCATE(qsqrefIRa(L_NSPECTI,ngau,naerkind))
     245        ALLOCATE(qrefIRa(ngau,naerkind))
     246        ALLOCATE(qsqrefIRb(L_NSPECTI,ngau,naerkind))
     247        ALLOCATE(qrefIRb(ngau,naerkind))
     248       
     249        ALLOCATE(omegIRa(L_NSPECTI,ngau,naerkind))
     250        ALLOCATE(omegrefIRa(ngau,naerkind))
     251        ALLOCATE(omegIRb(L_NSPECTI,ngau,naerkind))
     252        ALLOCATE(omegrefIRb(ngau,naerkind))
     253        ALLOCATE(gIRa(L_NSPECTI,ngau,naerkind))
     254        ALLOCATE(gIRb(L_NSPECTI,ngau,naerkind))
     255       
     256        first_allocate=.false.
     257      ENDIF ! of IF (first_allocate)
    199258
    200259      DO iaer = 1, naerkind ! Loop on aerosol kind
     
    260319
    261320        firstcall = .false.
    262       ENDIF
     321      ENDIF ! of IF (firstcall)
    263322
    264323!       1.4 Radius middle point and range for Gauss integration
     
    755814      ENDDO ! iaer (loop on aerosol kind)
    756815
    757       RETURN
    758816    END SUBROUTINE aeroptproperties
    759817
  • trunk/LMDZ.GENERIC/libf/phystd/aerosol_mod.F90

    r2898 r2972  
    193193    if (is_master) then
    194194      print*, 'Aerosols counted not equal to naerkind'
    195       print*, 'Compile with tag -s',ia,'to run'
    196       print*, 'or change options in callphys.def'
     195      print*, 'set correct value for nearkind in callphys.def'
     196      print*, 'which should be ',ia
     197      print*, 'according to current options in callphys.def'
     198      print*, 'or change/correct incompatible options there'
    197199      print*, 'Abort in iniaerosol'
    198200    endif
  • trunk/LMDZ.GENERIC/libf/phystd/callcorrk.F90

    r2960 r2972  
    117117     
    118118
    119       ! Globally varying aerosol optical properties on GCM grid ; not needed everywhere so not in radcommon_h.   
    120       REAL :: QVISsQREF3d(ngrid,nlayer,L_NSPECTV,naerkind)
    121       REAL :: omegaVIS3d(ngrid,nlayer,L_NSPECTV,naerkind)
    122       REAL :: gVIS3d(ngrid,nlayer,L_NSPECTV,naerkind)
    123       REAL :: QIRsQREF3d(ngrid,nlayer,L_NSPECTI,naerkind)
    124       REAL :: omegaIR3d(ngrid,nlayer,L_NSPECTI,naerkind)
    125       REAL :: gIR3d(ngrid,nlayer,L_NSPECTI,naerkind)
     119! Globally varying aerosol optical properties on GCM grid ; not needed everywhere so not in radcommon_h.   
     120! made "save" variables so they are allocated once in for all, not because
     121! the values need be saved from a time step to the next
     122      REAL,SAVE,ALLOCATABLE :: QVISsQREF3d(:,:,:,:)
     123      REAL,SAVE,ALLOCATABLE :: omegaVIS3d(:,:,:,:)
     124      REAL,SAVE,ALLOCATABLE :: gVIS3d(:,:,:,:)
     125!$OMP THREADPRIVATE(QVISsQREF3d,omegaVIS3d,gVIS3d)
     126      REAL,SAVE,ALLOCATABLE :: QIRsQREF3d(:,:,:,:)
     127      REAL,SAVE,ALLOCATABLE :: omegaIR3d(:,:,:,:)
     128      REAL,SAVE,ALLOCATABLE :: gIR3d(:,:,:,:)
     129!$OMP THREADPRIVATE(QIRsQREF3d,omegaIR3d,gIR3d)
    126130
    127131!      REAL :: omegaREFvis3d(ngrid,nlayer,naerkind)
     
    155159      REAL*8,allocatable,save :: taucumi(:,:,:)
    156160!$OMP THREADPRIVATE(tauv,taucumv,taucumi)
    157       REAL*8 tauaero(L_LEVELS,naerkind)
     161      REAL*8,allocatable,save :: tauaero(:,:)
     162!$OMP THREADPRIVATE(tauaero)
    158163      REAL*8 nfluxtopv,nfluxtopi,nfluxtop,fluxtopvdn
    159164      REAL*8 nfluxoutv_nu(L_NSPECTV)                 ! Outgoing band-resolved VI flux at TOA (W/m2).
     
    231236
    232237        ! test on allocated necessary because of CLFvarying (two calls to callcorrk in physiq)
     238        if(.not.allocated(QVISsQREF3d)) then
     239          allocate(QVISsQREF3d(ngrid,nlayer,L_NSPECTV,naerkind))
     240        endif
     241        if(.not.allocated(omegaVIS3d)) then
     242          allocate(omegaVIS3d(ngrid,nlayer,L_NSPECTV,naerkind))
     243        endif
     244        if(.not.allocated(gVIS3d)) then
     245          allocate(gVIS3d(ngrid,nlayer,L_NSPECTV,naerkind))
     246        endif
     247        if (.not.allocated(QIRsQREF3d)) then
     248          allocate(QIRsQREF3d(ngrid,nlayer,L_NSPECTI,naerkind))
     249        endif
     250        if (.not.allocated(omegaIR3d)) then
     251          allocate(omegaIR3d(ngrid,nlayer,L_NSPECTI,naerkind))
     252        endif
     253        if (.not.allocated(gIR3d)) then
     254          allocate(gIR3d(ngrid,nlayer,L_NSPECTI,naerkind))
     255        endif
     256        if (.not.allocated(tauaero)) then
     257          allocate(tauaero(L_LEVELS,naerkind))
     258        endif
     259       
    233260        if(.not.allocated(QXVAER)) then
    234261          allocate(QXVAER(L_LEVELS,L_NSPECTV,naerkind), stat=ok)
    235262          if (ok /= 0) then
    236263             write(*,*) "memory allocation failed for QXVAER!"
    237              call abort_physic(subname,'allocation failurei for QXVAER',1)
     264             call abort_physic(subname,'allocation failure for QXVAER',1)
    238265          endif
    239266        endif
  • trunk/LMDZ.GENERIC/libf/phystd/callsedim.F

    r2671 r2972  
    5454
    5555      ! for particles with varying radii:
    56       real reffrad(ngrid,nlay,naerkind) ! particle radius (m)
    57       real nueffrad(ngrid,nlay,naerkind) ! aerosol effective radius variance
     56      real,allocatable,save :: reffrad(:,:,:) ! particle radius (m)
     57      real,allocatable,save :: nueffrad(:,:,:) ! aerosol effective radius variance
     58!$OMP THREADPRIVATE(reffrad,nueffrad)
    5859
    5960      real zqi(ngrid,nlay,nq) ! to locally store tracers
     
    7980          stop
    8081        endif
     82        ! allocate "naerkind" size local arrays (which are also
     83        ! "saved" so that this is done only once in for all even if
     84        ! we don't need to store the value from a time step to the next)
     85        allocate(reffrad(ngrid,nlay,naerkind))
     86        allocate(nueffrad(ngrid,nlay,naerkind))
    8187      ENDIF ! of IF (firstcall)
    8288     
  • trunk/LMDZ.GENERIC/libf/phystd/condense_co2.F90

    r1543 r2972  
    66          pdtc,pdtsrfc,pdpsrfc,pdqc)
    77
    8       use radinc_h, only : L_NSPECTV, naerkind
     8      use radinc_h, only : L_NSPECTV
    99      use gases_h, only: gfrac, igas_co2
    1010      use radii_mod, only : co2_reffrad
  • trunk/LMDZ.GENERIC/libf/phystd/dyn1d/rcm1d.F

    r2785 r2972  
    2929      USE vertical_layers_mod, ONLY: init_vertical_layers
    3030      USE logic_mod, ONLY: hybrid
     31      use radinc_h, only: naerkind
    3132      use regular_lonlat_mod, only: init_regular_lonlat
    3233      use planete_mod, only: ini_planete_mod
     
    154155c INITIALISATION
    155156c=======================================================================
     157! check if 'rcm1d.def' file is around
     158      open(90,file='rcm1d.def',status='old',form='formatted',
     159     &     iostat=ierr)
     160      if (ierr.ne.0) then
     161        write(*,*) 'Cannot find required file "rcm1d.def"'
     162        write(*,*) 'which should contain some input parameters'
     163        write(*,*) ' ... might as well stop here ...'
     164        stop
     165      else
     166        close(90)
     167      endif
     168
     169! now, run.def is needed anyway. so we create a dummy temporary one
     170! for ioipsl to work. if a run.def is already here, stop the
     171! program and ask the user to do a bit of cleaning
     172      open(90,file='run.def',status='old',form='formatted',
     173     &     iostat=ierr)
     174      if (ierr.eq.0) then
     175        close(90)
     176        write(*,*) 'There is already a run.def file.'
     177        write(*,*) 'This is not compatible with 1D runs.'
     178        write(*,*) 'Please remove the file and restart the run.'
     179        write(*,*) 'Runtime parameters are supposed to be in rcm1d.def'
     180        stop
     181      else
     182        call system('touch run.def')
     183        call system("echo 'INCLUDEDEF=callphys.def' >> run.def")
     184        call system("echo 'INCLUDEDEF=rcm1d.def' >> run.def")
     185      endif
    156186
    157187      ! read nq from traceur.def
     
    187217      ! Initialize dimphy module
    188218      call init_dimphy(1,llm)
     219     
    189220      ! now initialize arrays using phys_state_var_init
     221      ! but first initialise naerkind (from callphys.def)
     222      naerkind=0 !default
     223      call getin("naerkind",naerkind)
     224     
    190225      call phys_state_var_init(nq)
    191226     
     
    221256c ------------------------------------------------------
    222257
    223 ! check if 'rcm1d.def' file is around
    224       open(90,file='rcm1d.def',status='old',form='formatted',
    225      &     iostat=ierr)
    226       if (ierr.ne.0) then
    227         write(*,*) 'Cannot find required file "rcm1d.def"'
    228         write(*,*) 'which should contain some input parameters'
    229         write(*,*) ' ... might as well stop here ...'
    230         stop
    231       else
    232         close(90)
    233       endif
    234 
    235 ! now, run.def is needed anyway. so we create a dummy temporary one
    236 ! for ioipsl to work. if a run.def is already here, stop the
    237 ! program and ask the user to do a bit of cleaning
    238       open(90,file='run.def',status='old',form='formatted',
    239      &     iostat=ierr)
    240       if (ierr.eq.0) then
    241         close(90)
    242         write(*,*) 'There is already a run.def file.'
    243         write(*,*) 'This is not compatible with 1D runs.'
    244         write(*,*) 'Please remove the file and restart the run.'
    245         write(*,*) 'Runtime parameters are supposed to be in rcm1d.def'
    246         stop
    247       else
    248         call system('touch run.def')
    249         call system("echo 'INCLUDEDEF=callphys.def' >> run.def")
    250         call system("echo 'INCLUDEDEF=rcm1d.def' >> run.def")
    251       endif
    252258
    253259! check if we are going to run with or without tracers
  • trunk/LMDZ.GENERIC/libf/phystd/inifis_mod.F90

    r2958 r2972  
    1111  use init_print_control_mod, only: init_print_control
    1212  use radinc_h, only: ini_radinc_h, naerkind
     13  use radcommon_h, only: ini_radcommon_h
    1314  use radii_mod, only: radfixed, Nmix_co2
    1415  use datafile_mod, only: datadir
     
    615616     if (is_master) write(*,*)trim(rname)//": Nmix_co2 = ",Nmix_co2
    616617
    617 !         write(*,*)"Number of radiatively active aerosols:"
    618 !         naerkind=0. ! default value
    619 !         call getin_p("naerkind",naerkind)
    620 !         write(*,*)" naerkind = ",naerkind
     618     if (is_master) write(*,*)trim(rname)//&
     619       "Number of radiatively active aerosols:"
     620     naerkind=0 ! default value
     621     call getin_p("naerkind",naerkind)
     622     if (is_master) write(*,*)trim(rname)//": naerkind = ",naerkind
    621623
    622624     if (is_master) write(*,*)trim(rname)//": Opacity of dust (if used):"
     
    11591161  ! initialize variables in radinc_h
    11601162  call ini_radinc_h(nlayer,tplanckmin,tplanckmax,dtplanck)
    1161  
     1163
     1164  ! initialize variables and allocate arrays in radcommon_h
     1165  call ini_radcommon_h(naerkind)
     1166   
    11621167  ! allocate "comsoil_h" arrays
    11631168  call ini_comsoil_h(ngrid)
  • trunk/LMDZ.GENERIC/libf/phystd/optci.F90

    r2957 r2972  
    5858  real*8,intent(in) ::  GIAER(L_LEVELS,L_NSPECTI,NAERKIND)
    5959  real*8,intent(in) ::  TAUAERO(L_LEVELS,NAERKIND)
    60   real*8  TAUAEROLK(L_LEVELS,L_NSPECTI,NAERKIND)
    61   real*8  TAEROS(L_LEVELS,L_NSPECTI,NAERKIND)
     60
     61  ! local variables (saved for convenience as need be allocated)
     62  real*8,save,allocatable :: TAUAEROLK(:,:,:)
     63  real*8,save,allocatable :: TAEROS(:,:,:)
     64!$OMP THREADPRIVATE(TAUAEROLK,TAEROS)
    6265
    6366  integer L, NW, NG, K, LK, IAER
     
    9497
    9598  integer interm
     99 
     100  logical :: firstcall=.true.
     101!$OMP THREADPRIVATE(firstcall)
    96102
    97103  !--- Kasting's CIA ----------------------------------------
     
    107113  !     -1.7,-1.7,-1.7,-1.7,-1.7,-1.7,-1.7, -1.7,0.0 ]
    108114  !----------------------------------------------------------
     115
     116  if (firstcall) then
     117    ! allocate local arrays of size "naerkind" (which are also
     118    ! "saved" so that this is done only once in for all even if
     119    ! we don't need to store the value from a time step to the next)
     120    allocate(TAUAEROLK(L_LEVELS,L_NSPECTI,NAERKIND))
     121    allocate(TAEROS(L_LEVELS,L_NSPECTI,NAERKIND))
     122    firstcall=.false.
     123  endif ! of if (firstcall)
    109124
    110125  !! AS: to save time in computing continuum (see bilinearbig)
  • trunk/LMDZ.GENERIC/libf/phystd/optcv.F90

    r2875 r2972  
    4747
    4848
    49   real*8 DTAUV(L_NLAYRAD,L_NSPECTV,L_NGAUSS)
     49  real*8,intent(out) :: DTAUV(L_NLAYRAD,L_NSPECTV,L_NGAUSS)
    5050  real*8 DTAUKV(L_LEVELS,L_NSPECTV,L_NGAUSS)
    51   real*8 TAUV(L_NLEVRAD,L_NSPECTV,L_NGAUSS)
    52   real*8 TAUCUMV(L_LEVELS,L_NSPECTV,L_NGAUSS)
    53   real*8 PLEV(L_LEVELS)
    54   real*8 TMID(L_LEVELS), PMID(L_LEVELS)
    55   real*8 COSBV(L_NLAYRAD,L_NSPECTV,L_NGAUSS)
    56   real*8 WBARV(L_NLAYRAD,L_NSPECTV,L_NGAUSS)
     51  real*8,intent(out) :: TAUV(L_NLEVRAD,L_NSPECTV,L_NGAUSS)
     52  real*8,intent(out) :: TAUCUMV(L_LEVELS,L_NSPECTV,L_NGAUSS)
     53  real*8,intent(in) :: PLEV(L_LEVELS)
     54  real*8,intent(in) :: TMID(L_LEVELS), PMID(L_LEVELS)
     55  real*8,intent(out) :: COSBV(L_NLAYRAD,L_NSPECTV,L_NGAUSS)
     56  real*8,intent(out) :: WBARV(L_NLAYRAD,L_NSPECTV,L_NGAUSS)
    5757
    5858  ! for aerosols
    59   real*8  QXVAER(L_LEVELS,L_NSPECTV,NAERKIND)
    60   real*8  QSVAER(L_LEVELS,L_NSPECTV,NAERKIND)
    61   real*8  GVAER(L_LEVELS,L_NSPECTV,NAERKIND)
    62   real*8  TAUAERO(L_LEVELS,NAERKIND)
    63   real*8  TAUAEROLK(L_LEVELS,L_NSPECTV,NAERKIND)
    64   real*8  TAEROS(L_LEVELS,L_NSPECTV,NAERKIND)
     59  real*8,intent(in) :: QXVAER(L_LEVELS,L_NSPECTV,NAERKIND)
     60  real*8,intent(in) :: QSVAER(L_LEVELS,L_NSPECTV,NAERKIND)
     61  real*8,intent(in) :: GVAER(L_LEVELS,L_NSPECTV,NAERKIND)
     62  real*8,intent(in) :: TAUAERO(L_LEVELS,NAERKIND)
     63 
     64  ! local arrays (saved for convenience as need be allocated)
     65  real*8,save,allocatable :: TAUAEROLK(:,:,:)
     66  real*8,save,allocatable :: TAEROS(:,:,:)
     67!$OMP THREADPRIVATE(TAUAEROLK,TAEROS)
    6568
    6669  integer L, NW, NG, K, LK, IAER
    6770  integer MT(L_LEVELS), MP(L_LEVELS), NP(L_LEVELS)
    6871  real*8  ANS, TAUGAS
    69   real*8  TAURAY(L_NSPECTV)
     72  real*8,intent(in) :: TAURAY(L_NSPECTV)
    7073  real*8  TRAY(L_LEVELS,L_NSPECTV)
    7174  real*8  DPR(L_LEVELS), U(L_LEVELS)
    7275  real*8  LCOEF(4), LKCOEF(L_LEVELS,4)
    7376
    74   real*8 taugsurf(L_NSPECTV,L_NGAUSS-1)
     77  real*8,intent(out) :: taugsurf(L_NSPECTV,L_NGAUSS-1)
    7578  real*8 DCONT,DAERO
    7679  real*8 DRAYAER
     
    7982
    8083  ! variable species mixing ratio variables
    81   real*8  QVAR(L_LEVELS), WRATIO(L_LEVELS), MUVAR(L_LEVELS)
     84  real*8,intent(in) :: QVAR(L_LEVELS)
     85  real*8,intent(in) :: MUVAR(L_LEVELS)
     86  real*8 :: WRATIO(L_LEVELS)
    8287  real*8  KCOEF(4)
    8388  integer NVAR(L_LEVELS)
     
    99104
    100105  integer interm
     106
     107  logical :: firstcall=.true.
     108!$OMP THREADPRIVATE(firstcall)
     109
     110  if (firstcall) then
     111    ! allocate local arrays of size "naerkind" (which are also
     112    ! "saved" so that this is done only once in for all even if
     113    ! we don't need to store the value from a time step to the next)
     114    allocate(TAUAEROLK(L_LEVELS,L_NSPECTV,NAERKIND))
     115    allocate(TAEROS(L_LEVELS,L_NSPECTV,NAERKIND))
     116    firstcall=.false.
     117  endif ! of if (firstcall)
    101118
    102119  !! AS: to save time in computing continuum (see bilinearbig)
  • trunk/LMDZ.GENERIC/libf/phystd/physiq_mod.F90

    r2958 r2972  
    2020      use gases_h, only: gnom, gfrac
    2121      use radcommon_h, only: sigma, glat, grav, BWNV, WNOI, DWNI, DWNV, WNOV
     22      use suaer_corrk_mod, only: suaer_corrk
    2223      use radii_mod, only: h2o_reffrad, co2_reffrad
    2324      use aerosol_mod, only: iniaerosol, iaero_co2, iaero_h2o
     
    260261!     for the "naerkind" optically active aerosols:
    261262
    262       real aerosol(ngrid,nlayer,naerkind) ! Aerosols.
     263      real,save,allocatable :: aerosol(:,:,:) ! Aerosols
     264!$OMP THREADPRIVATE(aerosol)
    263265      real zh(ngrid,nlayer)               ! Potential temperature (K).
    264266      real pw(ngrid,nlayer)               ! Vertical velocity (m/s). (NOTE : >0 WHEN DOWNWARDS !!)
     
    342344      REAL,allocatable,save :: zdqchim(:,:,:) ! Calchim_asis routine
    343345      REAL,allocatable,save :: zdqschim(:,:)  ! Calchim_asis routine
     346!$OMP THREADPRIVATE(zdqchim,zdqschim)
    344347
    345348      REAL array_zero1(ngrid)
     
    441444      real muvar(ngrid,nlayer+1) ! For Runaway Greenhouse 1D study. By RW
    442445
    443       real reffcol(ngrid,naerkind)
     446      real,save,allocatable :: reffcol(:,:)
     447!$OMP THREADPRIVATE(reffcol)
    444448
    445449!     Sourceevol for 'accelerated ice evolution'. By RW
     
    513517!        ~~~~~~~~~~~~~~~~~~~~~~~~~~~
    514518         call iniaerosol
     519         ! allocate related local arrays
     520         ! (need be allocated instead of automatic because of "naerkind")
     521         allocate(aerosol(ngrid,nlayer,naerkind))
     522         allocate(reffcol(ngrid,naerkind))
    515523
    516524#ifdef CPP_XIOS
  • trunk/LMDZ.GENERIC/libf/phystd/radcommon_h.F90

    r2297 r2972  
    11module radcommon_h
    22      use radinc_h, only: L_NSPECTI, L_NSPECTV, NTstart, NTstop, &
    3                           naerkind, nsizemax
     3                          nsizemax
    44      implicit none
    55
     
    9393        !$OMP FZEROI,FZEROV)     !pgasmin,pgasmax,tgasmin,tgasmax read by master in sugas_corrk
    9494
    95       real QVISsQREF(L_NSPECTV,naerkind,nsizemax)
    96       real omegavis(L_NSPECTV,naerkind,nsizemax)
    97       real gvis(L_NSPECTV,naerkind,nsizemax)
    98       real QIRsQREF(L_NSPECTI,naerkind,nsizemax)
    99       real omegair(L_NSPECTI,naerkind,nsizemax)
    100       real gir(L_NSPECTI,naerkind,nsizemax)
     95      real,allocatable,save :: QVISsQREF(:,:,:)
     96      real,allocatable,save :: omegavis(:,:,:)
     97      real,allocatable,save :: gvis(:,:,:)
     98      real,allocatable,save :: QIRsQREF(:,:,:)
     99      real,allocatable,save :: omegair(:,:,:)
     100      real,allocatable,save :: gir(:,:,:)
    101101!$OMP THREADPRIVATE(QVISsQREF,omegavis,gvis,QIRsQREF,omegair,gir)
    102102
     
    105105! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    106106
    107       REAL lamrefir(naerkind),lamrefvis(naerkind)
    108 
     107      real,allocatable,save :: lamrefir(:),lamrefvis(:)
     108!$OMP THREADPRIVATE(lamrefir,lamrefvis)
    109109! Actual number of grain size classes in each domain for a
    110110!   given aerosol:
    111111
    112       INTEGER          :: nsize(naerkind,2)
     112      integer,allocatable,save :: nsize(:,:)
     113!$OMP THREADPRIVATE(nsize) ! nsize filled by suaer_corrk
    113114
    114115! Particle size axis (depend on the kind of aerosol and the
    115116!   radiation domain)
    116117
    117       DOUBLE PRECISION :: radiustab(naerkind,2,nsizemax)
    118 !$OMP THREADPRIVATE(lamrefir,lamrefvis,radiustab) !nsize read by suaer_corrk
     118      double precision,allocatable,save :: radiustab(:,:,:)
     119!$OMP THREADPRIVATE(radiustab)
    119120
    120121! Extinction coefficient at reference wavelengths;
     
    122123!   longrefvis and longrefir.
    123124
    124       REAL :: QREFvis(naerkind,nsizemax)
    125       REAL :: QREFir(naerkind,nsizemax)
     125      real,allocatable,save :: QREFvis(:,:)
     126      real,allocatable,save :: QREFir(:,:)
    126127!      REAL :: omegaREFvis(naerkind,nsizemax)
    127       REAL :: omegaREFir(naerkind,nsizemax)
     128      real,allocatable,save :: omegaREFir(:,:)
    128129
    129130      REAL,SAVE :: tstellar ! Stellar brightness temperature (SW)
     
    160161!$OMP THREADPRIVATE(glat,eclipse)
    161162
     163contains
     164     
     165subroutine ini_radcommon_h(naerkind)
     166  ! Initialize module variables
     167  implicit none
     168  integer,intent(in) :: naerkind
     169
     170  allocate(QVISsQREF(L_NSPECTV,naerkind,nsizemax))
     171  allocate(omegavis(L_NSPECTV,naerkind,nsizemax))
     172  allocate(gvis(L_NSPECTV,naerkind,nsizemax))
     173  allocate(QIRsQREF(L_NSPECTI,naerkind,nsizemax))
     174  allocate(omegair(L_NSPECTI,naerkind,nsizemax))
     175  allocate(gir(L_NSPECTI,naerkind,nsizemax))
     176 
     177  allocate(lamrefir(naerkind))
     178  allocate(lamrefvis(naerkind))
     179  allocate(nsize(naerkind,2))
     180  allocate(radiustab(naerkind,2,nsizemax))
     181 
     182  allocate(QREFvis(naerkind,nsizemax))
     183  allocate(QREFir(naerkind,nsizemax))
     184  allocate(omegaREFir(naerkind,nsizemax))
     185 
     186end subroutine ini_radcommon_h
     187
    162188end module radcommon_h
  • trunk/LMDZ.GENERIC/libf/phystd/radinc_h.F90

    r2283 r2972  
    44
    55  include "bands.h"
    6   include "scatterers.h"
     6
     7  integer,save :: naerkind ! number of radiatively active aerosols
     8                           ! set via inifis
     9!$OMP THREADPRIVATE(naerkind)
    710
    811!======================================================================
  • trunk/LMDZ.GENERIC/libf/phystd/suaer_corrk.F90

    r2831 r2972  
    1       subroutine suaer_corrk
     1module suaer_corrk_mod
     2
     3implicit none
     4
     5contains
     6
     7subroutine suaer_corrk
    28
    39      ! inputs
     
    1016      use radcommon_h, only: radiustab,nsize,tstellar
    1117      use radcommon_h, only: qrefvis,qrefir,omegarefir !,omegarefvis
    12       use aerosol_mod
     18      use aerosol_mod, only: noaero,iaero_co2,iaero_h2o,iaero_dust,iaero_h2so4
     19      use aerosol_mod, only: iaero_back2lay,iaero_nh3,iaero_nlay,iaero_aurora
     20      use aerosol_mod, only: iaero_venus1,iaero_venus2,iaero_venus2p
     21      use aerosol_mod, only: iaero_venus3,iaero_venusUV
     22      use aerosol_mod, only: iaero_generic,i_rgcs_ice
    1323      use callkeys_mod, only: tplanet, optprop_back2lay_vis, optprop_back2lay_ir, &
    1424                              optprop_aeronlay_vis, optprop_aeronlay_ir,          &
    1525                              aeronlay_lamref, nlayaero,aerogeneric
    1626      use tracer_h, only: noms
     27     
     28      use mod_phys_lmdz_para, only : is_master, bcast
     29
    1730      implicit none
    1831
     
    4861
    4962!     Optical properties (read in external ASCII files)
    50       INTEGER,SAVE      :: nwvl  ! Number of wavelengths in
     63      INTEGER      :: nwvl  ! Number of wavelengths in
    5164                                ! the domain (VIS or IR), read by master
    5265
     
    5568
    5669      REAL, DIMENSION(:),&
    57       ALLOCATABLE, SAVE :: wvl  ! Wavelength axis, read by master
     70      ALLOCATABLE :: wvl  ! Wavelength axis, read by master
    5871      REAL, DIMENSION(:),&
    59       ALLOCATABLE, SAVE :: radiusdyn ! Particle size axis, read by master
     72      ALLOCATABLE :: radiusdyn ! Particle size axis, read by master
    6073
    6174      REAL, DIMENSION(:,:),&
    62       ALLOCATABLE, SAVE :: ep,& ! Extinction coefficient Qext, read by master
     75      ALLOCATABLE :: ep,& ! Extinction coefficient Qext, read by master
    6376      omeg,&                    ! Single Scattering Albedo, read by master
    6477      gfactor                   ! Assymetry Factor, read by master
     
    95108!     Local saved variables:
    96109
    97       CHARACTER(LEN=50), DIMENSION(naerkind,2), SAVE :: file_id
    98 !$OMP THREADPRIVATE(file_id)
     110      CHARACTER(LEN=50),ALLOCATABLE :: file_id(:,:)
     111
    99112!---- Please indicate the names of the optical property files below
    100113!     Please also choose the reference wavelengths of each aerosol     
     
    119132
    120133!--------------------------------------------------------------
     134      ! allocate file_id, as naerkind is a variable
     135      allocate(file_id(naerkind,2))
     136
    121137      if (noaero) then
    122138        print*, 'naerkind= 0'
     
    344360      QIRsQREF(:,:,:)  = 0.0
    345361
    346       DO iaer = 1, naerkind     ! Loop on aerosol kind
    347          DO idomain = 1, 2      ! Loop on radiation domain (VIS or IR)
     362  DO iaer = 1, naerkind     ! Loop on aerosol kind
     363    DO idomain = 1, 2      ! Loop on radiation domain (VIS or IR)
    348364!==================================================================
    349365!     1. READ OPTICAL PROPERTIES
     
    352368!     1.1 Open the ASCII file
    353369
    354 !$OMP MASTER
    355 
     370!!!!$OMP MASTER
     371      if (is_master) then
     372         
    356373            INQUIRE(FILE=TRIM(datadir)//'/'//TRIM(aerdir)//&
    357374                    '/'//TRIM(file_id(iaer,idomain)),&
     
    415432      ENDDO
    416433
     434      endif ! of if (is_master)
     435
     436      ! broadcast nwvl and nsize to all cores
     437      call bcast(nwvl)
     438      call bcast(nsize)
     439
    417440      ALLOCATE(wvl(nwvl))       ! wvl
    418441      ALLOCATE(radiusdyn(nsize(iaer,idomain))) ! radiusdyn
     
    424447!     1.3 Read the data
    425448
     449      if (is_master) then
    426450      jfile = 1
    427451      endwhile = .false.
     
    504528      endif
    505529
    506 !$OMP END MASTER
    507 !$OMP BARRIER
    508 
    509 
    510 
     530      endif ! of if (is_master)
     531
     532      ! broadcast arrays to all cores
     533      call bcast(wvl)
     534      call bcast(radiusdyn)
     535      call bcast(ep)
     536      call bcast(omeg)
     537      call bcast(gfactor)
    511538
    512539!==================================================================
     
    588615
    589616
    590       ENDDO                    ! isize (particle size) -------------------------------------
     617         ENDDO ! isize (particle size) -------------------------------------
    591618
    592619      END SELECT domain
     
    596623!========================================================================
    597624
    598 !$OMP BARRIER
    599 !$OMP MASTER
    600       IF (ALLOCATED(wvl)) DEALLOCATE(wvl)                 ! wvl
    601       IF (ALLOCATED(radiusdyn)) DEALLOCATE(radiusdyn)     ! radiusdyn
    602       IF (ALLOCATED(ep)) DEALLOCATE(ep)                   ! ep
    603       IF (ALLOCATED(omeg)) DEALLOCATE(omeg)               ! omeg
    604       IF (ALLOCATED(gfactor)) DEALLOCATE(gfactor)         ! g
    605 !$OMP END MASTER
    606 !$OMP BARRIER
    607 
    608       END DO                    ! Loop on iaer
    609       END DO                    ! Loop on idomain
     625      DEALLOCATE(wvl)             ! wvl
     626      DEALLOCATE(radiusdyn)       ! radiusdyn
     627      DEALLOCATE(ep)              ! ep
     628      DEALLOCATE(omeg)            ! omeg
     629      DEALLOCATE(gfactor)         ! g
     630
     631    END DO                    ! Loop on iaer
     632  END DO                    ! Loop on idomain
    610633!========================================================================
    611       RETURN
    612 
    613 
    614 
    615     END subroutine suaer_corrk
     634 
     635  ! cleanup
     636  deallocate(file_id)
     637
     638end subroutine suaer_corrk
    616639     
     640end module suaer_corrk_mod
Note: See TracChangeset for help on using the changeset viewer.