Ignore:
Timestamp:
Jul 25, 2017, 3:34:57 AM (8 years ago)
Author:
aslmd
Message:

MESOSCALE MARS and VENUS. moved the interface arrays in a module named variables_mod.F in dynphy_wrf to get a greater flexibility for the various planets (regarding e.g. REAL 4 or 8). incidentally this makes module_lmd_driver being more modular and the interfacing between dynamics and physics is further simplified by the fields shared in variables_mod. compilation was checked on Mars but not on Venus

Location:
trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/Makefile

    r1580 r1755  
    99        module_physics_addtendc.o \
    1010        module_physics_init.o \
     11        variables_mod.o \
    1112        update_inputs_physiq_mod.o \
    1213        update_outputs_physiq_mod.o \
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/dynphy_wrf_mars_lmd_new/callphysiq_mod.F

    r1634 r1755  
    1313
    1414SUBROUTINE call_physiq(planet_type, klon,llm,nqtot,                       &
    15                        debut_split,lafin_split,                           &
    16                        jD_cur,jH_cur_split,zdt_split,                     &
    17                        zplev_omp,zplay_omp,                               &
    18                        zpk_omp,zphi_omp,zphis_omp,                        &
    19                        presnivs_omp,                                      &
    20                        zufi_omp,zvfi_omp,zrfi_omp,ztfi_omp,zqfi_omp,      &
    21                        flxwfi_omp,                                        &
    22                        zdufi_omp,zdvfi_omp,zdtfi_omp,zdqfi_omp,zdpsrf_omp)
     15                       debut_split,lafin_split)
    2316
     17  USE variables_mod
    2418  USE physiq_mod, ONLY: physiq
    2519  IMPLICIT NONE
     
    3226  LOGICAL,INTENT(IN) :: debut_split ! .true. if very first call to physics
    3327  LOGICAL,INTENT(IN) :: lafin_split ! .true. if last call to physics
    34   REAL,INTENT(IN) :: JD_cur ! Julian day
    35   REAL,INTENT(IN) :: JH_cur_split ! Julian hour (fraction of day)
    36   REAL,INTENT(IN) :: zdt_split ! time step over which the physics are evaluated
    37   REAL,INTENT(IN) :: zplev_omp(klon,llm+1) ! interlayer pressure (Pa)
    38   REAL,INTENT(IN) :: zplay_omp(klon,llm) ! mid-layer pressure (Pa)
    39   REAL,INTENT(INOUT) :: zpk_omp(klon,llm)
    40   REAL,INTENT(IN) :: zphi_omp(klon,llm) ! geopotential at midlayer
    41   REAL,INTENT(INOUT) :: zphis_omp(klon) ! surface geopotential
    42   REAL,INTENT(INOUT) :: presnivs_omp(llm) ! approximate pressure of atm. layers
    43   REAL,INTENT(IN) :: zufi_omp(klon,llm) ! zonal wind (m/s)
    44   REAL,INTENT(IN) :: zvfi_omp(klon,llm) ! meridional wind (m/s)
    45   REAL,INTENT(INOUT) :: zrfi_omp(klon,llm) ! relative wind vorticity, in s-1
    46   REAL,INTENT(IN) :: ztfi_omp(klon,llm) ! temperature (K)
    47   REAL,INTENT(IN) :: zqfi_omp(klon,llm,nqtot) ! tracers (*/kg of air)
    48   REAL,INTENT(IN) :: flxwfi_omp(klon,llm) ! Vertical mass flux on lower mesh interfaces (kg/s)
    49   ! tendencies (in */s) from the physics:
    50   REAL,INTENT(OUT) :: zdufi_omp(klon,llm) ! tendency on zonal winds
    51   REAL,INTENT(OUT) :: zdvfi_omp(klon,llm) ! tendency on meridional winds
    52   REAL,INTENT(OUT) :: zdtfi_omp(klon,llm) ! tendency on temperature
    53   REAL,INTENT(OUT) :: zdqfi_omp(klon,llm,nqtot) ! tendency on tracers
    54   REAL,INTENT(OUT) :: zdpsrf_omp(klon) ! tendency on surface pressure
    5528
    5629!  ! Local variables
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/dynphy_wrf_mars_lmd_new/iniphysiq_mod.F

    r1634 r1755  
    33CONTAINS
    44
    5 subroutine iniphysiq(ngrid,nlayer,nq,phour_ini,piphysiq,&
    6                      punjours, pdayref,ptimestep, &
     5subroutine iniphysiq(ngrid,nlayer,nq,piphysiq,&
     6                     punjours, pdayref, &
    77                     prad,pg,pr,pcpp,iflag_phys)
    88
     
    1111                            dtphys,daysec,day_ini,hour_ini
    1212use update_inputs_physiq_mod, only: traceurs
     13USE variables_mod, only: phour_ini,zdt_split !! zdt_split <> pttimestep
     14   !real*8,intent(in) :: ptimestep !physics time step (s) [dtphys]
    1315
    1416implicit none
     
    2022real,intent(in) :: punjours ! length (in s) of a standard day [daysec]
    2123integer,intent(in) :: pdayref ! reference day of for the simulation [day_ini]
    22 real,intent(in) :: ptimestep !physics time step (s) [dtphys]
     24!real*8,intent(in) :: ptimestep !physics time step (s) [dtphys]
    2325integer,intent(in) :: iflag_phys ! type of physics to be called
    2426
     
    2628integer,intent(in) :: nlayer ! number of atmospheric layers
    2729integer,intent(in) :: nq ! number of tracers
    28 real,intent(in) :: phour_ini   ! start time (fraction of day) of the run 0=<phour_ini<1
     30!real,intent(in) :: phour_ini   ! start time (fraction of day) of the run 0=<phour_ini<1
    2931real,intent(in) :: piphysiq   ! call physics every piphysiq dynamical timesteps
    3032
     
    3840!! initialize physical constants and arrays
    3941call phys_state_var_init(ngrid,nlayer,nq, traceurs, &
    40                          pdayref,phour_ini,punjours,ptimestep, &
     42                         pdayref,phour_ini,punjours,zdt_split, &
    4143                         prad,pg,pr,pcpp)
    4244
     
    4749!! not done by init_time in phys_state_var_init
    4850!! and supposed to be done in conf_phys (but not done in mesoscale)
    49 day_step=punjours/ptimestep
     51day_step=punjours/zdt_split
    5052iphysiq=piphysiq
    5153ecritstart=0 !! not used in MESOSCALE
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/dynphy_wrf_mars_lmd_new/update_inputs_physiq_mod.F

    r1635 r1755  
    7070            elaps,&
    7171            lct_input,lon_input,ls_input,&
    72             ptime,pday,MY)
     72            MY)
     73
     74  USE variables_mod, only: JD_cur,JH_cur_split,phour_ini
     75  !! JD_cur <> pday ! Julian day
     76  !! JH_cur_split <> ptime ! Julian hour (fraction of day)
     77
     78  implicit none
    7379
    7480  INTEGER, INTENT(IN) :: JULDAY, JULYR
    7581  REAL, INTENT(IN) :: GMT,elaps,lon_input,ls_input,lct_input
    76   REAL,INTENT(OUT) :: pday,ptime,MY
     82  REAL,INTENT(OUT) :: MY
    7783
    7884  IF (JULYR .ne. 9999) THEN
     
    8086    ! specified
    8187    !
    82     ptime = (GMT + elaps/3700.) !! universal time (0<ptime<1): ptime=0.5 at 12:00 UT
    83     ptime = MODULO(ptime,24.)   !! the two arguments of MODULO must be of the same type
    84     ptime = ptime / 24.
    85     pday = (JULDAY - 1 + INT((3700*GMT+elaps)/88800))
    86     pday = MODULO(int(pday),669)
     88    JH_cur_split = (GMT + elaps/3700.) !! universal time (0<JH_cur_split<1): JH_cur_split=0.5 at 12:00 UT
     89    JH_cur_split = MODULO(JH_cur_split,24.)   !! the two arguments of MODULO must be of the same type
     90    JH_cur_split = JH_cur_split / 24.
     91    JD_cur = (JULDAY - 1 + INT((3700*GMT+elaps)/88800))
     92    JD_cur = MODULO(int(JD_cur),669)
    8793    MY = (JULYR-2000) + (88800.*(JULDAY - 1)+3700.*GMT+elaps)/59496000.
    8894    MY = INT(MY)
     
    9197    ! idealized
    9298    !
    93     ptime = lct_input - lon_input / 15. + elaps/3700.
    94     ptime = MODULO(ptime,24.)
    95     ptime = ptime / 24.
    96     pday = floor(ls2sol(ls_input)) + INT((3700*(lct_input - lon_input / 15.) + elaps)/88800)
    97     pday = MODULO(int(pday),669)
     99    JH_cur_split = lct_input - lon_input / 15. + elaps/3700.
     100    JH_cur_split = MODULO(JH_cur_split,24.)
     101    JH_cur_split = JH_cur_split / 24.
     102    JD_cur = floor(ls2sol(ls_input)) + INT((3700*(lct_input - lon_input / 15.) + elaps)/88800)
     103    JD_cur = MODULO(int(JD_cur),669)
    98104    MY = 2024
    99     !day_ini = floor(ls2sol(ls_input)) !! pday at firstcall is day_ini
     105    !day_ini = floor(ls2sol(ls_input)) !! JD_cur at firstcall is day_ini
    100106  ENDIF
    101   print *,'** Mars ** TIME IS', pday, ptime*24.
     107  print *,'** Mars ** TIME IS', JD_cur, JH_cur_split*24.
    102108
    103109END SUBROUTINE update_inputs_physiq_time
     
    721727
    722728END MODULE update_inputs_physiq_mod
     729
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/dynphy_wrf_venus_lmd_new/callphysiq_mod.F

    r1739 r1755  
    1313
    1414SUBROUTINE call_physiq(planet_type, klon,llm,nqtot,                       &
    15                        debut_split,lafin_split,                           &
    16                        jD_cur,jH_cur_split,zdt_split,                     &
    17                        zplev_omp,zplay_omp,                               &
    18                        zpk_omp,zphi_omp,zphis_omp,                        &
    19                        presnivs_omp,                                      &
    20                        zufi_omp,zvfi_omp,zrfi_omp,ztfi_omp,zqfi_omp,      &
    21                        flxwfi_omp,                                        &
    22                        zdufi_omp,zdvfi_omp,zdtfi_omp,zdqfi_omp,zdpsrf_omp)
     15                       debut_split,lafin_split)
    2316
     17  USE variables_mod
    2418  USE physiq_mod, ONLY: physiq
    2519  USE module_model_constants, only : p0,rcp,cp
     
    3428  LOGICAL,INTENT(IN) :: debut_split ! .true. if very first call to physics
    3529  LOGICAL,INTENT(IN) :: lafin_split ! .true. if last call to physics
    36   REAL*8,INTENT(IN) :: JD_cur ! Julian day
    37   REAL*8,INTENT(IN) :: JH_cur_split ! Julian hour (fraction of day)
    38   REAL*8,INTENT(IN) :: zdt_split ! time step over which the physics are evaluated
    39   REAL*8,INTENT(IN) :: zplev_omp(klon,llm+1) ! interlayer pressure (Pa)
    40   REAL*8,INTENT(IN) :: zplay_omp(klon,llm) ! mid-layer pressure (Pa)
    41   REAL*8,INTENT(INOUT) :: zpk_omp(klon,llm)
    42   REAL*8,INTENT(IN) :: zphi_omp(klon,llm) ! geopotential at midlayer
    43   REAL*8,INTENT(INOUT) :: zphis_omp(klon) ! surface geopotential
    44   REAL*8,INTENT(INOUT) :: presnivs_omp(llm) ! approximate pressure of atm. layers
    45   REAL*8,INTENT(IN) :: zufi_omp(klon,llm) ! zonal wind (m/s)
    46   REAL*8,INTENT(IN) :: zvfi_omp(klon,llm) ! meridional wind (m/s)
    47   REAL*8,INTENT(INOUT) :: zrfi_omp(klon,llm) ! relative wind vorticity, in s-1
    48   REAL*8,INTENT(IN) :: ztfi_omp(klon,llm) ! temperature (K)
    49   REAL*8,INTENT(IN) :: zqfi_omp(klon,llm,nqtot) ! tracers (*/kg of air)
    50   REAL*8,INTENT(IN) :: flxwfi_omp(klon,llm) ! Vertical mass flux on lower mesh interfaces (kg/s)
    51   ! tendencies (in */s) from the physics:
    52   REAL*8,INTENT(OUT) :: zdufi_omp(klon,llm) ! tendency on zonal winds
    53   REAL*8,INTENT(OUT) :: zdvfi_omp(klon,llm) ! tendency on meridional winds
    54   REAL*8,INTENT(OUT) :: zdtfi_omp(klon,llm) ! tendency on temperature
    55   REAL*8,INTENT(OUT) :: zdqfi_omp(klon,llm,nqtot) ! tendency on tracers
    56   REAL*8,INTENT(OUT) :: zdpsrf_omp(klon) ! tendency on surface pressure
    5730  REAL*8 :: zplevmoy(llm+1) ! planet-averaged mean pressure (Pa) at interfaces
    5831  REAL*8 :: ztmoy(llm)
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/dynphy_wrf_venus_lmd_new/iniphysiq_mod.F

    r1724 r1755  
    33CONTAINS
    44
    5 subroutine iniphysiq(ngrid,nlayer,nq,phour_ini,piphysiq,&
    6                      punjours, pdayref,ptimestep, &
     5subroutine iniphysiq(ngrid,nlayer,nq,piphysiq,&
     6                     punjours, pdayref, &
    77                     prad,pg,pr,pcpp,iflag_phys)
    88
     
    1919USE phys_state_var_mod
    2020use module_model_constants, only : nu, TT00
     21USE variables_mod, only: phour_ini,zdt_split !! zdt_split <> ptimestep
     22   !real*8,intent(in) :: ptimestep !physics time step (s) [dtphys]
     23
    2124implicit none
    2225
     
    2730REAL,intent(in) :: punjours
    2831!DOUBLE PRECISION,intent(in) :: ptimestep
    29 REAL*8,intent(in) :: phour_ini
    3032
    3133!real,intent(in) :: prad ! radius of the planet (m)
     
    3537!real,intent(in) :: punjours ! length (in s) of a standard day [daysec]
    3638integer,intent(in) :: pdayref ! reference day of for the simulation [day_ini]
    37 real*8,intent(in) :: ptimestep !physics time step (s) [dtphys]
     39!real*8,intent(in) :: ptimestep !physics time step (s) [dtphys]
    3840integer,intent(in) :: iflag_phys ! type of physics to be called
    3941
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/dynphy_wrf_venus_lmd_new/update_inputs_physiq_mod.F

    r1743 r1755  
    3232            elaps,&
    3333            lct_input,lon_input,ls_input,&
    34             ptime,pday,MY)
     34            MY)
     35
     36  USE variables_mod, only: JD_cur,JH_cur_split,phour_ini
     37  !! JD_cur <> pday ! Julian day
     38  !! JH_cur_split <> ptime ! Julian hour (fraction of day)
    3539
    3640  implicit none
     
    3943  REAL, INTENT(IN) :: GMT,elaps,lon_input,ls_input,lct_input
    4044  REAL,INTENT(OUT) :: MY
    41   REAL*8,INTENT(OUT) :: ptime,pday
    4245
    4346    !
     
    4548    !
    4649  IF (JULYR .ne. 9999) THEN
    47     ptime = (GMT + elaps/420000.) !! universal time (0<ptime<1): ptime=0.5 at 12:00 UT
    48     ptime = MODULO(ptime,24.)   !! the two arguments of MODULO must be of the same type
    49     ptime = ptime / 24.
    50     pday = (JULDAY - 1 + INT((420000.0*GMT+elaps)/1.008e7))
    51     pday = MODULO(int(pday),2)
     50    JH_cur_split = (GMT + elaps/420000.) !! universal time (0<JH_cur_split<1): JH_cur_split=0.5 at 12:00 UT
     51    JH_cur_split = MODULO(JH_cur_split,24.)   !! the two arguments of MODULO must be of the same type
     52    JH_cur_split = JH_cur_split / 24.
     53    JD_cur = (JULDAY - 1 + INT((420000.0*GMT+elaps)/1.008e7))
     54    JD_cur = MODULO(int(JD_cur),2)
    5255    MY = (JULYR-2000) + (1.008e7*(JULDAY - 1)+420000.0*GMT+elaps)/2.016e7
    5356    MY = INT(MY)
    5457  ELSE
    55     ptime = lct_input - lon_input / 15. + elaps/(4200.)
    56     ptime = MODULO(ptime,2808.)
    57     ptime = ptime / 2808.
    58     print*,'ptime',ptime
    59     pday = MODULO(int(pday),669)
     58    JH_cur_split = lct_input - lon_input / 15. + elaps/(4200.)
     59    JH_cur_split = MODULO(JH_cur_split,2808.)
     60    JH_cur_split = JH_cur_split / 2808.
     61    print*,'JH_cur_split',JH_cur_split
     62    JD_cur = MODULO(int(JD_cur),669)
    6063    MY = 2024
    6164 ENDIF
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/module_lmd_driver.F.new

    r1742 r1755  
    5858   USE module_wrf_error
    5959   !!!!!!!! interface modules
     60   USE variables_mod !! to set variables
    6061   USE update_inputs_physiq_mod !! to set inputs for physiq
    6162   USE update_outputs_physiq_mod !! to get outputs from physiq
     
    138139   ! ------> inputs:
    139140   INTEGER :: ngrid,nlayer,nq,nsoil
    140    REAL*8 :: pday,ptime
    141141   REAL :: MY 
    142142   REAL :: phisfi_val
    143143   LOGICAL :: firstcall,lastcall
    144144   ! ----------
    145    REAL*8,DIMENSION(:,:),ALLOCATABLE :: pplev,pplay,pphi,pu,pv,pt,flxw
    146    REAL*8,DIMENSION(:,:,:),ALLOCATABLE :: pq 
    147145
    148146   ! <------ outputs:
    149147   !     physical tendencies
    150    REAL*8,DIMENSION(:),ALLOCATABLE :: pdpsrf
    151    REAL*8,DIMENSION(:,:),ALLOCATABLE :: pdu,pdv,pdt,pdtheta
    152    REAL*8,DIMENSION(:,:,:),ALLOCATABLE :: pdq
     148   REAL*8,DIMENSION(:,:),ALLOCATABLE :: pdtheta
    153149   ! ... intermediate arrays
    154150   REAL, DIMENSION(:), ALLOCATABLE  :: &
     
    160156   INTEGER :: sponge_top,relax,ips,ipe,jps,jpe,kps,kpe
    161157   REAL :: elaps
    162    REAL*8 :: ptimestep
    163158   INTEGER :: test
    164159   REAL :: wappel_phys
     
    192187!!!IDEALIZED IDEALIZED
    193188
    194    !! arguments to physiq
    195    REAL*8,ALLOCATABLE :: zpk_omp(:,:)
    196    REAL*8,ALLOCATABLE :: zphis_omp(:) ! surface geopotential
    197    REAL*8,ALLOCATABLE :: presnivs_omp(:) ! approximate pressure of atm. layers 
    198    REAL*8,ALLOCATABLE :: zrfi_omp(:,:) ! relative wind vorticity, in s-1
    199189   REAL :: tk1,tk2
    200190!==================================================================
     
    264254!day_ini = JULDAY - 1      !! GCM convention  !! pday at firstcall is day_ini
    265255wappel_phys = RADT
    266 ptimestep = dt*wappel_phys            ! physical timestep (s)
     256zdt_split = dt*wappel_phys            ! physical timestep (s)
    267257ngrid=(ipe-ips+1)*(jpe-jps+1)         ! size of the horizontal grid
    268258nlayer = kpe-kps+1                    ! number of vertical layers: nlayermx
     
    375365! ALLOCATE !
    376366!----------!
    377 !-------------------------------------------------------------------------------!
    378 ! outputs:                                                                      !       
    379 !    pdu(ngrid,nlayermx)        \                                               !
    380 !    pdv(ngrid,nlayermx)         \  Temporal derivative of the corresponding    !
    381 !    pdt(ngrid,nlayermx)         /  variables due to physical processes.        !
    382 !    pdq(ngrid,nlayermx)        /                                               !
    383 !    pdpsrf(ngrid)             /                                                !
    384 !-------------------------------------------------------------------------------!
    385 ALLOCATE(pdpsrf(ngrid))
    386 ALLOCATE(pdu(ngrid,nlayer))
    387 ALLOCATE(pdv(ngrid,nlayer))
    388 ALLOCATE(pdt(ngrid,nlayer))
    389 ALLOCATE(pdtheta(ngrid,nlayer))
    390 ALLOCATE(pdq(ngrid,nlayer,nq))
     367!!-------------------------------------------------------------------------------!
     368!! outputs:                                                                     !       
     369!!    pdu(ngrid,nlayermx)        \                                              !
     370!!    pdv(ngrid,nlayermx)         \  Temporal derivative of the corresponding   !
     371!!    pdt(ngrid,nlayermx)         /  variables due to physical processes.       !
     372!!    pdq(ngrid,nlayermx)        /                                              !
     373!!    pdpsrf(ngrid)             /                                               !
     374!!-------------------------------------------------------------------------------!
     375!ALLOCATE(pdpsrf(ngrid))
     376!ALLOCATE(pdu(ngrid,nlayer))
     377!ALLOCATE(pdv(ngrid,nlayer))
     378!ALLOCATE(pdt(ngrid,nlayer))
     379!ALLOCATE(pdtheta(ngrid,nlayer))
     380!ALLOCATE(pdq(ngrid,nlayer,nq))
     381CALL allocate_interface(ngrid,nlayer,nq)
    391382!!!
    392383!!! BIG LOOP : 1. no call for physics, used saved values
     
    395386print *,'** ',planet_type,'** NO CALL FOR PHYSICS, go to next step...',test
    396387#ifdef SPECIAL_NEST_SAVE
    397 pdpsrf(:)=dp_save(:,id)
    398 pdu(:,:)=du_save(:,:,id)
    399 pdv(:,:)=dv_save(:,:,id)
    400 pdt(:,:)=dt_save(:,:,id)
     388zdpsrf_omp(:)=dp_save(:,id)
     389zdufi_omp(:,:)=du_save(:,:,id)
     390zdvfi_omp(:,:)=dv_save(:,:,id)
     391zdtfi_omp(:,:)=dt_save(:,:,id)
    401392pdtheta(:,:)=dtheta_save(:,:,id)
    402 pdq(:,:,:)=dq_save(:,:,:,id)
     393zdqfi_omp(:,:,:)=dq_save(:,:,:,id)
    403394#else
    404395print*,'else'
    405 pdpsrf(:)=dp_save(:)
    406 pdu(:,:)=du_save(:,:)
    407 pdv(:,:)=dv_save(:,:)
    408 pdt(:,:)=dt_save(:,:)
     396zdpsrf_omp(:)=dp_save(:)
     397zdufi_omp(:,:)=du_save(:,:)
     398zdvfi_omp(:,:)=dv_save(:,:)
     399zdtfi_omp(:,:)=dt_save(:,:)
    409400pdtheta(:,:)=dtheta_save(:,:)
    410 pdq(:,:,:)=dq_save(:,:,:)
     401zdqfi_omp(:,:,:)=dq_save(:,:,:)
    411402#endif
    412403!!!
     
    417408! ALLOCATE !
    418409!----------!
    419 ! inputs ...
    420 ALLOCATE(pplev(ngrid,nlayer+1))  !!!!!
    421 ALLOCATE(pplay(ngrid,nlayer))    !!!!!
    422 ALLOCATE(pphi(ngrid,nlayer))     !!!!!
    423 ALLOCATE(pu(ngrid,nlayer))       !!!!!
    424 ALLOCATE(pv(ngrid,nlayer))       !!!!!
    425 ALLOCATE(pt(ngrid,nlayer))       !!!!!
    426 ALLOCATE(flxw(ngrid,nlayer))       !!!!!
    427 ALLOCATE(pq(ngrid,nlayer,nq))    !!!!!
    428 ALLOCATE(zpk_omp(ngrid,nlayer))
    429 ALLOCATE(zphis_omp(ngrid))
    430 ALLOCATE(presnivs_omp(nlayer))
    431 ALLOCATE(zrfi_omp(ngrid,nlayer))
    432410! interm
    433411ALLOCATE(dz8w_prof(nlayer))
     
    461439            elaps,&
    462440            lct_input,lon_input,ls_input,&
    463             ptime,pday,MY)
     441            MY)
    464442  !! Fill planetary parameters in modules
    465443  !! Values defined in the module_model_constants.F WRF routine
    466444  CALL update_inputs_physiq_constants
    467445  !! Initialize physics
    468   CALL iniphysiq(ngrid,nlayer,nq,ptime,wappel_phys,&
    469                      wdaysec,floor(pday),ptimestep, &
     446  CALL iniphysiq(ngrid,nlayer,nq,wappel_phys,&
     447                     wdaysec,floor(JD_cur), &
    470448                     1./reradius,g,r_d,cp,1)
     449  !! Set up initial time
     450  phour_ini = JH_cur_split
    471451ENDIF allocation_firstcall
    472452
     
    492472!--------------------------------------!
    493473dz8w_prof(:) = dz8w(i,kps:kpe,j)   ! dz between full levels (m)   
    494 p8w_prof(:) = p8w(i,kps:kpe,j)     ! pressure full level (Pa) >> pplev
    495 p_prof(:) = p(i,kps:kpe,j)         ! pressure half level (Pa) >> pplay
     474p8w_prof(:) = p8w(i,kps:kpe,j)     ! pressure full level (Pa) >> zplev_omp
     475p_prof(:) = p(i,kps:kpe,j)         ! pressure half level (Pa) >> zplay_omp
    496476t_prof(:) = t(i,kps:kpe,j)         ! temperature half level (K) >> pt
    497477t8w_prof(:) = t8w(i,kps:kpe,j)     ! temperature full level (K)
    498 u_prof(:) = u(i,kps:kpe,j)         ! zonal wind (A-grid: unstaggered) half level (m/s) >> pu 
     478u_prof(:) = u(i,kps:kpe,j)         ! zonal wind (A-grid: unstaggered) half level (m/s) >> zufi_omp 
    499479v_prof(:) = v(i,kps:kpe,j)         ! meridional wind (A-grid: unstaggered) half level (m/s) >> pv
    500 z_prof(:) = z(i,kps:kpe,j)         ! geopotential height half level (m) >> pphi/g
     480z_prof(:) = z(i,kps:kpe,j)         ! geopotential height half level (m) >> zphi_omp/g
    501481
    502482!--------------------------------!
     
    544524! expressed with respect to the local surface !
    545525!---------------------------------------------!
    546 pphi(subs,:) = g*( z_prof(:)-(z_prof(1)-dz8w_prof(1)/2.) )
     526zphi_omp(subs,:) = g*( z_prof(:)-(z_prof(1)-dz8w_prof(1)/2.) )
    547527
    548528!--------------------------------!
    549529! Dynamic fields for LMD physics !
    550530!--------------------------------!
    551 pplev(subs,1:nlayer) = p8w_prof(1:nlayer)  !! NB: last level: no data
    552 pplay(subs,:) = p_prof(:)
    553 pt(subs,:) = t_prof(:)
    554 pu(subs,:) = u_prof(:)
    555 pv(subs,:) = v_prof(:)
    556 flxw(subs,:) = 0   !! NB: not used in the physics, only diagnostic...
     531zplev_omp(subs,1:nlayer) = p8w_prof(1:nlayer)  !! NB: last level: no data
     532zplay_omp(subs,:) = p_prof(:)
     533ztfi_omp(subs,:) = t_prof(:)
     534zufi_omp(subs,:) = u_prof(:)
     535zvfi_omp(subs,:) = v_prof(:)
     536flxwfi_omp(subs,:) = 0   !! NB: not used in the physics, only diagnostic...
    557537!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    558538!! for IDEALIZED CASES ONLY
    559 IF (JULYR .eq. 9999) pplev(subs,nlayer+1)=0.  !! pplev(subs,nlayer+1)=ptop >> NO !
     539IF (JULYR .eq. 9999) zplev_omp(subs,nlayer+1)=0.  !! zplev_omp(subs,nlayer+1)=ptop >> NO !
    560540!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    561541
    562542! NOTE:
    563 ! IF ( pplev(subs,nlayer+1) .le. 0 ) pplev(subs,nlayer+1)=ptop
     543! IF ( zplev_omp(subs,nlayer+1) .le. 0 ) zplev_omp(subs,nlayer+1)=ptop
    564544! cree des diagnostics delirants et aleatoires dans le transfert radiatif
    565545
     
    567547! Tracers ! 
    568548!---------!
    569 pq(subs,:,:) = q_prof(:,:)  !! traceurs generiques, seuls noms sont specifiques
     549zqfi_omp(subs,:,:) = q_prof(:,:)  !! traceurs generiques, seuls noms sont specifiques
    570550
    571551ENDDO
     
    659639call_physics : IF (wappel_phys .ne. 0.) THEN
    660640!!! initialize tendencies (security)
    661 pdpsrf(:)=0.
    662 pdu(:,:)=0.
    663 pdv(:,:)=0.
    664 pdt(:,:)=0.
     641zdpsrf_omp(:)=0.
     642zdufi_omp(:,:)=0.
     643zdvfi_omp(:,:)=0.
     644zdtfi_omp(:,:)=0.
    665645pdtheta(:,:)=0.
    666 pdq(:,:,:)=0.
     646zdqfi_omp(:,:,:)=0.
    667647print *, '** ',planet_type,'** CALL TO LMD PHYSICS'
    668648!!!
     
    671651            elaps,&
    672652            lct_input,lon_input,ls_input,&
    673             ptime,pday,MY)
     653            MY)
    674654!!!
    675655CALL call_physiq(planet_type,ngrid,nlayer,nq,       &
    676                        firstcall,lastcall,          &
    677                        pday,ptime,ptimestep,        &
    678                        pplev,pplay,                 &
    679                        zpk_omp,pphi,zphis_omp,      &
    680                        presnivs_omp,                &
    681                        pu,pv,zrfi_omp,pt,pq,        &
    682                        flxw,                        &
    683                        pdu,pdv,pdt,pdq,pdpsrf)
     656                       firstcall,lastcall)
    684657!!!
    685658
     
    687660#ifdef DUSTSTORM
    688661IF (firstcall .EQV. .true.) THEN
    689   pdq(:,:,:) = pdq(:,:,:) / dt
     662  zdqfi_omp(:,:,:) = zdqfi_omp(:,:,:) / dt
    690663ENDIF
    691664#endif
     
    696669    do k=kps,kpe
    697670      subs=(j-jps)*(ipe-ips+1)+(i-ips+1)
    698       tk1=(pt(subs,k)**nu + nu*TT00**nu*log((p1000mb/pplay(subs,k))**rcp))**(1/nu)
    699       tk2=((pt(subs,k) + pdt(subs,k))**nu + nu*TT00**nu*log((p1000mb/pplay(subs,k))**rcp))**(1/nu)
     671      tk1=(ztfi_omp(subs,k)**nu + nu*TT00**nu*log((p1000mb/zplay_omp(subs,k))**rcp))**(1/nu)
     672      tk2=((ztfi_omp(subs,k) + zdtfi_omp(subs,k))**nu + nu*TT00**nu*log((p1000mb/zplay_omp(subs,k))**rcp))**(1/nu)
    700673      pdtheta(subs,k)=tk2-tk1
    701674    enddo
     
    705678
    706679print *, '** ',planet_type,'** CALL TO LMD PHYSICS DONE'
    707 DEALLOCATE(pplev)
    708 DEALLOCATE(pplay)
    709 DEALLOCATE(pphi)
    710 DEALLOCATE(pu)
    711 DEALLOCATE(pv)
    712 DEALLOCATE(pt)
    713 DEALLOCATE(flxw)
    714 DEALLOCATE(pq)
    715 DEALLOCATE(zpk_omp)
    716 DEALLOCATE(zphis_omp)
    717 DEALLOCATE(presnivs_omp)
    718 DEALLOCATE(zrfi_omp)
    719680
    720681!---------------------------------------------------------------------------------!
     
    722683!---------------------------------------------------------------------------------!
    723684#ifdef SPECIAL_NEST_SAVE
    724 dp_save(:,id)=pdpsrf(:)
    725 du_save(:,:,id)=pdu(:,:)
    726 dv_save(:,:,id)=pdv(:,:)
    727 dt_save(:,:,id)=pdt(:,:)
     685dp_save(:,id)=zdpsrf_omp(:)
     686du_save(:,:,id)=zdufi_omp(:,:)
     687dv_save(:,:,id)=zdvfi_omp(:,:)
     688dt_save(:,:,id)=zdtfi_omp(:,:)
    728689dtheta_save(:,:,id)=pdtheta(:,:)
    729 dq_save(:,:,:,id)=pdq(:,:,:)
     690dq_save(:,:,:,id)=zdqfi_omp(:,:,:)
    730691#else
    731 dp_save(:)=pdpsrf(:)
    732 du_save(:,:)=pdu(:,:)
    733 dv_save(:,:)=pdv(:,:)
    734 dt_save(:,:)=pdt(:,:)
     692dp_save(:)=zdpsrf_omp(:)
     693du_save(:,:)=zdufi_omp(:,:)
     694dv_save(:,:)=zdvfi_omp(:,:)
     695dt_save(:,:)=zdtfi_omp(:,:)
    735696dtheta_save(:,:)=pdtheta(:,:)
    736 dq_save(:,:,:)=pdq(:,:,:)
     697dq_save(:,:,:)=zdqfi_omp(:,:,:)
    737698#endif
    738699
     
    806767
    807768    ! zonal wind
    808   RUBLTEN(i,kps:kpe,j) = pdu(subs,kps:kpe)
     769  RUBLTEN(i,kps:kpe,j) = zdufi_omp(subs,kps:kpe)
    809770    ! meridional wind
    810   RVBLTEN(i,kps:kpe,j) = pdv(subs,kps:kpe)
     771  RVBLTEN(i,kps:kpe,j) = zdvfi_omp(subs,kps:kpe)
    811772    ! potential temperature
    812773    ! (dT = dtheta * exner for isobaric coordinates or if pressure variations are negligible)
     
    814775    RTHBLTEN(i,kps:kpe,j) = pdtheta(subs,kps:kpe)
    815776  ELSE
    816    RTHBLTEN(i,kps:kpe,j) = pdt(subs,kps:kpe) / exner(i,kps:kpe,j)
     777   RTHBLTEN(i,kps:kpe,j) = zdtfi_omp(subs,kps:kpe) / exner(i,kps:kpe,j)
    817778  ENDIF
    818779    ! update surface pressure (cf CO2 cycle in physics)
    819780    ! here dt is needed
    820   PSFC(i,j)=PSFC(i,j)+pdpsrf(subs)*dt
     781  PSFC(i,j)=PSFC(i,j)+zdpsrf_omp(subs)*dt
    821782    ! tracers
    822783  SCALAR(i,kps:kpe,j,1)=0.
     
    831792      SCALAR(i,1,j,2) = SCALAR(i,1,j,2) + 1. !! this tracer is emitted in the surface layer
    832793    CASE DEFAULT
    833       SCALAR(i,kps:kpe,j,2:nq+1)=SCALAR(i,kps:kpe,j,2:nq+1)+pdq(subs,kps:kpe,1:nq)*dt  !!! here dt is needed
     794      SCALAR(i,kps:kpe,j,2:nq+1)=SCALAR(i,kps:kpe,j,2:nq+1)+zdqfi_omp(subs,kps:kpe,1:nq)*dt  !!! here dt is needed
    834795  END SELECT
    835796   
    836797ENDDO
    837798ENDDO
    838 DEALLOCATE(pdpsrf)
    839 DEALLOCATE(pdu)
    840 DEALLOCATE(pdv)
    841 DEALLOCATE(pdt)
    842 DEALLOCATE(pdq)
     799CALL deallocate_interface
    843800DEALLOCATE(pdtheta)
    844801!!*****!!
Note: See TracChangeset for help on using the changeset viewer.