Changeset 1883


Ignore:
Timestamp:
Jan 2, 2018, 3:11:14 PM (7 years ago)
Author:
emillour
Message:

Generic GCM:

  • fix rcm1d.F to cope with modifications introduced in revision 1835-1836
  • also add some missing threadprivate OpenMP directives in phys_state_var_mod and turb_mod

EM

Location:
trunk/LMDZ.GENERIC
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/README

    r1882 r1883  
    13661366  libf/dynphy_lonlat/phystd directory
    13671367- dtridgl.F already exists in libf/phystd
     1368- fix rcm1d.F to cope with modifications introduced in revision 1835-1836
     1369- also add some missing threadprivate OpenMP directives in phys_state_var_mod
     1370  and turb_mod
     1371
  • trunk/LMDZ.GENERIC/libf/phystd/comsaison_h.F90

    r1327 r1883  
    44       implicit none
    55
    6        integer isaison
    7        logical callsais
    8        real dist_star,declin,right_ascen
     6!       integer,save :: isaison
     7!       logical,save :: callsais
     8!!$OMP THREADPRIVATE(isaison,callsais)
     9
     10       real,save :: dist_star,declin,right_ascen
     11!$OMP THREADPRIVATE(dist_star,declin,right_ascen)
    912
    1013       real, allocatable, dimension(:) :: mu0,fract
    11 !$OMP THREADPRIVATE(isaison,callsais,dist_star,declin,mu0,fract)
     14!$OMP THREADPRIVATE(mu0,fract)
    1215
    1316       end module comsaison_h
  • trunk/LMDZ.GENERIC/libf/phystd/dyn1d/rcm1d.F

    r1826 r1883  
    3535      use mod_interface_dyn_phys, only: init_interface_dyn_phys
    3636      use inifis_mod, only: inifis
     37      use phys_state_var_mod, only: phys_state_var_init
    3738      use physiq_mod, only: physiq
    3839      implicit none
     
    146147c INITIALISATION
    147148c=======================================================================
    148 ! initialize "serial/parallel" related stuff
    149 !      CALL init_phys_lmdz(iim,jjm+1,llm,1,(/(jjm-1)*iim+2/))
    150 !      CALL init_phys_lmdz(1,1,llm,1,(/1/))
    151 !      call initcomgeomphy
    152 
    153       !! those are defined in surfdat_h.F90
    154       IF (.not. ALLOCATED(albedodat)) ALLOCATE(albedodat(1))
    155       IF (.not. ALLOCATED(phisfi)) ALLOCATE(phisfi(1))
    156       IF (.not. ALLOCATED(zmea)) ALLOCATE(zmea(1))
    157       IF (.not. ALLOCATED(zstd)) ALLOCATE(zstd(1))
    158       IF (.not. ALLOCATED(zsig)) ALLOCATE(zsig(1))
    159       IF (.not. ALLOCATED(zgam)) ALLOCATE(zgam(1))
    160       IF (.not. ALLOCATED(zthe)) ALLOCATE(zthe(1))
    161       IF (.not. ALLOCATED(dryness)) ALLOCATE(dryness(1))
    162       IF (.not. ALLOCATED(watercaptag)) ALLOCATE(watercaptag(1))
    163       !! those are defined in comdiurn_h.F90
    164       IF (.not.ALLOCATED(sinlat)) ALLOCATE(sinlat(1))
    165       IF (.not.ALLOCATED(coslat)) ALLOCATE(coslat(1))
    166       IF (.not.ALLOCATED(sinlon)) ALLOCATE(sinlon(1))
    167       IF (.not.ALLOCATED(coslon)) ALLOCATE(coslon(1))
    168 
     149
     150      ! read nq from traceur.def
     151      open(90,file='traceur.def',status='old',form='formatted',
     152     &       iostat=ierr)
     153      if (ierr.eq.0) then
     154        read(90,*,iostat=ierr) nq
     155      else
     156        nq=0
     157      endif
     158      close(90)
     159     
     160      ! Initialize dimphy module
     161      call init_dimphy(1,llm)
     162      ! now initialize arrays using phys_state_var_init
     163      call phys_state_var_init(nq)
     164     
    169165      saveprofile=.false.
    170166      saveprofile=.true.
     
    512508!      call init_vertical_layers(nlayer,preff,scaleheight,
    513509!     &                      ap,bp,aps,bps,presnivs,pseudoalt)
    514       call init_dimphy(1,nlayer) ! Initialize dimphy module
     510!      call init_dimphy(1,nlayer) ! Initialize dimphy module
    515511      call ini_planete_mod(nlayer,preff,ap,bp)
    516512
  • trunk/LMDZ.GENERIC/libf/phystd/phys_state_var_mod.F90

    r1842 r1883  
    1717      use surfdat_h, only: phisfi, albedodat,  &
    1818                        zmea, zstd, zsig, zgam, zthe
    19       use turb_mod
    20 !#include "bands.h"
    21 !#include "scatterers.h"
    22 !      INTEGER, SAVE :: radpas
    23 !!$OMP THREADPRIVATE(radpas)
    24 !      REAL, SAVE :: dtime
    25 !!$OMP THREADPRIVATE(dtime)
     19      use turb_mod, only: q2,sensibFlux,wstar,ustar,tstar,hfmax_th,zmax_th
     20
    2621      real,allocatable,dimension(:,:),save :: ztprevious ! Previous loop Atmospheric Temperature (K)
    2722! Useful for Dynamical Heating calculation.
    2823      real,allocatable,dimension(:,:),save :: zuprevious
     24!$OMP THREADPRIVATE(ztprevious,zuprevious)
     25
    2926      real, dimension(:),allocatable,save ::  tsurf                ! Surface temperature (K).
    3027      real, dimension(:,:),allocatable,save ::  tsoil              ! Sub-surface temperatures (K).
     
    3330      real, dimension(:),allocatable,save :: albedo_snow_SPECTV    ! Snow Spectral albedo.
    3431      real, dimension(:),allocatable,save :: albedo_co2_ice_SPECTV ! CO2 ice Spectral albedo.
    35 
    3632!$OMP THREADPRIVATE(tsurf,tsoil,albedo,albedo_equivalent,albedo_snow_SPECTV,albedo_co2_ice_SPECTV)
    3733
    3834      real,dimension(:),allocatable,save :: albedo_bareground ! Bare Ground Albedo. By MT 2015.
    3935      real,dimension(:),allocatable,save :: rnat              ! Defines the type of the grid (ocean,continent,...). By BC.
    40 
    4136!$OMP THREADPRIVATE(albedo_bareground,rnat)
    4237
     
    4843      real,dimension(:),allocatable,save :: fluxgrd     ! Surface conduction flux (W.m-2).
    4944      real,dimension(:,:),allocatable,save :: qsurf     ! Tracer on surface (e.g. kg.m-2).
    50       !real,dimension(:,:),allocatable,save :: q2        ! Turbulent Kinetic Energy.
    51 
     45!$OMP THREADPRIVATE(emis,dtrad,fluxrad_sky,fluxrad,capcal,fluxgrd,qsurf)
    5246
    5347      ! FOR DIAGNOSTIC :
     
    5650      real,dimension(:),allocatable,save :: fluxsurf_sw     ! Incident Short Wave (stellar) surface flux (W.m-2).
    5751      real,dimension(:),allocatable,save :: fluxsurfabs_sw  ! Absorbed Short Wave (stellar) flux by the surface (W.m-2).
     52!$OMP THREADPRIVATE(fluxsurf_lw,fluxsurf_sw,fluxsurfabs_sw)
     53
    5854      real,dimension(:),allocatable,save :: fluxtop_lw      ! Outgoing LW (IR) flux to space (W.m-2).
    5955      real,dimension(:),allocatable,save :: fluxabs_sw      ! Absorbed SW (stellar) flux (W.m-2).
    6056      real,dimension(:),allocatable,save :: fluxtop_dn      ! Incoming SW (stellar) radiation at the top of the atmosphere (W.m-2).
    6157      real,dimension(:),allocatable,save :: fluxdyn         ! Horizontal heat transport by dynamics (W.m-2).
     58!$OMP THREADPRIVATE(fluxtop_lw,fluxabs_sw,fluxtop_dn,fluxdyn)
     59
    6260      real,dimension(:,:),allocatable,save :: OLR_nu        ! Outgoing LW radiation in each band (Normalized to the band width (W/m2/cm-1)).
    6361      real,dimension(:,:),allocatable,save :: OSR_nu        ! Outgoing SW radiation in each band (Normalized to the band width (W/m2/cm-1)).
     
    6563      real,dimension(:,:),allocatable,save :: zdtsw         ! SW heating tendencies (K/s).
    6664      !real,dimension(:),allocatable,save :: sensibFlux      ! Turbulent flux given by the atmosphere to the surface (W.m-2).
     65!$OMP THREADPRIVATE(OLR_nu,OSR_nu,zdtlw,zdtsw)
    6766
    6867      real,allocatable,dimension(:),save :: tau_col ! Total Aerosol Optical Depth.
     
    7574
    7675      real,allocatable,dimension(:,:),save :: qsurf_hist
    77 !$OMP THREADPRIVATE(qsurf_hist)
    7876      real,allocatable,dimension(:,:,:),save :: nueffrad ! Aerosol effective radius variance. By RW
     77!$OMP THREADPRIVATE(qsurf_hist,nueffrad)
    7978
    8079      real,allocatable,dimension(:),save :: ice_initial
    8180      real,allocatable,dimension(:),save :: ice_min
    82 
     81!$OMP THREADPRIVATE(ice_initial,ice_min)
    8382
    8483      real, dimension(:),allocatable,save ::  pctsrf_sic
     
    8988      integer, dimension(:),allocatable,save ::knindex
    9089      real,allocatable,dimension(:,:,:),save :: reffrad
    91 
    92 !$OMP THREADPRIVATE(dlw,fder)
     90!$OMP THREADPRIVATE(pctsrf_sic,tslab,tsea_ice,sea_ice,zmasq,knindex,reffrad)
    9391     
    9492CONTAINS
     
    9997IMPLICIT NONE
    10098
    101         integer :: nqtot
     99        integer,intent(in) :: nqtot
    102100
    103101!  Parametres de l'Orographie a l'Echelle Sous-Maille (OESM):
  • trunk/LMDZ.GENERIC/libf/phystd/physiq_mod.F90

    r1877 r1883  
    404404! --------------------------------
    405405      if (firstcall) then
    406         ! Allocate saved arrays.
    407         call phys_state_var_init(nq)
     406        ! Allocate saved arrays (except for 1D model, where this has already
     407        ! been done)
     408        if (ngrid>1) call phys_state_var_init(nq)
    408409
    409410!        Variables set to 0
  • trunk/LMDZ.GENERIC/libf/phystd/turb_mod.F90

    r1834 r1883  
    44  REAL,SAVE,ALLOCATABLE :: q2(:,:)    ! Turbulent Kinetic Energy
    55  REAL,allocatable,SAVE :: l0(:)
     6!$OMP THREADPRIVATE(q2,l0)
    67  REAL,SAVE,ALLOCATABLE :: ustar(:)
    78  REAL,SAVE,ALLOCATABLE :: wstar(:)
    89  REAL,SAVE,ALLOCATABLE :: tstar(:)
     10!$OMP THREADPRIVATE(ustar,wstar,tstar)
    911  REAL,SAVE,ALLOCATABLE :: hfmax_th(:)
    1012  REAL,SAVE,ALLOCATABLE :: zmax_th(:)
     13!$OMP THREADPRIVATE(hfmax_th,zmax_th)
    1114  REAL,SAVE,ALLOCATABLE :: sensibFlux(:)
    12   LOGICAL :: turb_resolved = .false.
     15  LOGICAL,SAVE :: turb_resolved = .false.
     16!$OMP THREADPRIVATE(sensibFlux,turb_resolved)
    1317      ! this is a flag to say 'turbulence is resolved'
    1418      ! mostly for LES use. default is FALSE (for GCM and mesoscale)
Note: See TracChangeset for help on using the changeset viewer.