Changeset 2068 for trunk/MESOSCALE


Ignore:
Timestamp:
Jan 18, 2019, 12:25:29 PM (6 years ago)
Author:
mlefevre
Message:

Fixed compilation problems for generic mesoscale model

Location:
trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/dynphy_wrf_generic_lmd_new
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/dynphy_wrf_generic_lmd_new/callphysiq_mod.F

    r2011 r2068  
    88CONTAINS
    99
    10 SUBROUTINE call_physiq(planet_type,klon,llm,nqtot,tname,                  &
     10SUBROUTINE call_physiq(planet_type,klon,llm,nqtot,                  &
    1111                       debut_split,lafin_split)
    12 
     12 
    1313  USE variables_mod
    1414  USE physiq_mod, ONLY: physiq
     
    2424  LOGICAL,INTENT(IN) :: debut_split ! .true. if very first call to physics
    2525  LOGICAL,INTENT(IN) :: lafin_split ! .true. if last call to physics
    26   REAL*8,INTENT(IN) :: JD_cur ! Julian day
    27   REAL*8,INTENT(IN) :: JH_cur_split ! Julian hour (fraction of day)
    2826
    2927  ! Local variables
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/dynphy_wrf_generic_lmd_new/iniphysiq_mod.F

    r2011 r2068  
    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
     
    4343REAL,intent(in) :: punjours
    4444!DOUBLE PRECISION,intent(in) :: ptimestep
    45 REAL*8,intent(in) :: phour_ini
    4645
    4746!real,intent(in) :: prad ! radius of the planet (m)
     
    5150!real,intent(in) :: punjours ! length (in s) of a standard day [daysec]
    5251integer,intent(in) :: pdayref ! reference day of for the simulation [day_ini]
    53 real*8,intent(in) :: ptimestep !physics time step (s) [dtphys]
    5452integer,intent(in) :: iflag_phys ! type of physics to be called
    5553
     
    6765real*8 :: lat(ngrid),long(ngrid),cellarea(ngrid)
    6866REAL*8 :: pprad,ppg,ppr,ppcpp,ppunjours
     67REAL*8 :: dummy
    6968  ! the common part for all planetary physics
    7069  !------------------------------------------
     
    9291!endif
    9392
    94 
     93dummy=1.
    9594lat(:)=0.
    9695long(:)=0.
     
    103102ppr=pr
    104103ppcpp=pcpp
    105 call inifis(ngrid,nlayer,nq,pdayref,ppunjours,nday,ptimestep, &
     104call inifis(ngrid,nlayer,nq,pdayref,ppunjours,nday,dummy, &
    106105            lat,long,cellarea,pprad,ppg,ppr,ppcpp)
    107106
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/dynphy_wrf_generic_lmd_new/update_inputs_physiq_mod.F

    r2061 r2068  
    2424  INTEGER, INTENT(IN) :: JULDAY, JULYR
    2525  REAL, INTENT(IN) :: GMT,elaps,lon_input,ls_input,lct_input
    26   REAL*8,INTENT(OUT) :: pday,ptime
    2726  REAL,INTENT(OUT) :: MY
    2827  REAL :: sec,nsec
     
    7069!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    7170!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    72 SUBROUTINE update_inputs_physiq_tracers(nq,MARS_MODE,tname)
     71SUBROUTINE update_inputs_physiq_tracers(nq,MARS_MODE)
    7372
    7473  use tracer_h, only: noms,nqtot
     
    7776  INTEGER, INTENT(IN) :: nq,MARS_MODE
    7877  INTEGER :: i,k
    79   CHARACTER(len=20), INTENT(INOUT) :: tname(nq) ! tracer names
     78!  CHARACTER(len=20), INTENT(INOUT) :: tname(nq) ! tracer names
    8079  logical :: end_of_file
    8180
     
    8887  nqtot=nq
    8988  if (MARS_MODE .eq. 1) THEN
    90     tname(1)="h2o_vap"
    91     tname(2)="h2o_ice"
     89    noms(1)="h2o_vap"
     90    noms(2)="h2o_ice"
    9291  else if (MARS_MODE .eq. 22)  then
    93     tname(1)="co2_vap"
    94     tname(2)="co2_ice"
     92    noms(1)="co2_vap"
     93    noms(2)="co2_ice"
    9594  else
    96     tname(:)="zolbxs"
     95    noms(:)="zolbxs"
    9796  endif
    98   noms(:)=tname(:)
     97  !noms(:)=tname(:)
    9998  print*,'noms',noms
    10099  !!---------------------!!
Note: See TracChangeset for help on using the changeset viewer.