Ignore:
Timestamp:
Aug 23, 2016, 10:42:41 AM (8 years ago)
Author:
aslmd
Message:

Goal: make the mesoscale model compliant
with new interface philosophy and adapted
to easy interfacing with any physics

Commit 4: call to call_physiq in module_lmd_driver
(callphysiq_mod is in WRFV2/phys)

module_lmd_driver.F.new is now supposedly independent
of the considered planet

to build an interface with new planetary physics
consider adapting

  • update_inputs_physiq_mod.F
  • update_outputs_physiq_mod.F
  • iniphysiq_mod.F
  • callphysiq_mod.F

for the last two, see examples for a given planet
in LMDZ._yourplanet_/libf/dynphy_lonlat/phy_yourplanet_

NB: checked compatibility of results with previous commit

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/module_lmd_driver.F.new

    r1579 r1580  
    1313!           - unified module_lmd_driver: old, new phys and LES - February 2011
    1414!           - a new paradigm to prepare nested simulations - April 2014
     15!           - adapted to new interface philosophy & other planets - August 2016
    1516!*******************************************************************************
    1617MODULE module_lmd_driver
     
    6364   USE comm_wrf !! to get fields to be written from physiq
    6465   USE iniphysiq_mod !! to get iniphysiq subroutine
    65    USE physiq_mod, only : physiq
     66   USE callphysiq_mod !! to call the LMD physics
    6667#endif
    6768
     
    132133   
    133134
    134    ! *** for Mars Mode 20 ***
     135   ! *** for tracer Mode 20 ***
    135136   REAL ::    tau_decay
    136137   ! *** ----------------------- ***
     
    143144   LOGICAL :: firstcall,lastcall
    144145   ! ----------
    145    REAL,DIMENSION(:,:),ALLOCATABLE :: pplev,pplay,pphi,pu,pv,pt,pw
     146   REAL,DIMENSION(:,:),ALLOCATABLE :: pplev,pplay,pphi,pu,pv,pt,flxw
    146147   REAL,DIMENSION(:,:,:),ALLOCATABLE :: pq 
    147148
     
    191192!!!IDEALIZED IDEALIZED
    192193
    193 
    194 !REAL, DIMENSION(:,:,:), ALLOCATABLE, SAVE :: &
    195 !     UMAX, UMIN, VMAX, VMIN, WMAX, WMIN, TMAX, TMIN
    196 
    197 
     194   !! arguments to physiq
     195   CHARACTER(len=20),ALLOCATABLE :: tname(:) ! tracer names
     196   REAL,ALLOCATABLE :: zpk_omp(:,:)
     197   REAL,ALLOCATABLE :: zphis_omp(:) ! surface geopotential
     198   REAL,ALLOCATABLE :: presnivs_omp(:) ! approximate pressure of atm. layers 
     199   REAL,ALLOCATABLE :: zrfi_omp(:,:) ! relative wind vorticity, in s-1
     200
     201   !! this is temporary and supposed to be set by namelist
     202   character(len=10),save :: planet_type ! planet type ('earth','mars',...)
     203   planet_type = "mars"
    198204
    199205!==================================================================
     
    225231
    226232
    227 print *,'** Mars ** DOMAIN',id
     233print *,'** ',planet_type,' ** DOMAIN',id
    228234
    229235!-------------------------!
     
    356362!!!***********!!
    357363IF (JULYR .eq. 9999) THEN
    358   PRINT *,'** Mars ** IDEALIZED SIMULATION'
    359   PRINT *,'** Mars ** BEWARE: input_coord must be here'
     364  PRINT *,'** ',planet_type,'** IDEALIZED SIMULATION'
     365  PRINT *,'** ',planet_type,'** BEWARE: input_coord must be here'
    360366  open(unit=14,file='input_coord',form='formatted',status='old')
    361367  rewind(14)
     
    370376! ALLOCATE !
    371377!----------!
     378IF (.not.ALLOCATED(tname)) ALLOCATE(tname(nq))
    372379!-------------------------------------------------------------------------------!
    373380! outputs:                                                                      !       
     
    387394!!!
    388395IF (test.NE.0) THEN
    389 print *,'** Mars ** NO CALL FOR PHYSICS, go to next step...',test
     396print *,'** ',planet_type,'** NO CALL FOR PHYSICS, go to next step...',test
    390397#ifdef SPECIAL_NEST_SAVE
    391398pdpsrf(:)=dp_save(:,id)
     
    418425ALLOCATE(pv(ngrid,nlayer))       !!!!!
    419426ALLOCATE(pt(ngrid,nlayer))       !!!!!
    420 ALLOCATE(pw(ngrid,nlayer))       !!!!!
     427ALLOCATE(flxw(ngrid,nlayer))       !!!!!
    421428ALLOCATE(pq(ngrid,nlayer,nq))    !!!!!
     429ALLOCATE(zpk_omp(ngrid,nlayer))
     430ALLOCATE(zphis_omp(ngrid))
     431ALLOCATE(presnivs_omp(nlayer))
     432ALLOCATE(zrfi_omp(ngrid,nlayer))
    422433! interm
    423434ALLOCATE(dz8w_prof(nlayer))
     
    442453allocation_firstcall: IF (firstcall .EQV. .true.) THEN
    443454  !! tracers' name
    444   PRINT *,'** Mars ** TRACERS NAMES'
    445   CALL update_inputs_physiq_tracers(nq,MARS_MODE)
     455  PRINT *,'** ',planet_type,'** TRACERS NAMES'
     456  CALL update_inputs_physiq_tracers(nq,MARS_MODE,tname)
    446457  !! PHYSICS VARIABLES (cf. iniphysiq in LMD GCM)
    447458  !! parameters are defined in the module_model_constants.F WRF routine
    448   PRINT *,'** Mars ** INITIALIZE ARRAYS FOR PHYSICS'
     459  PRINT *,'** ',planet_type,'** INITIALIZE ARRAYS FOR PHYSICS'
    449460  !! need to get initial time first
    450461  CALL update_inputs_physiq_time(&
     
    538549pu(subs,:) = u_prof(:)
    539550pv(subs,:) = v_prof(:)
    540 pw(subs,:) = 0   !! NB: not used in the physics, only diagnostic...
     551flxw(subs,:) = 0   !! NB: not used in the physics, only diagnostic...
    541552!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    542553!! for IDEALIZED CASES ONLY
     
    584595!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    585596pass_interface: IF ( (firstcall .EQV. .true.) .or. (max_dom .GT. 1) ) THEN
    586 PRINT *,'** Mars ** PASS INTERFACE. EITHER FIRSTCALL or NESTED SIMULATION.'
     597PRINT *,'** ',planet_type,'** PASS INTERFACE. EITHER FIRSTCALL or NESTED SIMULATION.'
    587598!!*******************************************!!
    588599!!*******************************************!!
     
    649660pdq(:,:,:)=0.
    650661#ifndef NOPHYS
    651 print *, '** Mars ** CALL TO LMD PHYSICS'
     662print *, '** ',planet_type,'** CALL TO LMD PHYSICS'
    652663!!!
    653664CALL update_inputs_physiq_time(&
     
    657668            ptime,pday,MY)
    658669!!!
    659 CALL physiq (ngrid,nlayer,nq,                         &
    660              firstcall,lastcall,pday,ptime,ptimestep, &
    661              pplev,pplay,pphi,pu,pv,pt,pq,pw,         &
    662              pdu,pdv,pdt,pdq,pdpsrf)
     670CALL call_physiq(planet_type,ngrid,nlayer,nq,tname, &
     671                       firstcall,lastcall,          &
     672                       pday,ptime,ptimestep,        &
     673                       pplev,pplay,                 &
     674                       zpk_omp,pphi,zphis_omp,      &
     675                       presnivs_omp,                &
     676                       pu,pv,zrfi_omp,pt,pq,        &
     677                       flxw,                        &
     678                       pdu,pdv,pdt,pdq,pdpsrf)
     679!!!
    663680#endif
    664681
     
    670687#endif
    671688
    672 print *, '** Mars ** CALL TO LMD PHYSICS DONE'
     689print *, '** ',planet_type,'** CALL TO LMD PHYSICS DONE'
    673690DEALLOCATE(pplev)
    674691DEALLOCATE(pplay)
     
    677694DEALLOCATE(pv)
    678695DEALLOCATE(pt)
    679 DEALLOCATE(pw)
     696DEALLOCATE(flxw)
    680697DEALLOCATE(pq)
     698DEALLOCATE(zpk_omp)
     699DEALLOCATE(zphis_omp)
     700DEALLOCATE(presnivs_omp)
     701DEALLOCATE(zrfi_omp)
     702
    681703
    682704!---------------------------------------------------------------------------------!
     
    796818      SCALAR(i,kps:kpe,j,:)=0.
    797819    CASE(20)
    798       !! Mars mode 20 : add a passive tracer with radioactive-like decay
     820      !! tracer mode 20 : add a passive tracer with radioactive-like decay
    799821      IF ( (i == ips) .AND. (j == jps) )   print *, 'RADIOACTIVE-LIKE TRACER WITH SOURCE AT SURFACE LAYER.'
    800822      tau_decay=60.*10. !! why not make it a namelist argument?
     
    817839!! END !!
    818840!!*****!!
    819 print *,'** Mars ** END LMD PHYSICS'
     841print *,'** ',planet_type,'** END LMD PHYSICS'
    820842!----------------------------------------------------------------!
    821843! use debug (see solve_em) if you wanna display some message ... !
Note: See TracChangeset for help on using the changeset viewer.