Changeset 2578 for trunk/LMDZ.MARS/libf


Ignore:
Timestamp:
Oct 29, 2021, 1:00:06 PM (4 years ago)
Author:
romain.vande
Message:

First stage of implementing Open_MP in the physic.
So far it can initialyse physic and run with all routines at .FALSE.

Location:
trunk/LMDZ.MARS/libf
Files:
16 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/aeronomars/calchim_mod.F90

    r2563 r2578  
    66  REAL,SAVE,ALLOCATABLE :: zdqchim(:,:,:) ! Tendancy on pq due to photochemistry
    77  REAL,SAVE,ALLOCATABLE :: zdqschim(:,:) ! Tendancy on qsurf due to photochemistry
     8
     9!$OMP THREADPRIVATE(ichemistry,zdqchim,zdqschim)
    810
    911  CONTAINS
  • trunk/LMDZ.MARS/libf/phymars/comgeomfi_h.F90

    r1952 r2578  
    88       REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: sinlat
    99       REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: coslat
     10
     11!$OMP THREADPRIVATE(sinlon,coslon,sinlat,coslat)
    1012
    1113       contains
  • trunk/LMDZ.MARS/libf/phymars/comsaison_h.F90

    r1974 r2578  
    1010  real,save,allocatable :: fract(:)
    1111  real,save,allocatable :: local_time(:) ! local solar time as fraction of day (0,1)
     12
     13!$OMP THREADPRIVATE(callsais,isaison,dist_sol,declin,mu0,fract,local_time)
    1214
    1315contains
  • trunk/LMDZ.MARS/libf/phymars/comsoil_h.F90

    r1770 r2578  
    1414       !                 soil_settings.F)
    1515
     16!$OMP THREADPRIVATE(layer,mlayer,inertiedat)
     17
    1618  ! variables (FC: built in firstcall in soil.F)
    1719  REAL,SAVE,ALLOCATABLE :: tsoil(:,:)       ! sub-surface temperatures (K)
     
    2325  real,save,allocatable :: beta(:,:)        ! beta_k coefficients
    2426  real,save :: mu
     27
     28!$OMP THREADPRIVATE(tsoil,mthermdiff,thermdiff,coefq,coefd,alph,beta,mu )
    2529
    2630contains
  • trunk/LMDZ.MARS/libf/phymars/conc_mod.F90

    r1770 r2578  
    77  real,save,allocatable :: cpnew(:,:)  ! specicic heat
    88  real,save,allocatable :: rnew(:,:)   ! specific gas constant
     9
     10!$OMP THREADPRIVATE(mmean,Akknew,cpnew,rnew)
    911 
    1012contains
  • trunk/LMDZ.MARS/libf/phymars/dimradmars_mod.F90

    r2448 r2578  
    1313  integer,save :: NDLO2 !=NDLON
    1414
     15!$OMP THREADPRIVATE(NFLEV,ndomainsz,NDLON,NDLO2)
    1516
    1617! Number of kind of tracer radiative properties
     
    2425  ! AS: previously in aerkind.h
    2526  character*20, SAVE, ALLOCATABLE :: name_iaer(:)  ! name of the scatterers
     27
     28!$OMP THREADPRIVATE(naerkind,name_iaer)
     29
    2630  integer iaer_dust_conrath ! Typical dust profiles using a
    2731                            ! Conrath type analytical equation
     
    4448  INTEGER,SAVE,ALLOCATABLE :: iaerdust(:)
    4549
     50!$OMP THREADPRIVATE(iaerdust)
     51
    4652  ! AS: was in suaer
    4753  CHARACTER(LEN=30), SAVE, ALLOCATABLE :: file_id(:,:)
     54
     55!$OMP THREADPRIVATE(file_id)
    4856
    4957! Reference wavelengths used to compute reference optical depth (m)
    5058! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    5159  REAL,SAVE,ALLOCATABLE :: longrefir(:),longrefvis(:)
     60!$OMP THREADPRIVATE(longrefir,longrefvis)
    5261 
    5362! Definition of spectral intervals at thermal infrared wavelengths (LW)
     
    7382  real,save :: sunfr(2) = (/ 0.274490 , 0.725509 /)
    7483
     84!$OMP THREADPRIVATE(sunfr)
     85
    7586! Maximum number of grain size classes
    7687! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
     
    111122  REAL,SAVE,ALLOCATABLE :: nueffdust(:,:) ! Dust effective variance
    112123
     124!$OMP THREADPRIVATE(dtrad,fluxrad_sky,fluxrad,albedo,totcloudfrac,aerosol,      &
     125!$OMP                nueffdust)
     126
    113127!! ------------------------------------------------------
    114128!! AS: what was previously in yomaer
     
    139153  real,save,allocatable :: omegaIR(:,:,:)
    140154  real,save,allocatable :: gIR(:,:,:)
     155
     156!$OMP THREADPRIVATE(tauvis,QVISsQREF,omegavis,gvis,QIRsQREF,omegaIR,gIR)
     157
    141158! Actual number of grain size classes in each domain for a
    142159!   given aerosol:
     
    152169  real,save,allocatable :: omegaREFvis(:,:)
    153170  real,save,allocatable :: omegaREFir(:,:)
     171
     172!$OMP THREADPRIVATE(nsize,radiustab,QREFvis,QREFir,omegaREFvis,omegaREFir)
     173
    154174!! ------------------------------------------------------
    155175
  • trunk/LMDZ.MARS/libf/phymars/dust_param_mod.F90

    r2417 r2578  
    88  LOGICAL,SAVE :: freedust ! if true: no rescaling (via tauscaling) of the dust mass and number
    99  LOGICAL,SAVE :: callddevil ! flag to activate dust devil (dust lifing/injection) parametrization
     10
     11!$OMP THREADPRIVATE(active, doubleq,submicron,lifting,freedust,     &
     12!$OMP                callddevil)
    1013 
    1114  INTEGER,SAVE :: dustbin ! number of bins of dust tracers
     15
     16!$OMP THREADPRIVATE(dustbin)
    1217
    1318  REAL,PARAMETER :: odpref = 610. ! Reference pressure (Pa) of
     
    2227  REAL,PARAMETER :: t_scenario_sol=14/24. ! time of day (sol) at which
    2328                    ! tau_pref_scenario is deemed exact
     29
     30!$OMP THREADPRIVATE(tauscaling, dustscaling_mode,dust_rad_adjust)
    2431
    2532contains
  • trunk/LMDZ.MARS/libf/phymars/nonoro_gwd_ran_mod.F90

    r2400 r2578  
    77REAL,ALLOCATABLE,SAVE :: east_gwstress(:,:) ! Profile of eastward stress
    88REAL,ALLOCATABLE,SAVE :: west_gwstress(:,:) ! Profile of westward stress
     9
     10!$OMP THREADPRIVATE(du_nonoro_gwd,dv_nonoro_gwd,east_gwstress,west_gwstress)
    911
    1012CONTAINS
  • trunk/LMDZ.MARS/libf/phymars/phyetat0_mod.F90

    r2562 r2578  
    33implicit none
    44  real,save :: tab_cntrl_mod(100)
     5
     6!$OMP THREADPRIVATE(tab_cntrl_mod)
    57
    68contains
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r2573 r2578  
    246246      INTEGER,SAVE :: day_ini ! Initial date of the run (sol since Ls=0)
    247247      INTEGER,SAVE :: icount     ! counter of calls to physiq during the run.
     248      REAL,SAVE :: time_phys
     249
     250!$OMP THREADPRIVATE(day_ini,icount,time_phys)
    248251
    249252#ifdef DUSTSTORM
     
    447450      REAL satuco2(ngrid,nlayer)  ! co2 satu ratio for output
    448451      REAL zqsatco2(ngrid,nlayer) ! saturation co2
    449       REAL,SAVE :: time_phys
     452
    450453
    451454! Added for new NLTE scheme
  • trunk/LMDZ.MARS/libf/phymars/slope_mod.F90

    r1770 r2578  
    55  real,save,allocatable :: theta_sl(:) ! slope angle versus horizontal (deg)
    66  real,save,allocatable :: psi_sl(:)   ! slope orientation (deg)
     7
     8!$OMP THREADPRIVATE(theta_sl,psi_sl)
    79
    810contains
  • trunk/LMDZ.MARS/libf/phymars/surfdat_h.F90

    r2561 r2578  
    1010  logical,save,allocatable :: watercaptag(:) ! flag for water ice surface
    1111  real, save, allocatable :: dryness(:)
     12
     13!$OMP THREADPRIVATE(albedodat, phisfi,albedice,emisice,emissiv,TESicealbedo,     &
     14!$OMP                watercaptag,dryness)
    1215     
    1316  logical,save :: temptag !temp tag for water caps
     17
     18!$OMP THREADPRIVATE(temptag)
    1419     
    1520  real,save :: albedo_h2o_cap ! water cap albedo
     
    2631  real,save :: z0_default ! default (constant over planet) surface roughness (m)
    2732
     33!$OMP THREADPRIVATE(albedo_h2o_cap,albedo_h2o_frost,inert_h2o_ice,               &
     34!$OMP                frost_albedo_threshold,frost_metam_threshold,TESice_Ncoef,  &
     35!$OMP                TESice_Scoef,iceradius,dtemisice,                           &
     36!$OMP                zmea,zstd,zsig,zgam,zthe,hmons,summit,base,z0,z0_default )
     37
    2838  !! variables
    2939  REAL,SAVE,ALLOCATABLE :: tsurf(:)   ! Surface temperature (K)
     
    3444  REAL,ALLOCATABLE,SAVE :: qsurf(:,:) ! tracer on surface (e.g. kg.m-2)
    3545  REAL,SAVE,ALLOCATABLE :: watercap(:) ! Surface water ice (kg.m-2)
     46
     47!$OMP THREADPRIVATE(tsurf,co2ice,emis,capcal,fluxgrd,qsurf,watercap)
    3648
    3749contains
  • trunk/LMDZ.MARS/libf/phymars/tracer_mod.F90

    r2562 r2578  
    55      ! number of tracers:
    66      integer,save :: nqmx ! initialized in conf_phys
     7
     8!$OMP THREADPRIVATE(nqmx) 
    79   
    810      character*30,allocatable,save ::  noms(:)  ! name of the tracer
     
    1214      real,allocatable,save :: alpha_lift(:) ! saltation vertical flux/horiz flux ratio (m-1)
    1315      real,allocatable,save :: alpha_devil(:) ! lifting coeeficient by dust devil
     16
     17!$OMP THREADPRIVATE(noms,mmol,radius,rho_q,alpha_lift,                           &
     18!$OMP                alpha_devil) 
    1419
    1520      real,save :: varian      ! Characteristic variance of log-normal distribution
     
    2328      real,save :: nuiceco2_sed   ! Sedimentation effective variance of the co2 ice dist.
    2429      real,save :: nuiceco2_ref   ! Effective variance of the co2 ice dist.
     30
     31!$OMP THREADPRIVATE(varian,r3n_q,rho_dust,rho_ice,nuice_ref,                     &
     32!$OMP                nuice_sed,ref_r0,rho_ice_co2,nuiceco2_sed,nuiceco2_ref) 
    2533     
    2634      real,save :: ccn_factor  ! ratio of nuclei for water ice particles
     35
     36!$OMP THREADPRIVATE(ccn_factor) 
    2737
    2838      INTEGER,ALLOCATABLE,SAVE :: nqdust(:) ! to store the indexes of dust tracers (cf aeropacity)
    2939      real,allocatable,save :: dryness(:)!"Dryness coefficient" for grnd water ice sublimation
     40
     41!$OMP THREADPRIVATE(nqdust,dryness) 
    3042
    3143
     
    4759      integer,save :: igcm_topdust_number !  topdust number mixing ratio
    4860
     61!$OMP THREADPRIVATE(igcm_dustbin,igcm_dust_mass,igcm_dust_number,igcm_ccn_mass,  &
     62!$OMP                igcm_ccn_number,igcm_dust_submicron,igcm_stormdust_mass,    &
     63!$OMP                igcm_stormdust_number,igcm_topdust_mass,igcm_topdust_number) 
     64
    4965      integer,save :: igcm_ccnco2_mass   ! CCN (dust and/or water ice) for CO2 mass mixing ratio
    5066      integer,save :: igcm_ccnco2_number ! CCN (dust and/or water ice) for CO2 number mixing ratio
     
    5268      integer,save :: igcm_ccnco2_h2o_mass_ccn   ! CCN (dust and/or water ice) for CO2 mass mixing ratio
    5369      integer,save :: igcm_ccnco2_h2o_number ! CCN (dust and/or water ice) for CO2 number mixing ratio
     70
     71!$OMP THREADPRIVATE(igcm_ccnco2_mass,igcm_ccnco2_number,                         &
     72!$OMP                igcm_ccnco2_h2o_mass_ice,igcm_ccnco2_h2o_mass_ccn,          &
     73!$OMP                igcm_ccnco2_h2o_number) 
    5474
    5575      ! water
     
    5979      integer,save :: igcm_hdo_ice ! hdo ice
    6080      integer,save :: igcm_co2_ice ! co2 ice
     81
     82!$OMP THREADPRIVATE(igcm_h2o_vap, igcm_h2o_ice, igcm_hdo_vap, igcm_hdo_ice,      &
     83!$OMP                igcm_co2_ice) 
    6184
    6285      ! chemistry:
     
    80103      integer,save :: igcm_he
    81104      integer,save :: igcm_ch4
     105
     106!$OMP THREADPRIVATE(igcm_co2,igcm_co,igcm_o,igcm_o1d,igcm_o2,igcm_o3,igcm_h,   &
     107!$OMP                igcm_h2,igcm_oh,igcm_ho2,igcm_h2o2,igcm_n2,igcm_ar,igcm_n,&
     108!$OMP               igcm_no,igcm_no2,igcm_n2d,igcm_he,igcm_ch4)
     109
    82110      !Deuterated species derived from HDO
    83111      integer,save :: igcm_od
     
    86114      integer,save :: igcm_do2
    87115      integer,save :: igcm_hdo2
     116
     117!$OMP THREADPRIVATE(igcm_od,igcm_d,igcm_hd, igcm_do2,igcm_hdo2)
     118
    88119      ! Ions
    89120      integer,save :: igcm_co2plus
     
    102133      integer,save :: igcm_ohplus
    103134      integer,save :: igcm_elec
     135
     136!$OMP THREADPRIVATE(igcm_co2plus,igcm_oplus,igcm_o2plus,igcm_coplus,igcm_cplus,   &
     137!$OMP                igcm_nplus,igcm_noplus,igcm_n2plus,igcm_hplus,igcm_hco2plus,&
     138!$OMP                igcm_hcoplus,igcm_h2oplus,igcm_h3oplus,igcm_ohplus,igcm_elec)
     139
    104140      ! other tracers
    105141      integer,save :: igcm_ar_n2 ! for simulations using co2 +neutral gas
     
    107143      integer, save                 :: nqperes ! numbers of tracers defined as "peres"
    108144      integer, allocatable, save    :: nqfils(:) ! numbers of sons ("fils") of the considered tracer
     145
     146!$OMP THREADPRIVATE(igcm_ar_n2,nqperes,nqfils) 
     147
    109148      real, parameter               :: qperemin=1.e-16 ! threschold for the "pere" mixing ratio qpere to calculate Ratio=qfils/qpere
    110149      real, parameter               :: masseqmin=1.e-16 ! threschold for the "pere" transporting masse martian case as there are no gran-sons
  • trunk/LMDZ.MARS/libf/phymars/turb_mod.F90

    r1770 r2578  
    1313      ! this is a flag to say 'turbulence is resolved'
    1414      ! mostly for LES use. default is FALSE (for GCM and mesoscale)
     15
     16!$OMP THREADPRIVATE(q2, l0,ustar,wstar,tstar,hfmax_th,zmax_th,     &
     17!$OMP                sensibFlux)
    1518
    1619contains
  • trunk/LMDZ.MARS/libf/phymars/watercloud_mod.F

    r2516 r2578  
    55       REAL,SAVE,ALLOCATABLE :: zdqcloud(:,:,:) ! tendencies on pq due to condensation of H2O(kg/kg.s-1)
    66       REAL,SAVE,ALLOCATABLE :: zdqscloud(:,:) ! tendencies on qsurf (calculated only by calchim but declared here)
     7
     8!$OMP THREADPRIVATE(zdqcloud,zdqscloud)
    79
    810       CONTAINS
  • trunk/LMDZ.MARS/libf/phymars/yomlw_h.F90

    r1772 r2578  
    1414  real,save :: gcp ! = g/cpp (set in callradite)
    1515
     16!$OMP THREADPRIVATE(at,bt,tref,xp,tstand,ga,gb,cst_voigt,gcp)
     17
    1618! Number of layers on which LTE calculations (in lw and sw) are performed
    1719! (Computed in nlthermeq) :
     
    2123  real,save,allocatable :: xi_ground(:,:)
    2224  real,save,allocatable :: xi_emis(:,:,:)
     25
     26!$OMP THREADPRIVATE(nlaylte,xi,xi_ground,xi_emis)
    2327
    2428contains
Note: See TracChangeset for help on using the changeset viewer.