Changeset 2584 for trunk


Ignore:
Timestamp:
Nov 16, 2021, 3:23:31 PM (4 years ago)
Author:
romain.vande
Message:

Second stage of implementation of Open_MP in the physic.
Run with callrad=.true.

Location:
trunk/LMDZ.MARS
Files:
11 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/README

    r2579 r2584  
    35113511Fixing missing case for hdo_ice in inichim_newstart
    35123512Should fix issue #25 on gitlab
     3513
     3514== 16/11/2021 == RV
     3515Second stage of implementation of Open_MP in the physic.
     3516Run with callrad=.true.
     3517
  • trunk/LMDZ.MARS/libf/phymars/aeropacity_mod.F

    r2494 r2584  
    173173      INTEGER,SAVE :: naerdust ! number of dust scatterers
    174174
     175!$OMP THREADPRIVATE(cstdustlevel,firstcall,i_ice,
     176!$OMP&                i_co2ice,naerdust)
     177
    175178! initializations
    176179      tau(1:ngrid,1:naerkind)=0
  • trunk/LMDZ.MARS/libf/phymars/aeroptproperties.F

    r2398 r2584  
    4040      REAL, SAVE, ALLOCATABLE :: refftabmax(:,:)
    4141
     42!$OMP THREADPRIVATE(varyingnueff,refftabmin,refftabmax)
     43
    4244c     Log of the min and max variance of the interpolation grid
    4345      REAL, PARAMETER :: nuefftabmin = -4.6
     
    5759c     Pi!
    5860      REAL,SAVE :: pi
     61
     62!$OMP THREADPRIVATE(pi)
     63
    5964c     Variables used by the Gauss-Legendre integration:
    6065      INTEGER radius_id,gausind
     
    6469      REAL weightgaus(ngau),radgaus(ngau)
    6570      SAVE weightgaus,radgaus
     71     
     72!$OMP THREADPRIVATE(weightgaus,radgaus)
     73
    6674c     DATA weightgaus/.2955242247,.2692667193,.2190863625,
    6775c    &                .1494513491,.0666713443/
     
    93101c     Volume ratio of the grid
    94102      REAL,SAVE,ALLOCATABLE :: logvratgrid(:,:)
     103
     104!$OMP THREADPRIVATE(refftab,nuefftab,logvratgrid)
     105
    95106c     Grid used to remember which calculation is done
    96107      LOGICAL,SAVE,ALLOCATABLE :: checkgrid(:,:,:,:)
     
    101112      REAL,SAVE,ALLOCATABLE :: omegVISgrid(:,:,:,:)
    102113      REAL,SAVE,ALLOCATABLE :: gVISgrid(:,:,:,:)
     114
     115!$OMP THREADPRIVATE(checkgrid,qsqrefVISgrid,qextVISgrid,
     116!$OMP&               qscatVISgrid,omegVISgrid,gVISgrid)
     117
     118
    103119c     Optical properties of the grid (INFRARED)
    104120      REAL,SAVE,ALLOCATABLE :: qsqrefIRgrid(:,:,:,:)
     
    107123      REAL,SAVE,ALLOCATABLE :: omegIRgrid(:,:,:,:)
    108124      REAL,SAVE,ALLOCATABLE :: gIRgrid(:,:,:,:)
     125
     126!$OMP THREADPRIVATE(qsqrefIRgrid,qextIRgrid,qscatIRgrid,
     127!$OMP&               omegIRgrid,gIRgrid)
     128
    109129c     Optical properties of the grid (REFERENCE WAVELENGTHS)
    110130      REAL,SAVE,ALLOCATABLE :: qrefVISgrid(:,:,:)
     
    116136c     Firstcall
    117137      LOGICAL,SAVE :: firstcall = .true.
     138
     139!$OMP THREADPRIVATE(qrefVISgrid,qscatrefVISgrid,qrefIRgrid ,   
     140!$OMP&               qscatrefIRgrid,omegrefVISgrid,omegrefIRgrid,
     141!$OMP&               firstcall)
     142
    118143c     Variables used by the Gauss-Legendre integration:
    119144      REAL,SAVE,ALLOCATABLE :: normd(:,:,:,:)
     
    122147      REAL,SAVE,ALLOCATABLE :: radGAUSa(:,:,:)
    123148      REAL,SAVE,ALLOCATABLE :: radGAUSb(:,:,:)
     149
     150!$OMP THREADPRIVATE(normd,dista,distb,radGAUSa,radGAUSb)
    124151
    125152      REAL,SAVE,ALLOCATABLE :: qsqrefVISa(:,:,:)
     
    134161      REAL,SAVE,ALLOCATABLE :: gVISb(:,:,:)
    135162
     163!$OMP THREADPRIVATE(qsqrefVISa,qrefVISa,qsqrefVISb,qrefVISb,   
     164!$OMP&               omegVISa,omegrefVISa,omegVISb,omegrefVISb, 
     165!$OMP&               gVISa,gVISb)
     166
    136167      REAL,SAVE,ALLOCATABLE :: qsqrefIRa(:,:,:)
    137168      REAL,SAVE,ALLOCATABLE :: qrefIRa(:,:)
     
    145176      REAL,SAVE,ALLOCATABLE :: gIRb(:,:,:)
    146177
     178!$OMP THREADPRIVATE(qsqrefIRa,qrefIRa,qsqrefIRb,qrefIRb,       
     179!$OMP&               omegIRa,omegrefIRa,omegIRb,omegrefIRb,gIRa,gIRb)
     180
    147181      REAL :: radiusm
    148182      REAL :: radiusr
     
    178212
    179213      LOGICAL,SAVE :: out_qwg = .false.
     214
     215!$OMP THREADPRIVATE(out_qwg)
     216
    180217      INTEGER, PARAMETER :: out_iaer = 2
    181218      INTEGER :: out_ndim
     
    304341
    305342      DO iaer = 1, naerkind ! Loop on aerosol kind
     343
    306344        IF ( (nsize(iaer,1).EQ.1).AND.(nsize(iaer,2).EQ.1) ) THEN
    307345c==================================================================
     
    460498          ENDIF
    461499        ENDDO
     500
    462501c==================================================================
    463502      IF ( .NOT.varyingnueff(iaer) ) THEN          ! CONSTANT NUEFF
     
    540579     &              )
    541580                ENDDO
     581
    542582                IF (normd(j,1,iaer,idomain).EQ.1e-30) THEN
    543583                  WRITE(*,*)"normd:", normd(j,1,iaer,idomain)
  • trunk/LMDZ.MARS/libf/phymars/callradite_mod.F

    r2494 r2584  
    289289
    290290      real zco2   ! volume fraction of CO2 in Mars atmosphere
     291!$OMP THREADPRIVATE(zco2)
    291292      DATA zco2/0.95/
    292293      SAVE zco2
    293294
    294295      LOGICAL firstcall
     296!$OMP THREADPRIVATE(firstcall)
    295297      DATA firstcall/.true./
    296298      SAVE firstcall
     299
     300
    297301
    298302c----------------------------------------------------------------------
     
    403407         gcp = g/cpp
    404408
     409
    405410c        Loading the optical properties in external look-up tables:
     411
    406412         CALL SUAER
     413         
    407414!         CALL SULW ! this step is now done in ini_yomlw_h
    408415
  • trunk/LMDZ.MARS/libf/phymars/dust_rad_adjust_mod.F90

    r2417 r2584  
    77real,save,allocatable :: dust_rad_adjust_next(:) ! adjustment coefficient
    88                         ! computed for t_scenario of the next sol
     9
     10!$OMP THREADPRIVATE(dust_rad_adjust_prev,dust_rad_adjust_next)
    911
    1012contains
  • trunk/LMDZ.MARS/libf/phymars/nlthermeq.F

    r1775 r2584  
    2222      integer igpmax, ismax
    2323      logical firstcall
     24
     25!$OMP THREADPRIVATE(firstcall,igpmax)
     26
    2427      data firstcall /.true./
    2528      save firstcall, igpmax
  • trunk/LMDZ.MARS/libf/phymars/read_dust_scenario.F90

    r2449 r2584  
    3939integer, save :: timelen,lonlen,latlen
    4040character(len=33),save :: filename
     41
     42!$OMP THREADPRIVATE(firstcall,radeg,pi, &
     43!$OMP                lat,lon,time,tautes,  &
     44!$OMP            timelen,lonlen,latlen,filename)
    4145
    4246realday=mod(zday,669.)
  • trunk/LMDZ.MARS/libf/phymars/rocketduststorm_mod.F90

    r2459 r2584  
    44
    55      REAL, SAVE, ALLOCATABLE :: dustliftday(:) ! dust lifting rate (s-1)
     6
     7!$OMP THREADPRIVATE(dustliftday)
    68     
    79      CONTAINS
  • trunk/LMDZ.MARS/libf/phymars/suaer.F90

    r2494 r2584  
    1313                    nsize
    1414use datafile_mod, only: datadir
     15USE mod_phys_lmdz_transfert_para, ONLY: bcast
    1516IMPLICIT NONE
    1617!==================================================================
     
    6061                       gfactor ! Assymetry Factor
    6162
     63!$OMP THREADPRIVATE(wvl,radiusdyn,ep,omeg,gfactor)
     64
    6265! Local variables:
    6366
     
    9295REAL gav(nir)        ! Average assymetry parameter
    9396
     97!$OMP MASTER
     98
    9499!==================================================================
    95100!---- Please indicate the names of the optical property files below
     
    218223DO iaer = 1, naerkind ! Loop on aerosol kind
    219224  DO idomain = 1, 2   ! Loop on radiation domain (VIS or IR)
     225
    220226!==================================================================
    221227! 1. READ OPTICAL PROPERTIES
     
    368374!       1.4 Close the file
    369375
    370 CLOSE(file_unit)
     376 CLOSE(file_unit)
     377
    371378
    372379!==================================================================
     
    540547DEALLOCATE(gfactor)    ! g
    541548
     549
     550
    542551  END DO ! Loop on iaer
    543552END DO   ! Loop on idomain
     553
     554!$OMP END MASTER
     555
     556      call bcast(longrefvis)
     557      call bcast(longrefir)
     558      call bcast(radiustab)
     559      call bcast(gvis)
     560      call bcast(omegavis)
     561      call bcast(QVISsQREF)
     562      call bcast(gIR)
     563      call bcast(omegaIR)
     564      call bcast(QIRsQREF)
     565      call bcast(QREFvis)
     566      call bcast(QREFir)
     567      call bcast(omegaREFvis)
     568      call bcast(omegaREFir)
     569      call bcast(nsize)
     570
    544571!==================================================================
    545572RETURN
  • trunk/LMDZ.MARS/libf/phymars/topmons_mod.F90

    r2459 r2584  
    55!     sub-grid scale mountain mesh fraction
    66      REAL, SAVE, ALLOCATABLE :: alpha_hmons(:)
     7
     8!$OMP THREADPRIVATE(alpha_hmons)
    79
    810      CONTAINS
  • trunk/LMDZ.MARS/libf/phymars/updatereffrad_mod.F

    r2562 r2584  
    104104      EXTERNAL CBRT
    105105
     106
     107!$OMP THREADPRIVATE(firstcall)
     108
    106109c==================================================================
    107110c 1. Update radius from fields from dynamics or initial state
Note: See TracChangeset for help on using the changeset viewer.