Ignore:
Timestamp:
Nov 28, 2014, 4:36:29 PM (10 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes -r2070:2158 into testing branch. Compilation problems introduced by revision r2155 have been corrected by hand

Location:
LMDZ5/branches/testing
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/dyn3dmem/iniacademic_loc.F90

    r2056 r2160  
    44SUBROUTINE iniacademic_loc(vcov,ucov,teta,q,masse,ps,phis,time_0)
    55
     6  USE filtreg_mod, ONLY: inifilr
    67  use exner_hyb_m, only: exner_hyb
    78  use exner_milieu_m, only: exner_milieu
    8   USE filtreg_mod
    99  USE infotrac, ONLY : nqtot
    1010  USE control_mod, ONLY: day_step,planet_type
    11   USE parallel_lmdz
     11  USE parallel_lmdz, ONLY: ijb_u, ije_u, ijb_v, ije_v
    1212#ifdef CPP_IOIPSL
    13   USE IOIPSL
     13  USE IOIPSL, ONLY: getin
    1414#else
    1515  ! if not using IOIPSL, we still need to use (a local version of) getin
    16   USE ioipsl_getincom
     16  USE ioipsl_getincom, ONLY: getin
    1717#endif
    1818  USE Write_Field
     
    4141  !   ----------
    4242
    43   real time_0
    44 
    45   !   variables dynamiques
    46   REAL vcov(ijb_v:ije_v,llm),ucov(ijb_u:ije_u,llm) ! vents covariants
    47   REAL teta(ijb_u:ije_u,llm)                 ! temperature potentielle
    48   REAL q(ijb_u:ije_u,llm,nqtot)               ! champs advectes
    49   REAL ps(ijb_u:ije_u)                       ! pression  au sol
    50   REAL masse(ijb_u:ije_u,llm)                ! masse d'air
    51   REAL phis(ijb_u:ije_u)                     ! geopotentiel au sol
     43  REAL,INTENT(OUT) :: time_0
     44
     45  !   fields
     46  REAL,INTENT(OUT) :: vcov(ijb_v:ije_v,llm) ! meridional covariant wind
     47  REAL,INTENT(OUT) :: ucov(ijb_u:ije_u,llm) ! zonal covariant wind
     48  REAL,INTENT(OUT) :: teta(ijb_u:ije_u,llm) ! potential temperature (K)
     49  REAL,INTENT(OUT) :: q(ijb_u:ije_u,llm,nqtot) ! advected tracers (.../kg_of_air)
     50  REAL,INTENT(OUT) :: ps(ijb_u:ije_u) ! surface pressure (Pa)
     51  REAL,INTENT(OUT) :: masse(ijb_u:ije_u,llm) ! air mass in grid cell (kg)
     52  REAL,INTENT(OUT) :: phis(ijb_u:ije_u) ! surface geopotential
    5253
    5354  !   Local:
     
    8081  character(len=80) :: abort_message
    8182
     83  ! Sanity check: verify that options selected by user are not incompatible
     84  if ((iflag_phys==1).and. .not. read_start) then
     85    write(lunout,*) trim(modname)," error: if read_start is set to ", &
     86    " false then iflag_phys should not be 1"
     87    write(lunout,*) "You most likely want an aquaplanet initialisation", &
     88    " (iflag_phys >= 100)"
     89    call abort_gcm(modname,"incompatible iflag_phys==1 and read_start==.false.",1)
     90  endif
     91 
    8292  !-----------------------------------------------------------------------
    8393  ! 1. Initializations for Earth-like case
Note: See TracChangeset for help on using the changeset viewer.