Changeset 1520 for trunk/LMDZ.GENERIC


Ignore:
Timestamp:
Mar 24, 2016, 12:51:12 PM (9 years ago)
Author:
emillour
Message:

Generic GCM:

  • Some fixes/adjustments to run using OpenMP (in the physics, best practice is to always have "save" variables, this of course includes all module variables, as "threadprivate").

EM

Location:
trunk/LMDZ.GENERIC
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/README

    r1516 r1520  
    11211121- Added tests to ensure that soil model settings are adequate to resolve
    11221122  sub-surface diurnal and annual thermal waves.
     1123
     1124== 24/03/2016 == EM
     1125- Some fixes/adjustments to run using OpenMP (in the physics, best practice is to always have "save" variables,
     1126  this of course includes all module variables, as "threadprivate").
     1127
  • trunk/LMDZ.GENERIC/libf/phystd/callkeys_mod.F90

    r1498 r1520  
    22IMPLICIT NONE 
    33
    4       logical callrad,corrk,calldifv,UseTurbDiff                        &
    5      &   , calladj,co2cond,callsoil                                     &
    6      &   , season,diurnal,tlocked,rings_shadow,lwrite                   &
    7      &   , callstats,calleofdump                                        &
    8      &   , callgasvis,continuum,H2Ocont_simple,graybody                 &
    9      &   , strictboundcorrk                                     
     4      logical,save :: callrad,corrk,calldifv,UseTurbDiff
     5!$OMP THREADPRIVATE(callrad,corrk,calldifv,UseTurbDiff)
     6      logical,save :: calladj,co2cond,callsoil
     7!$OMP THREADPRIVATE(calladj,co2cond,callsoil)
     8      logical,save :: season,diurnal,tlocked,rings_shadow,lwrite
     9!$OMP THREADPRIVATE(season,diurnal,tlocked,rings_shadow,lwrite)
     10      logical,save :: callstats,calleofdump
     11!$OMP THREADPRIVATE(callstats,calleofdump)
     12      logical,save :: callgasvis,continuum,H2Ocont_simple,graybody
     13!$OMP THREADPRIVATE(callgasvis,continuum,H2Ocont_simple,graybody)
     14      logical,save :: strictboundcorrk                                     
     15!$OMP THREADPRIVATE(strictboundcorrk)
    1016
    11       logical enertest
    12       logical nonideal
    13       logical meanOLR
    14       logical specOLR
    15       logical kastprof
    16       logical newtonian
    17       logical check_cpp_match
    18       logical force_cpp
    19       logical testradtimes
    20       logical rayleigh
    21       logical stelbbody
    22       logical ozone
    23       logical nearco2cond
    24       logical tracer
    25       logical mass_redistrib
    26       logical varactive
    27       logical varfixed
    28       logical radfixed
    29       logical sedimentation
    30       logical water,watercond,waterrain
    31       logical aeroco2,aeroh2o,aeroh2so4,aeroback2lay
    32       logical aerofixco2,aerofixh2o
    33       logical hydrology
    34       logical sourceevol
    35       logical CLFvarying
    36       logical nosurf
    37       logical oblate
    38       logical ok_slab_ocean
    39       logical ok_slab_sic
    40       logical ok_slab_heat_transp
    41       logical albedo_spectral_mode
     17      logical,save :: enertest
     18      logical,save :: nonideal
     19      logical,save :: meanOLR
     20      logical,save :: specOLR
     21      logical,save :: kastprof
     22!$OMP THREADPRIVATE(enertest,nonideal,meanOLR,kastprof)
     23      logical,save :: newtonian
     24      logical,save :: check_cpp_match
     25      logical,save :: force_cpp
     26      logical,save :: testradtimes
     27      logical,save :: rayleigh
     28!$OMP THREADPRIVATE(newtonian,check_cpp_match,force_cpp,testradtimes,rayleigh)
     29      logical,save :: stelbbody
     30      logical,save :: ozone
     31      logical,save :: nearco2cond
     32      logical,save :: tracer
     33      logical,save :: mass_redistrib
     34!$OMP THREADPRIVATE(stelbbody,ozone,nearco2cond,tracer,mass_redistrib)
     35      logical,save :: varactive
     36      logical,save :: varfixed
     37      logical,save :: radfixed
     38      logical,save :: sedimentation
     39!$OMP THREADPRIVATE(varactive,varfixed,radfixed,sedimentation)
     40      logical,save :: water,watercond,waterrain
     41!$OMP THREADPRIVATE(water,watercond,waterrain)
     42      logical,save :: aeroco2,aeroh2o,aeroh2so4,aeroback2lay
     43!$OMP THREADPRIVATE(aeroco2,aeroh2o,aeroh2so4,aeroback2lay)
     44      logical,save :: aerofixco2,aerofixh2o
     45!$OMP THREADPRIVATE(aerofixco2,aerofixh2o)
     46      logical,save :: hydrology
     47      logical,save :: sourceevol
     48      logical,save :: CLFvarying
     49      logical,save :: nosurf
     50      logical,save :: oblate
     51!$OMP THREADPRIVATE(hydrology,sourceevol,CLFvarying,nosurf,oblate)
     52      logical,save :: ok_slab_ocean
     53      logical,save :: ok_slab_sic
     54      logical,save :: ok_slab_heat_transp
     55      logical,save :: albedo_spectral_mode
     56!$OMP THREADPRIVATE(ok_slab_ocean,ok_slab_sic,ok_slab_heat_transp,albedo_spectral_mode)
    4257
    43       integer iddist
    44       integer iaervar
    45       integer iradia
    46       integer startype
     58      integer,save :: iddist
     59      integer,save :: iaervar
     60      integer,save :: iradia
     61      integer,save :: startype
     62!$OMP THREADPRIVATE(iddist,iaervar,iradia,startype)
    4763
    48       real topdustref
    49       real Nmix_co2
    50       real dusttau
    51       real Fat1AU
    52       real stelTbb
    53       real Tstrat
    54       real tplanet
    55       real obs_tau_col_tropo
    56       real obs_tau_col_strato
    57       real pres_bottom_tropo
    58       real pres_top_tropo
    59       real pres_bottom_strato
    60       real pres_top_strato
    61       real size_tropo
    62       real size_strato
    63       real satval
    64       real CLFfixval
    65       real n2mixratio
    66       real co2supsat
    67       real pceil
    68       real albedosnow
    69       real albedoco2ice
    70       real maxicethick
    71       real Tsaldiff
    72       real tau_relax
    73       real cloudlvl
    74       real icetstep
    75       real intheat
    76       real flatten
    77       real Rmean
    78       real J2
    79       real MassPlanet
    80      
    81       logical :: iscallphys=.false.!existence of callphys.def
     64      real,save :: topdustref
     65      real,save :: Nmix_co2
     66      real,save :: dusttau
     67      real,save :: Fat1AU
     68      real,save :: stelTbb
     69!$OMP THREADPRIVATE(topdustref,Nmix_co2,dusttau,Fat1AU,stelTbb)
     70      real,save :: Tstrat
     71      real,save :: tplanet
     72      real,save :: obs_tau_col_tropo
     73      real,save :: obs_tau_col_strato
     74!$OMP THREADPRIVATE(Tstrat,tplanet,obs_tau_col_tropo,obs_tau_col_strato)
     75      real,save :: pres_bottom_tropo
     76      real,save :: pres_top_tropo
     77      real,save :: pres_bottom_strato
     78      real,save :: pres_top_strato
     79!$OMP THREADPRIVATE(pres_bottom_tropo,pres_top_tropo,pres_bottom_strato,pres_top_strato)
     80      real,save :: size_tropo
     81      real,save :: size_strato
     82      real,save :: satval
     83      real,save :: CLFfixval
     84      real,save :: n2mixratio
     85!$OMP THREADPRIVATE(size_tropo,size_strato,satval,CLFfixval,n2mixratio)
     86      real,save :: co2supsat
     87      real,save :: pceil
     88      real,save :: albedosnow
     89      real,save :: albedoco2ice
     90      real,save :: maxicethick
     91!$OMP THREADPRIVATE(co2supsat,pceil,albedosnow,albedoco2ice,maxicethick)
     92      real,save :: Tsaldiff
     93      real,save :: tau_relax
     94      real,save :: cloudlvl
     95      real,save :: icetstep
     96      real,save :: intheat
     97!$OMP THREADPRIVATE(Tsaldiff,tau_relax,cloudlvl,icetstep,intheat)
     98      real,save :: flatten
     99      real,save :: Rmean
     100      real,save :: J2
     101      real,save :: MassPlanet
     102!$OMP THREADPRIVATE(flatten,Rmean,J2,MassPlanet)
     103
     104      logical,save :: iscallphys=.false.!existence of callphys.def
     105!$OMP THREADPRIVATE(iscallphys)
    82106
    83107END MODULE callkeys_mod
  • trunk/LMDZ.GENERIC/libf/phystd/comcstfi_mod.F90

    r1384 r1520  
    22IMPLICIT NONE
    33     
    4       REAL :: pi ! something like 3.14159
    5       REAL :: rad ! radius of the planet (m)
    6       REAL :: g ! gravity (m/s2)
    7       REAL :: r ! reduced gas constant (r=8.314511/(mugaz/1000.0))
    8       REAL :: cpp ! Cp of the atmosphere
    9       REAL :: rcp ! r/cpp
    10       REAL :: dtphys ! physics time step (s)
    11       REAL :: daysec ! length of day (s)
    12       REAL :: mugaz ! molar mass of the atmosphere (g/mol)
    13       REAL :: omeg ! planet rotation rate (rad/s)
    14       REAL :: avocado ! something like 6.022e23
     4      REAL,SAVE :: pi ! something like 3.14159
     5      REAL,SAVE :: rad ! radius of the planet (m)
     6      REAL,SAVE :: g ! gravity (m/s2)
     7      REAL,SAVE :: r ! reduced gas constant (r=8.314511/(mugaz/1000.0))
     8      REAL,SAVE :: cpp ! Cp of the atmosphere
     9      REAL,SAVE :: rcp ! r/cpp
     10      REAL,SAVE :: dtphys ! physics time step (s)
     11      REAL,SAVE :: daysec ! length of day (s)
     12      REAL,SAVE :: mugaz ! molar mass of the atmosphere (g/mol)
     13      REAL,SAVE :: omeg ! planet rotation rate (rad/s)
     14      REAL,SAVE :: avocado ! something like 6.022e23
     15!$OMP THREADPRIVATE(pi,rad,g,r,cpp,rcp,dtphys,daysec,mugaz,omeg,avocado)
    1516
    1617END MODULE comcstfi_mod
  • trunk/LMDZ.GENERIC/libf/phystd/comdiurn_h.F90

    r1315 r1520  
    44       implicit none
    55
    6        real, allocatable, dimension(:) :: sinlon, coslon, sinlat, coslat
    7        logical :: ldiurn
    8 !$OMP THREADPRIVATE(sinlon,coslon,sinlat,coslat,ldiurn) !ldiurn is unused
     6       real,allocatable,dimension(:),save :: sinlon, coslon, sinlat, coslat
     7!$OMP THREADPRIVATE(sinlon,coslon,sinlat,coslat)
    98
    109       end module comdiurn_h
  • trunk/LMDZ.GENERIC/libf/phystd/comgeomfi_h.F90

    r1315 r1520  
    44       implicit none
    55
    6        REAL,ALLOCATABLE,DIMENSION(:) :: long,lati,area
    7        REAL :: totarea, totarea_planet
    8 !$OMP THREADPRIVATE(long,lati,area,totarea)
     6       REAL,ALLOCATABLE,DIMENSION(:),SAVE :: long,lati,area
     7       REAL,SAVE :: totarea, totarea_planet
     8!$OMP THREADPRIVATE(long,lati,area,totarea,totarea_planet)
    99
    1010       end module comgeomfi_h
  • trunk/LMDZ.GENERIC/libf/phystd/datafile_mod.F90

    r1470 r1520  
    1010!      character(len=300) :: datadir='/san/home/rdword/gcm/datagcm'
    1111      ! Default for LMD machines:
    12       character(len=300) :: datadir='/u/lmdz/WWW/planets/LMDZ.GENERIC/datagcm'
     12      character(len=300),save :: datadir='/u/lmdz/WWW/planets/LMDZ.GENERIC/datagcm'
     13!$OMP THREADPRIVATE(datadir)
    1314     
    1415      ! Subdirectories of 'datadir':
  • trunk/LMDZ.GENERIC/libf/phystd/inifis.F

    r1498 r1520  
    5252!   -------------
    5353      use datafile_mod, only: datadir
    54 ! to use  'getin'
    55 !      USE ioipsl_getincom
    56       USE ioipsl_getincom_p
     54      USE ioipsl_getincom_p, only: getin_p
    5755      IMPLICIT NONE
    5856
     
    7876      real psurf,pN2 ! added by RW for Gliese 581d N2+CO2
    7977
    80 !$OMP MASTER
    8178      rad=prad
    8279      daysec=pdaysec
     
    8986      avocado = 6.02214179e23   ! added by RW
    9087
    91 !$OMP END MASTER
    92 !$OMP BARRIER
    9388
    9489      ! read in 'ecritphy' (frequency of calls to physics, in dynamical steps)
     
    10095! --------------------------------------------------------------
    10196     
    102 !$OMP MASTER     
    10397      ! check that 'callphys.def' file is around
    10498      OPEN(99,file='callphys.def',status='old',form='formatted'
     
    106100      CLOSE(99)
    107101      IF(ierr.EQ.0) iscallphys=.true. !iscallphys initialised as false in callkeys_mod module
    108 !$OMP END MASTER
    109 !$OMP BARRIER
    110102     
    111103!!!      IF(ierr.EQ.0) THEN
     
    721713      ENDDO
    722714
    723 !$OMP MASTER
    724715      pi=2.*asin(1.) ! NB: pi is a common in comcstfi_mod
    725 !$OMP END MASTER
    726 !$OMP BARRIER
    727716
    728717      ! allocate "comsoil_h" arrays
  • trunk/LMDZ.GENERIC/libf/phystd/planete_mod.F90

    r1315 r1520  
    22  IMPLICIT NONE
    33 
    4   REAL :: apoastr ! maximum star-planet distance (AU)
    5   REAL :: periastr ! minimum star-planet distance (AU)
    6   REAL :: year_day ! length of year (sols)
    7   REAL :: peri_day ! date of periastron (sols since N. spring)
    8   REAL :: obliquit ! Obliquity of the planet (deg)
    9   REAL :: nres ! tidal resonance ratio
    10   REAL :: z0 ! surface roughness (m)
    11   REAL :: lmixmin ! mixing length
    12   REAL :: emin_turb ! minimal energy
    13   REAL :: coefvis
    14   REAL :: coefir
    15   REAL :: timeperi
    16   REAL :: e_elips
    17   REAL :: p_elips
     4  REAL,SAVE :: apoastr ! maximum star-planet distance (AU)
     5  REAL,SAVE :: periastr ! minimum star-planet distance (AU)
     6  REAL,SAVE :: year_day ! length of year (sols)
     7  REAL,SAVE :: peri_day ! date of periastron (sols since N. spring)
     8  REAL,SAVE :: obliquit ! Obliquity of the planet (deg)
     9!$OMP THREADPRIVATE(apoastr,periastr,year_day,peri_day,obliquit)
     10  REAL,SAVE :: nres ! tidal resonance ratio
     11  REAL,SAVE :: z0 ! surface roughness (m)
     12  REAL,SAVE :: lmixmin ! mixing length
     13  REAL,SAVE :: emin_turb ! minimal energy
     14!$OMP THREADPRIVATE(nres,z0,lmixmin,emin_turb)
     15  REAL,SAVE :: coefvis
     16  REAL,SAVE :: coefir
     17  REAL,SAVE :: timeperi
     18  REAL,SAVE :: e_elips
     19  REAL,SAVE :: p_elips
     20!$OMP THREADPRIVATE(coefvis,coefir,timeperi,e_elips,p_elips)
    1821 
    19   REAL :: preff ! reference surface pressure (Pa)       !read by master
    20   REAL,ALLOCATABLE :: ap(:) ! hybrid coordinate at layer interface      !read by master
    21   REAL,ALLOCATABLE :: bp(:) ! hybrid coordinate at layer interface      !read by master
    22  
     22  REAL,SAVE :: preff ! reference surface pressure (Pa)  !read by master
     23  REAL,SAVE,ALLOCATABLE :: ap(:) ! hybrid coordinate at layer interface !read by master
     24  REAL,SAVE,ALLOCATABLE :: bp(:) ! hybrid coordinate at layer interface         !read by master
     25!$OMP THREADPRIVATE(preff,ap,bp)
     26
    2327  CONTAINS
    2428 
     
    3135  real,intent(in) :: bp_dyn(nlayer+1) ! hybrid coordinate at interfaces
    3236 
    33 !$OMP MASTER
    3437  allocate(ap(nlayer+1))
    3538  allocate(bp(nlayer+1))
     
    3841  ap(:)=ap_dyn(:)
    3942  bp(:)=bp_dyn(:)
    40 !$OMP END MASTER
    41 !$OMP BARRIER
    4243 
    4344  end subroutine ini_planete_mod
  • trunk/LMDZ.GENERIC/libf/phystd/radinc_h.F90

    r1315 r1520  
    9090      integer, parameter :: nsizemax = 60
    9191
    92       character (len=100) :: corrkdir
    93       save corrkdir
     92      character(len=100),save :: corrkdir
    9493!$OMP THREADPRIVATE(corrkdir)
    9594
    96       character (len=100) :: banddir
    97       save banddir
     95      character(len=100),save :: banddir
    9896!$OMP THREADPRIVATE(banddir)
    9997
Note: See TracChangeset for help on using the changeset viewer.