Changeset 2616 for trunk


Ignore:
Timestamp:
Jan 18, 2022, 4:28:31 PM (3 years ago)
Author:
romain.vande
Message:

LMDZ_MARS RV : Open_MP;
Put all the "save" variables as "!$OMP THREADPRIVATE" in phymars.
The code can now be tested, see README for more info

Location:
trunk/LMDZ.MARS
Files:
34 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/README

    r2615 r2616  
    35953595
    35963596== 18/01/2022 == RV
    3597 Put all the "save" variables as "!$OMP THREADPRIVATE" in aeronomars
     3597Put all the "save" variables as "!$OMP THREADPRIVATE" in phymars.
     3598The code can now be tested (comparison between restart(fi), diagfi files)
     3599Compile with the option : -parallel mpi_omp, add these lines in the bash:
     3600export OMP_NUM_THREADS= N
     3601export OMP_STACKSIZE=200M
     3602with "N" of the order of #levels/10
     3603
  • trunk/LMDZ.MARS/libf/phymars/calldrag_noro_mod.F

    r1912 r2616  
    108108
    109109      LOGICAL firstcall
     110
     111!$OMP THREADPRIVATE(firstcall)
     112
    110113      DATA firstcall/.true./
    111114      SAVE firstcall
  • trunk/LMDZ.MARS/libf/phymars/callsedim_mod.F

    r2589 r2616  
    102102!                                    !   CCNs (m)
    103103      real,save :: beta ! correction for the shape of the ice particles (cf. newsedim)
     104     
     105!$OMP THREADPRIVATE(beta)
     106     
    104107c     for ice radius computation
    105108      REAL Mo,No
     
    128131      real,parameter :: rdimin=1.e-8 ! 1.e-7
    129132      real,parameter :: rdimax=1.e-4
     133     
     134!$OMP THREADPRIVATE(rd,rdi)
    130135
    131136c       2) Second size distribution for the log-normal integration
     
    138143      real sigma0
    139144
     145!$OMP THREADPRIVATE(rr)
     146     
    140147c       3) Other local variables used in doubleq
    141148
     
    164171      INTEGER,SAVE :: iccnco2_meteor_mass ! index of tracer containing CCN number
    165172      INTEGER,SAVE :: ico2_ice ! index of tracer containing CCN number
     173     
     174!$OMP THREADPRIVATE(idust_mass,idust_number,iccn_mass,iccn_number)
     175!$OMP THREADPRIVATE(istormdust_mass,istormdust_number,itopdust_mass)
     176!$OMP THREADPRIVATE(itopdust_number)
     177!$OMP THREADPRIVATE(iccnco2_number,iccnco2_mass,iccnco2_h2o_number)
     178!$OMP THREADPRIVATE(iccnco2_h2o_mass_ice)
     179!$OMP THREADPRIVATE(iccnco2_h2o_mass_ccn,ico2_ice)
    166180
    167181
    168182      LOGICAL,SAVE :: firstcall=.true.
     183     
     184!$OMP THREADPRIVATE(firstcall)
    169185
    170186
  • trunk/LMDZ.MARS/libf/phymars/co2cloud.F90

    r2589 r2616  
    208208  logical, save :: &
    209209     firstcall = .true. ! Used to compute saved variables
     210     
     211!$OMP THREADPRIVATE(imicroco2,sigma_iceco2,microtimestep)
     212!$OMP THREADPRIVATE(dev2,Qext1bins,Qextv1mic,radv,rb_cldco2)
     213!$OMP THREADPRIVATE(firstcall)     
     214
    210215!----------------------------------------------------------------------------------------------------------------------!
    211216!-----3) Variables:
  • trunk/LMDZ.MARS/libf/phymars/co2condens_mod.F

    r2601 r2616  
    44
    55      logical, save :: scavco2cond = .false. ! flag for using scavenging_by_co2
     6!$OMP THREADPRIVATE(scavco2cond)
    67     
    78      CONTAINS
     
    131132
    132133      real :: emisref(ngrid)
     134      !$OMP THREADPRIVATE(emisref)
    133135     
    134136      REAL zdq_scav(ngrid,nlayer,nq) ! tendency due to scavenging by co2
     
    156158
    157159      LOGICAL,SAVE :: firstcall = .true. !,firstcall2=.true.
     160     
     161!$OMP THREADPRIVATE(ico2,qco2,mmean,acond,bcond,ccond,m_co2,m_noco2)
     162!$OMP THREADPRIVATE(A,B,firstcall)
    158163
    159164c D.BARDET: for debug
     
    166171      REAL masseq(nlayer),wq(nlayer+1)
    167172      INTEGER ifils,iq2
     173
    168174c----------------------------------------------------------------------
    169175
  • trunk/LMDZ.MARS/libf/phymars/co2snow.F

    r2447 r2616  
    9090      logical, save ::
    9191     &   firstcall = .true.
     92     
     93!$OMP THREADPRIVATE(Kscat,firstcall)     
     94
    9295c=======================================================================
    9396c BEGIN
  • trunk/LMDZ.MARS/libf/phymars/comm_wrf.F90

    r1590 r2616  
    1717  REAL,SAVE,ALLOCATABLE :: comm_TAU_ICE(:)
    1818  REAL,SAVE,ALLOCATABLE :: comm_RICE(:,:)
     19
     20!$OMP THREADPRIVATE(comm_HR_LW,comm_HR_SW,comm_ICETOT,comm_MTOT,comm_QSURFDUST)
     21!$OMP THREADPRIVATE(comm_RDUST,comm_RICE,comm_SWDOWNZ,comm_TAU_DUST,comm_TAU_ICE)
     22!$OMP THREADPRIVATE(comm_VMR_ICE)
    1923
    2024contains
  • trunk/LMDZ.MARS/libf/phymars/compute_dtau_mod.F90

    r2417 r2616  
    88        REAL,SAVE,ALLOCATABLE :: dtau(:) ! Dust opacity difference (at 610Pa)
    99                                         ! between GCM and dust scenario
     10                                         
     11!$OMP THREADPRIVATE(ti_injection_sol,tf_injection_sol,dtau)
    1012
    1113       CONTAINS
     
    4446       
    4547        LOGICAL, SAVE :: firstcall=.TRUE. ! signals first call to physics
     48       
     49!$OMP THREADPRIVATE(nb_daystep,local_time_prev,firstcall)
    4650       
    4751       
  • trunk/LMDZ.MARS/libf/phymars/comsoil_h.F90

    r2578 r2616  
    1414       !                 soil_settings.F)
    1515
    16 !$OMP THREADPRIVATE(layer,mlayer,inertiedat)
     16!$OMP THREADPRIVATE(layer,mlayer,inertiedat,volcapa)
    1717
    1818  ! variables (FC: built in firstcall in soil.F)
  • trunk/LMDZ.MARS/libf/phymars/dimphy.F90

    r1130 r2616  
    77!  INTEGER,SAVE :: kflev
    88
    9 !$OMP THREADPRIVATE(klon)
     9!$OMP THREADPRIVATE(klon,klev,klevp1,klevm1)
    1010
    1111CONTAINS
  • trunk/LMDZ.MARS/libf/phymars/dust_rad_adjust_mod.F90

    r2584 r2616  
    4040  real :: weight ! interpolation weight
    4141  real,save :: zday_prev_call=-666. ! stored value of zday from previous call
     42 
     43!$OMP THREADPRIVATE(  local_time,local_time_prevdt,zday_scenario,zday_scenario_next)
     44!$OMP THREADPRIVATE(firstcall,tau_pref_scenario_next,zday_prev_call)
     45
    4246 
    4347  ! 0. preliminary stuff
  • trunk/LMDZ.MARS/libf/phymars/dustlift.F

    r1266 r2616  
    4848      SAVE stress_seuil
    4949      DATA stress_seuil/0.0225/   ! stress seuil soulevement (N.m2)
     50     
     51!$OMP THREADPRIVATE(stress_seuil)
    5052
    5153#ifdef MESOSCALE
  • trunk/LMDZ.MARS/libf/phymars/eofdump_mod.F90

    r2398 r2616  
    3737
    3838      LOGICAL,SAVE :: firstcall=.true.
     39     
     40!$OMP THREADPRIVATE(count,firstcall)
    3941
    4042!-------------------------------------------------------
     
    9597      logical,save :: firstcall=.true.
    9698      integer,save :: npgrid
     99     
     100!$OMP THREADPRIVATE(firstcall,npgrid)
    97101
    98102
  • trunk/LMDZ.MARS/libf/phymars/improvedclouds_mod.F

    r2437 r2616  
    7171      DATA firstcall/.true./
    7272      SAVE firstcall
     73     
     74!$OMP THREADPRIVATE(firstcall)
    7375
    7476      REAL*8   derf ! Error function
     
    123125      DOUBLE PRECISION dr_cld(nbin_cld)   ! width of each rad_cld bin (m)
    124126      DOUBLE PRECISION vol_cld(nbin_cld)  ! particle volume for each bin (m3)
     127     
     128!$OMP THREADPRIVATE(rb_cld)
    125129
    126130
    127131      REAL sigma_ice ! Variance of the ice and CCN distributions
    128132      SAVE sigma_ice
     133     
     134!$OMP THREADPRIVATE(sigma_ice)
    129135
    130136
     
    137143      LOGICAL test_flag    ! flag for test/debuging outputs
    138144      SAVE    test_flag   
     145     
     146!$OMP THREADPRIVATE(test_flag)
    139147
    140148
  • trunk/LMDZ.MARS/libf/phymars/improvedco2clouds_mod.F90

    r2592 r2616  
    142142  real, save :: &
    143143     sigma_ice  ! Variance of the h2o ice and CCN distributions
     144     
     145!$OMP THREADPRIVATE(sigma_ice)
    144146
    145147  double precision, save :: &
     
    147149     meteor(nlev_meteor,nbin_meteor), &! Meteoritic flux read from file uMeteor
    148150     dev3                              ! 1. / ( sqrt(2.) * sigma_ice )
     151     
     152!$OMP THREADPRIVATE(meteor,dev3)
    149153
    150154  logical, save :: &
    151155     firstcall = .true. ! Used to compute saved variables
     156     
     157!$OMP THREADPRIVATE(firstcall)
     158     
    152159!----------------------------------------------------------------------------------------------------------------------!
    153160!----3) Variables:
     
    243250! 0.1. Bonus: meteoritic component, extract data
    244251!----------------------------------------------------------------------------------------------------------------------!
     252
    245253    if (meteo_flux) then
    246254      ! Check if file exists
  • trunk/LMDZ.MARS/libf/phymars/initracer.F

    r2589 r2616  
    122122      igcm_ohplus=0
    123123      igcm_elec=0
    124 
     124     
    125125      ! 1. find dust tracers
    126126      count=0
  • trunk/LMDZ.MARS/libf/phymars/newsedim_mod.F

    r2448 r2616  
    5252      LOGICAL,SAVE :: firstcall=.true.
    5353
     54!$OMP THREADPRIVATE(firstcall)
     55
    5456c    Traceurs :
    5557c    ~~~~~~~~
     
    6971c     local and saved variable
    7072      real,save :: a,b
     73
     74!$OMP THREADPRIVATE(a,b)
    7175
    7276
  • trunk/LMDZ.MARS/libf/phymars/nirco2abs.F

    r2398 r2616  
    8181      integer,save :: ico2=0 ! index of "co2" tracer
    8282      integer,save :: io=0 ! index of "o" tracer
     83     
     84!$OMP THREADPRIVATE(firstcall,ico2,io)
     85     
    8386c     p0noonlte is a pressure below which non LTE effects are significant.
    8487c     REAL p0nonlte
  • trunk/LMDZ.MARS/libf/phymars/nlte_calc.F

    r2398 r2616  
    2828      subroutine MZESC110 (ig,nl_cts_real, nzy_cts_real,ierr,varerr)
    2929c***********************************************************************
    30 
    3130      implicit none
    3231
     
    354353
    355354         else
    356 
    357355            call intzhunt (iaquiZ, zl(i),c1,p1,mr1,t1, con)
    358356            do kr=1,nbox
  • trunk/LMDZ.MARS/libf/phymars/nuclea.F

    r2561 r2616  
    4949     
    5050      LOGICAL firstcall
     51     
     52!$OMP THREADPRIVATE(firstcall)
     53     
    5154      DATA firstcall/.true./
    5255      SAVE firstcall
  • trunk/LMDZ.MARS/libf/phymars/orodrag_mod.F

    r1913 r2616  
    8686      parameter(kidia=1)
    8787      integer, save :: kfdia ! =NDLO2
     88     
     89!$OMP THREADPRIVATE(kfdia)
    8890
    8991      include "yoegwd.h"
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r2602 r2616  
    519519      logical,save :: check_physics_inputs=.false.
    520520      logical,save :: check_physics_outputs=.false.
     521     
     522!$OMP THREADPRIVATE(check_physics_inputs,check_physics_outputs)     
     523
    521524
    522525c=======================================================================
     
    958961#ifdef DUSTSTORM
    959962!! specific case: save the quantity of dust before adding perturbation
     963
    960964       if (firstcall) then
    961965        pq_tmp(1:ngrid,1:nlayer,1)=pq(1:ngrid,1:nlayer,igcm_dust_mass)
     
    985989     &     rstormdust,rtopdust,totstormfract,clearatm,dsords,dsotop,
    986990     &     alpha_hmons,nohmons,clearsky,totcloudfrac)
     991
    987992           ! case of sub-grid water ice clouds: callradite for the clear case
    988993            IF (CLFvarying) THEN
     
    10581063     &            odpref,tau_pref_gcm(igout),
    10591064     &            odpref,tau(igout,1)*odpref/zplev(igout,1)
     1065
     1066
    10601067c          ---------------------------------------------------------
    10611068c          Call slope parameterization for direct and scattered flux
    10621069c          ---------------------------------------------------------
    10631070           IF(callslope) THEN
     1071
    10641072            print *, 'Slope scheme is on and computing...'
    10651073            DO ig=1,ngrid 
     
    12971305
    12981306      IF(calllott)THEN
    1299 
    13001307        CALL calldrag_noro(ngrid,nlayer,ptimestep,
    13011308     &                 zplay,zplev,pt,pu,pv,zdtgw,zdugw,zdvgw)
     
    13151322
    13161323      IF (calldifv) THEN
    1317 
    13181324         DO ig=1,ngrid
    13191325            zflubid(ig)=fluxrad(ig)+fluxgrd(ig)
     
    13371343     .       .and. callrichsl
    13381344     .       .and. .not.turb_resolved) THEN
     1345
    13391346          DO ig=1, ngrid
    13401347             IF (zh(ig,1) .lt. tsurf(ig)) THEN
     
    13501357
    13511358         IF (tke_heat_flux .ne. 0.) THEN
     1359
    13521360             zz1(:)=(pt(:,1)+pdt(:,1)*ptimestep)*(r/g)*
    13531361     &                 (-alog(zplay(:,1)/zplev(:,1)))
  • trunk/LMDZ.MARS/libf/phymars/rocketduststorm_mod.F90

    r2584 r2616  
    160160   
    161161      LOGICAL,SAVE :: firstcall=.true.
     162     
     163!$OMP THREADPRIVATE(firstcall)
    162164
    163165!     variables for the radiative transfer
  • trunk/LMDZ.MARS/libf/phymars/surfini.F

    r2508 r2616  
    4545! For visualisation : > /u/tnalmd/bin/watercaps gcm_txt_output_file
    4646      INTEGER,SAVE :: icelocationmode = 4
     47     
     48!$OMP THREADPRIVATE(icelocationmode)
    4749       
    4850       
     
    6466     
    6567      REAL,SAVE :: min_icevalue = 500.
     68     
     69!$OMP THREADPRIVATE(min_icevalue)
     70     
    6671      character(len=50) :: string = 'thermal'
    6772     
  • trunk/LMDZ.MARS/libf/phymars/swrayleigh.F

    r1226 r2616  
    5252     S     .248261E+00,-.302031E+00, .129662E+00/
    5353      save cray
     54     
     55!$OMP THREADPRIVATE(cray)
     56     
    5457c----------------------------------------------------------------------
    5558
  • trunk/LMDZ.MARS/libf/phymars/thermcell_main_mars.F90

    r1226 r2616  
    185185      REAL zhc(ngrid,nlayer)
    186186      REAL ratiom(ngrid,nlayer)
     187     
     188!$OMP THREADPRIVATE(A,B)
    187189
    188190! =========================================
  • trunk/LMDZ.MARS/libf/phymars/topmons_mod.F90

    r2584 r2616  
    111111!--------------------------------------------------------
    112112      LOGICAL,SAVE :: firstcall=.true.
     113     
     114!$OMP THREADPRIVATE(firstcall)
     115     
    113116      INTEGER l,ig,tsub,iq,ll
    114117      REAL zq0(ngrid,nlayer,nq)     ! initial tracers
  • trunk/LMDZ.MARS/libf/phymars/vdif_cd.F

    r1238 r2616  
    5656
    5757      REAL karman,nu    ! Von Karman constant and fluid kinematic viscosity
     58     
    5859      LOGICAL firstcal
    5960      DATA karman,nu/.41,0.001/
    6061      DATA firstcal/.true./
    6162      SAVE karman,nu
     63
     64!$OMP THREADPRIVATE(karman,nu)
    6265
    6366c    Local(2):
  • trunk/LMDZ.MARS/libf/phymars/vdif_kc.F

    r1779 r2616  
    210210      INTEGER ico2,iq
    211211      SAVE ico2
     212
     213!$OMP THREADPRIVATE(ico2)
     214
    212215      REAL m_co2, m_noco2, A , B
    213216      SAVE A, B
     217
     218!$OMP THREADPRIVATE(A,B)
     219
    214220      LOGICAL firstcall
    215221      save firstcall
     222
     223!$OMP THREADPRIVATE(firstcall)
     224
    216225      data firstcall/.true./
    217226      REAL zhc(ngrid,nlay)
  • trunk/LMDZ.MARS/libf/phymars/vdifc_mod.F

    r2593 r2616  
    120120      LOGICAL,SAVE :: firstcall=.true.
    121121
     122!$OMP THREADPRIVATE(firstcall)
    122123
    123124c     variable added for CO2 condensation:
     
    127128      REAL,PARAMETER :: tcond1mb=136.27
    128129      REAL,SAVE :: acond,bcond
     130
     131!$OMP THREADPRIVATE(acond,bcond)
    129132     
    130133c     Subtimestep & implicit treatment of water vapor
     
    175178      REAL,SAVE :: ccond
    176179
     180!$OMP THREADPRIVATE(ccond)
     181
    177182c     Theta_m formulation for mass-variation scheme :
    178183c     ~~~~~~~
     
    183188      REAL vmr_co2(ngrid,nlay)
    184189      REAL qco2,mmean
     190
     191!$OMP THREADPRIVATE(ico2,m_co2,m_noco2,A,B)
    185192
    186193      REAL,INTENT(OUT) :: sensibFlux(ngrid)
  • trunk/LMDZ.MARS/libf/phymars/watercloud_mod.F

    r2578 r2616  
    9797      REAL,SAVE :: microtimestep_prev=-999
    9898     
     99      !$OMP THREADPRIVATE(imicro,microtimestep)
     100      !$OMP THREADPRIVATE(microtimestep_prev)
    99101      ! tendency given by clouds (inside the micro loop)
    100102      REAL subpdqcloud(ngrid,nlay,nq) ! cf. pdqcloud
     
    111113      INTEGER iq,ig,l
    112114      LOGICAL,SAVE :: firstcall=.true.
     115     
     116      !$OMP THREADPRIVATE(firstcall)
    113117
    114118! Representation of sub-grid water ice clouds A. Pottier 2013
     
    128132      REAL :: mincloud ! min cloud frac
    129133      LOGICAL, save :: flagcloud=.true.
     134     
     135      !$OMP THREADPRIVATE(flagcloud)
    130136
    131137c    ** un petit test de coherence
  • trunk/LMDZ.MARS/libf/phymars/writediagmicrofi.F

    r2573 r2616  
    7575      real*4,save :: date
    7676      real*4,save :: subdate=0.
    77 !$OMP THREADPRIVATE(date)
     77!$OMP THREADPRIVATE(date,subdate)
    7878
    7979      REAL phis((nbp_lon+1),nbp_lat)
  • trunk/LMDZ.MARS/libf/phymars/wstats_mod.F90

    r2573 r2616  
    4242character (len=50) :: namebis
    4343character (len=50), save :: firstvar
    44 !$OMP THREADPRIVATE(firstvar)
     44!$OMP THREADPRIVATE(mean3d,sd3d,dx3,mean2d,sd2d,dx2,firstvar)
    4545integer :: ierr,varid,nbdim,nid
    4646integer :: meanid,sdid
     
    5959character(len=120),save :: name_def(n_name_def_max)
    6060logical :: getout ! to trigger an early exit if variable not in output list
     61
     62!$OMP THREADPRIVATE(stats_def,n_name_def,name_def)
    6163
    6264! Added to work in parallel mode
  • trunk/LMDZ.MARS/libf/phymars/yamada4.F

    r2311 r2616  
    7676      LOGICAL first
    7777      INTEGER ipas,nlev
     78
     79!$OMP THREADPRIVATE(first,ipas)
     80
    7881      SAVE first,ipas
    7982!FH/IM     DATA first,ipas/.true.,0/
     
    9497      REAL ric,rifc,b1,kap
    9598      SAVE ric,rifc,b1,kap
     99
     100!$OMP THREADPRIVATE(ric,rifc,b1,kap)
     101
    96102      DATA ric,rifc,b1,kap/0.195,0.191,16.6,0.4/
    97103      REAL frif,falpha,fsm
     
    102108     s  ,w2yam(ngrid,nlay),t2yam(ngrid,nlay)
    103109      LOGICAL,SAVE :: firstcall=.true.
     110
     111!$OMP THREADPRIVATE(firstcall)
     112
    104113      frif(ri)=0.6588*(ri+0.1776-sqrt(ri*ri-0.3221*ri+0.03156))
    105114      falpha(ri)=1.318*(0.2231-ri)/(0.2341-ri)
     
    112121! MARS
    113122      REAL,SAVE :: q2min,q2max,knmin,kmmin
     123
     124!$OMP THREADPRIVATE(q2min,q2max,knmin,kmmin)
     125
    114126      DATA q2min,q2max,knmin,kmmin/1.E-10,1.E+2,1.E-5,1.E-5/
    115127      INTEGER ico2,iq
     
    123135      REAL ztimestep
    124136      INTEGER :: ndt
     137
     138!$OMP THREADPRIVATE(ico2,A,B)
    125139
    126140      nlev=nlay+1
Note: See TracChangeset for help on using the changeset viewer.