Ignore:
Timestamp:
Dec 4, 2017, 6:53:22 PM (7 years ago)
Author:
mlefevre
Message:

MESOSCALE GENERIC. Modified physiq_mod. This is a potentially Cannibal Corpse commit. But should be working. (1) replaced allocations by call to phys_state_var_mod (2) replaced writediagfis by comm_wrf call (3) here and there MESOSCALE precomp flags e.g. phyetat0 (4) if condition with turb_resolved useful for LES. All changes shall be harmless to GCM runs.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/libf/phystd/physiq_mod.F90

    r1801 r1836  
    4848      use callkeys_mod
    4949      use conc_mod
     50      use phys_state_var_mod
     51      use turb_mod, only : q2,sensibFlux,turb_resolved
     52#ifndef MESOSCALE
    5053      use vertical_layers_mod, only: presnivs, pseudoalt
    5154      use mod_phys_lmdz_omp_data, ONLY: is_omp_master
     55#else
     56      use comm_wrf, only : comm_HR_SW, comm_HR_LW, &
     57                           comm_CLOUDFRAC,comm_TOTCLOUDFRAC,&
     58                           comm_RAIN,comm_SNOW,comm_ALBEQ,&
     59                           comm_FLUXTOP_DN,comm_FLUXABS_SW,&
     60                           comm_FLUXTOP_LW,comm_FLUXSURF_SW,&
     61                           comm_FLUXSURF_LW,comm_FLXGRD,&
     62                           comm_LSCEZ,comm_H2OICE_REFF
     63#endif
     64
    5265#ifdef CPP_XIOS     
    5366      use xios_output_mod, only: initialize_xios_output, &
     
    5669      use wxios, only: wxios_context_init, xios_context_finalize
    5770#endif
     71
    5872      implicit none
    5973
     
    209223! Local saved variables:
    210224! ----------------------
    211 
    212225      integer,save :: day_ini                                      ! Initial date of the run (sol since Ls=0).
    213226      integer,save :: icount                                       ! Counter of calls to physiq during the run.
     
    223236!$OMP THREADPRIVATE(tsurf,tsoil,albedo,albedo_equivalent,albedo_snow_SPECTV,albedo_co2_ice_SPECTV)
    224237
    225       real,dimension(:),allocatable,save :: albedo_bareground ! Bare Ground Albedo. By MT 2015.
    226       real,dimension(:),allocatable,save :: rnat              ! Defines the type of the grid (ocean,continent,...). By BC.
    227      
    228 !$OMP THREADPRIVATE(albedo_bareground,rnat)
    229 
    230       real,dimension(:),allocatable,save :: emis        ! Thermal IR surface emissivity.
    231       real,dimension(:,:),allocatable,save :: dtrad     ! Net atmospheric radiative heating rate (K.s-1).
    232       real,dimension(:),allocatable,save :: fluxrad_sky ! Radiative flux from sky absorbed by surface (W.m-2).
    233       real,dimension(:),allocatable,save :: fluxrad     ! Net radiative surface flux (W.m-2).
    234       real,dimension(:),allocatable,save :: capcal      ! Surface heat capacity (J m-2 K-1).
    235       real,dimension(:),allocatable,save :: fluxgrd     ! Surface conduction flux (W.m-2).
    236       real,dimension(:,:),allocatable,save :: qsurf     ! Tracer on surface (e.g. kg.m-2).
    237       real,dimension(:,:),allocatable,save :: q2        ! Turbulent Kinetic Energy.
    238      
    239 !$OMP THREADPRIVATE(emis,dtrad,fluxrad_sky,fluxrad,capcal,fluxgrd,qsurf,q2)
    240 
    241 
    242238! Local variables :
    243239! -----------------
     
    252248      integer l,ig,ierr,iq,nw,isoil
    253249     
    254       ! FOR DIAGNOSTIC :
    255      
    256       real,dimension(:),allocatable,save :: fluxsurf_lw     ! Incident Long Wave (IR) surface flux (W.m-2).
    257       real,dimension(:),allocatable,save :: fluxsurf_sw     ! Incident Short Wave (stellar) surface flux (W.m-2).
    258       real,dimension(:),allocatable,save :: fluxsurfabs_sw  ! Absorbed Short Wave (stellar) flux by the surface (W.m-2).
    259       real,dimension(:),allocatable,save :: fluxtop_lw      ! Outgoing LW (IR) flux to space (W.m-2).
    260       real,dimension(:),allocatable,save :: fluxabs_sw      ! Absorbed SW (stellar) flux (W.m-2).
    261       real,dimension(:),allocatable,save :: fluxtop_dn      ! Incoming SW (stellar) radiation at the top of the atmosphere (W.m-2).
    262       real,dimension(:),allocatable,save :: fluxdyn         ! Horizontal heat transport by dynamics (W.m-2).
    263       real,dimension(:,:),allocatable,save :: OLR_nu        ! Outgoing LW radiation in each band (Normalized to the band width (W/m2/cm-1)).
    264       real,dimension(:,:),allocatable,save :: OSR_nu        ! Outgoing SW radiation in each band (Normalized to the band width (W/m2/cm-1)).
    265       real,dimension(:,:),allocatable,save :: zdtlw         ! LW heating tendencies (K/s).
    266       real,dimension(:,:),allocatable,save :: zdtsw         ! SW heating tendencies (K/s).
    267       real,dimension(:),allocatable,save :: sensibFlux      ! Turbulent flux given by the atmosphere to the surface (W.m-2).
    268      
    269 !$OMP THREADPRIVATE(fluxsurf_lw,fluxsurf_sw,fluxsurfabs_sw,fluxtop_lw,fluxabs_sw,fluxtop_dn,fluxdyn,OLR_nu,OSR_nu,&
    270250       
    271251        !$OMP zdtlw,zdtsw,sensibFlux)
     
    363343      real vmr(ngrid,nlayer)                        ! volume mixing ratio
    364344      real time_phys
    365       real,allocatable,dimension(:),save :: tau_col ! Total Aerosol Optical Depth.
    366 !$OMP THREADPRIVATE(tau_col)
    367345     
    368346      real ISR,ASR,OLR,GND,DYN,GSR,Ts1,Ts2,Ts3,TsS ! for Diagnostic.
     
    389367      real dItot, dItot_tmp, dVtot, dVtot_tmp
    390368
    391       real,allocatable,save :: hice(:) ! Oceanic Ice height. by BC
    392  !$OMP THREADPRIVATE(hice)     
    393369
    394370      real h2otot                      ! Total Amount of water. For diagnostic.
     
    438414!$OMP THREADPRIVATE(ice_initial,ice_min,ice_update)
    439415
    440 !     For slab ocean. By BC
    441       real, dimension(:),allocatable,save ::  pctsrf_sic
    442       real, dimension(:,:),allocatable,save :: tslab
    443       real, dimension(:),allocatable,save ::  tsea_ice
    444       real, dimension(:),allocatable,save :: sea_ice
    445       real, dimension(:),allocatable,save :: zmasq
    446       integer, dimension(:),allocatable,save ::knindex
    447 !$OMP THREADPRIVATE(pctsrf_sic,tslab,tsea_ice,sea_ice,zmasq,knindex)
    448416
    449417      real :: tsurf2(ngrid)
     
    463431! --------------------------------
    464432      if (firstcall) then
    465 
    466433        ! Allocate saved arrays.
    467         ALLOCATE(tsurf(ngrid))
    468         ALLOCATE(tsoil(ngrid,nsoilmx))   
    469         ALLOCATE(albedo(ngrid,L_NSPECTV))
    470          ALLOCATE(albedo_equivalent(ngrid))       
    471          ALLOCATE(albedo_snow_SPECTV(L_NSPECTV))
    472          ALLOCATE(albedo_co2_ice_SPECTV(L_NSPECTV))
    473          ALLOCATE(albedo_bareground(ngrid))           
    474         ALLOCATE(rnat(ngrid))         
    475         ALLOCATE(emis(ngrid))   
    476         ALLOCATE(dtrad(ngrid,nlayer))
    477         ALLOCATE(fluxrad_sky(ngrid))
    478         ALLOCATE(fluxrad(ngrid))   
    479         ALLOCATE(capcal(ngrid))   
    480         ALLOCATE(fluxgrd(ngrid)) 
    481         ALLOCATE(qsurf(ngrid,nq)) 
    482         ALLOCATE(q2(ngrid,nlayer+1))
    483         ALLOCATE(ztprevious(ngrid,nlayer))
    484         ALLOCATE(zuprevious(ngrid,nlayer))
    485         ALLOCATE(cloudfrac(ngrid,nlayer))
    486         ALLOCATE(totcloudfrac(ngrid))
    487         ALLOCATE(hice(ngrid))
    488         ALLOCATE(qsurf_hist(ngrid,nq))
    489         ALLOCATE(reffrad(ngrid,nlayer,naerkind))
    490         ALLOCATE(nueffrad(ngrid,nlayer,naerkind))
    491         ALLOCATE(ice_initial(ngrid))
    492         ALLOCATE(ice_min(ngrid))
    493         ALLOCATE(fluxsurf_lw(ngrid))
    494         ALLOCATE(fluxsurf_sw(ngrid))
    495         ALLOCATE(fluxsurfabs_sw(ngrid))
    496         ALLOCATE(fluxtop_lw(ngrid))
    497         ALLOCATE(fluxabs_sw(ngrid))
    498         ALLOCATE(fluxtop_dn(ngrid))
    499         ALLOCATE(fluxdyn(ngrid))
    500         ALLOCATE(OLR_nu(ngrid,L_NSPECTI))
    501         ALLOCATE(OSR_nu(ngrid,L_NSPECTV))
    502         ALLOCATE(sensibFlux(ngrid))
    503         ALLOCATE(zdtlw(ngrid,nlayer))
    504         ALLOCATE(zdtsw(ngrid,nlayer))
    505         ALLOCATE(tau_col(ngrid))
    506         ALLOCATE(pctsrf_sic(ngrid))
    507         ALLOCATE(tslab(ngrid,noceanmx))
    508         ALLOCATE(tsea_ice(ngrid))
    509         ALLOCATE(sea_ice(ngrid))
    510         ALLOCATE(zmasq(ngrid))
    511         ALLOCATE(knindex(ngrid))
    512 
    513         ! This is defined in comsaison_h
    514         ALLOCATE(mu0(ngrid))
    515         ALLOCATE(fract(ngrid))           
    516          ! This is defined in radcommon_h
    517         ALLOCATE(glat(ngrid))
    518        
     434        call phys_stat_var_mod
    519435
    520436!        Variables set to 0
     
    550466!        Read 'startfi.nc' file.
    551467!        ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
     468#ifndef MESOSCALE
    552469         call phyetat0(startphy_file,                                 &
    553470                       ngrid,nlayer,"startfi.nc",0,0,nsoilmx,nq,      &
     
    555472                       cloudfrac,totcloudfrac,hice,                   &
    556473                       rnat,pctsrf_sic,tslab, tsea_ice,sea_ice)
     474#else
     475      emis(:)=0.0
     476      q2(:,:)=0.0
     477      qsurf(:,:)=0.0
     478      day_ini = pday
     479#endif
     480
     481#ifndef MESOSCALE
    557482         if (.not.startphy_file) then
    558483           ! additionnal "academic" initialization of physics
     
    566491           day_ini=pday
    567492         endif
     493#endif
    568494
    569495         if (pday.ne.day_ini) then
     
    739665         call su_watercycle ! even if we don't have a water cycle, we might
    740666                            ! need epsi for the wvp definitions in callcorrk.F
    741 
     667#ifndef MESOSCALE
    742668         if (ngrid.ne.1) then ! Note : no need to create a restart file in 1d.
    743669            call physdem0("restartfi.nc",longitude,latitude,nsoilmx,ngrid,nlayer,nq, &
     
    745671                          albedo_bareground,inertiedat,zmea,zstd,zsig,zgam,zthe)
    746672         endif
     673#endif         
    747674         
    748675         ! XIOS outputs
     
    11071034         end if !end of 'UseTurbDiff'
    11081035
    1109 
    1110          pdv(1:ngrid,1:nlayer)=pdv(1:ngrid,1:nlayer)+zdvdif(1:ngrid,1:nlayer)
    1111          pdu(1:ngrid,1:nlayer)=pdu(1:ngrid,1:nlayer)+zdudif(1:ngrid,1:nlayer)
    1112          pdt(1:ngrid,1:nlayer)=pdt(1:ngrid,1:nlayer)+zdtdif(1:ngrid,1:nlayer)
    1113          zdtsurf(1:ngrid)=zdtsurf(1:ngrid)+zdtsdif(1:ngrid)
    1114 
     1036         !!! this is always done, except for turbulence-resolving simulations
     1037         if (.not. turb_resolved) then
     1038           pdv(1:ngrid,1:nlayer)=pdv(1:ngrid,1:nlayer)+zdvdif(1:ngrid,1:nlayer)
     1039           pdu(1:ngrid,1:nlayer)=pdu(1:ngrid,1:nlayer)+zdudif(1:ngrid,1:nlayer)
     1040           pdt(1:ngrid,1:nlayer)=pdt(1:ngrid,1:nlayer)+zdtdif(1:ngrid,1:nlayer)
     1041           zdtsurf(1:ngrid)=zdtsurf(1:ngrid)+zdtsdif(1:ngrid)
     1042         endif
    11151043
    11161044         if(ok_slab_ocean)then
     
    19491877
    19501878         endif
    1951 
     1879#ifndef MESOSCALE
     1880         
    19521881         if (ngrid.ne.1) then
    19531882            write(*,*)'PHYSIQ: for physdem ztime_fin =',ztime_fin
     
    19591888                          rnat,pctsrf_sic,tslab,tsea_ice,sea_ice)
    19601889         endif
    1961 
     1890#endif
    19621891         if(ok_slab_ocean) then
    19631892            call ocean_slab_final!(tslab, seaice)
     
    20581987      endif ! end of 'callstats'
    20591988
    2060 
     1989#ifndef MESOSCALE
     1990       
    20611991!-----------------------------------------------------------------------------------------------------
    20621992!           OUTPUT in netcdf file "DIAGFI.NC", containing any variable for diagnostic
     
    20671997!                      but its preferable to keep all the calls in one place ...
    20681998!-----------------------------------------------------------------------------------------------------
    2069 
    20701999
    20712000      call writediagfi(ngrid,"Ls","solar longitude","deg",0,zls*180./pi)
     
    22392168      endif
    22402169
     2170#else
     2171      comm_HR_SW(1:ngrid,1:nlayer) = zdtsw(1:ngrid,1:nlayer)
     2172      comm_HR_LW(1:ngrid,1:nlayer) = zdtlw(1:ngrid,1:nlayer)
     2173      comm_CLOUDFRAC(1:ngrid,1:nlayer)=cloudfrac(1:ngrid,1:nlayer)
     2174      comm_TOTCLOUDFRAC(1:ngrid)=totcloudfrac(1:ngrid)
     2175      comm_RAIN(1:ngrid,1:nlayer)=zdqrain(1:ngrid,1:nlayer,igcm_h2o_vap)
     2176      comm_SNOW(1:ngrid,1:nlayer)=zdqrain(1:ngrid,1:nlayer,igcm_h2o_ice)
     2177      comm_ALBEQ(1:ngrid)=albedo_equivalent(1:ngrid)
     2178      comm_FLUXTOP_DN(1:ngrid)=fluxtop_dn(1:ngrid)
     2179      comm_FLUXABS_SW(1:ngrid)=fluxabs_sw(1:ngrid)
     2180      comm_FLUXTOP_LW(1:ngrid)=fluxtop_lw(1:ngrid)
     2181      comm_FLUXSURF_SW(1:ngrid)=fluxsurf_sw(1:ngrid)
     2182      comm_FLUXSURF_LW(1:ngrid)=fluxsurf_lw(1:ngrid)
     2183      comm_FLXGRD(1:ngrid)=fluxgrd(1:ngrid)
     2184      comm_LSCEZ(1:ngrid,1:nlayer)=lscaledEz(1:ngrid,1:nlayer)
     2185      comm_H2OICE_REFF(1:ngrid,1:nlayer)=reffrad(1:ngrid,1:nlayer,iaero_h2o)
     2186      sensibFlux(1:ngrid) = zflubid(1:ngrid) - capcal(1:ngrid)*zdtsdif(1:ngrid) !!! ????
     2187#endif
     2188
    22412189! XIOS outputs
    22422190#ifdef CPP_XIOS     
Note: See TracChangeset for help on using the changeset viewer.