Ignore:
Timestamp:
Jul 9, 2014, 4:43:31 PM (10 years ago)
Author:
Ehouarn Millour
Message:
  • Minor fix in dyn3dpar/leapfrog_p.F , should call geopot_p and not geopot
  • Added a sanity check in iniacademic
  • Added flag "resetvarc" to trigger a reset of initial values in sortvarc
  • Removed "sortvarc0" since the job can now be done with "resetvarc" and having set flag resertvarc to true.

EM

Location:
LMDZ5/trunk/libf/dyn3dpar
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3dpar/conf_gcm.F

    r1984 r2083  
    176176      raz_date = 0
    177177      CALL getin('raz_date', raz_date)
     178
     179!Config  Key  = resetvarc
     180!Config  Desc = Reinit des variables de controle
     181!Config  Def  = n
     182!Config  Help = Reinit des variables de controle
     183      resetvarc = .false.
     184      CALL getin('resetvarc',resetvarc)
    178185
    179186!Config  Key  = nday
  • LMDZ5/trunk/libf/dyn3dpar/iniacademic.F90

    r2021 r2083  
    44SUBROUTINE iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
    55
    6   use exner_hyb_m, only: exner_hyb
    7   use exner_milieu_m, only: exner_milieu
    8   USE filtreg_mod
     6  USE filtreg_mod, ONLY: inifilr
    97  USE infotrac, ONLY : nqtot
    108  USE control_mod, ONLY: day_step,planet_type
    119#ifdef CPP_IOIPSL
    12   USE IOIPSL
     10  USE IOIPSL, ONLY: getin
    1311#else
    1412  ! if not using IOIPSL, we still need to use (a local version of) getin
    15   USE ioipsl_getincom
     13  USE ioipsl_getincom, ONLY: getin
    1614#endif
    1715  USE Write_Field
     16  use exner_hyb_m, only: exner_hyb
     17  use exner_milieu_m, only: exner_milieu
    1818
    1919  !   Author:    Frederic Hourdin      original: 15/01/93
     
    4040  !   ----------
    4141
    42   real time_0
    43 
    44   !   variables dynamiques
    45   REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
    46   REAL teta(ip1jmp1,llm)                 ! temperature potentielle
    47   REAL q(ip1jmp1,llm,nqtot)               ! champs advectes
    48   REAL ps(ip1jmp1)                       ! pression  au sol
    49   REAL masse(ip1jmp1,llm)                ! masse d'air
    50   REAL phis(ip1jmp1)                     ! geopotentiel au sol
     42  REAL,INTENT(OUT) :: time_0
     43
     44  !   fields
     45  REAL,INTENT(OUT) :: vcov(ip1jm,llm) ! meridional covariant wind
     46  REAL,INTENT(OUT) :: ucov(ip1jmp1,llm) ! zonal covariant wind
     47  REAL,INTENT(OUT) :: teta(ip1jmp1,llm) ! potential temperature (K)
     48  REAL,INTENT(OUT) :: q(ip1jmp1,llm,nqtot) ! advected tracers (.../kg_of_air)
     49  REAL,INTENT(OUT) :: ps(ip1jmp1) ! surface pressure (Pa)
     50  REAL,INTENT(OUT) :: masse(ip1jmp1,llm) ! air mass in grid cell (kg)
     51  REAL,INTENT(OUT) :: phis(ip1jmp1) ! surface geopotential
    5152
    5253  !   Local:
     
    7677  character(len=80) :: abort_message
    7778
     79
     80  ! Sanity check: verify that options selected by user are not incompatible
     81  if ((iflag_phys==1).and.(read_start==.false.)) then
     82    write(lunout,*) trim(modname)," error: if read_start is set to ", &
     83    " false then iflag_phys should not be 1"
     84    write(lunout,*) "You most likely want an aquaplanet initialisation", &
     85    " (iflag_phys >= 100)"
     86    call abort_gcm(modname,"incompatible iflag_phys==1 and read_start==.false.",1)
     87  endif
     88 
    7889  !-----------------------------------------------------------------------
    7990  ! 1. Initializations for Earth-like case
     
    224235        CALL pression ( ip1jmp1, ap, bp, ps, p       )
    225236        if (pressure_exner) then
    226           CALL exner_hyb( ip1jmp1, ps, p, pks, pk )
     237          CALL exner_hyb( ip1jmp1, ps, p, pks, pk)
    227238        else
    228239          call exner_milieu(ip1jmp1,ps,p,pks,pk)
  • LMDZ5/trunk/libf/dyn3dpar/leapfrog_p.F

    r2039 r2083  
    717717           CALL exner_milieu_p( ip1jmp1, ps, p, pks, pk, pkf )
    718718         endif
     719c$OMP BARRIER
    719720! Appel a geopot ajoute le 2014/05/08 pour garantir la convergence numerique
    720721! avec dyn3dmem
    721       CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
    722 c$OMP BARRIER
     722      CALL geopot_p  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
     723
    723724           jD_cur = jD_ref + day_ini - day_ref
    724725     $        + itau/day_step
Note: See TracChangeset for help on using the changeset viewer.