Changeset 3579


Ignore:
Timestamp:
Oct 9, 2019, 3:11:07 PM (5 years ago)
Author:
Laurent Fairhead
Message:

Make aquaplanets run again (on jean-zay)
EM & MP

Location:
LMDZ6/trunk/libf
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3d/gcm.F90

    r3435 r3579  
    241241       'GCM: AVANT iniacademic AVANT AVANT AVANT AVANT'
    242242  if (.not.read_start) then
     243     start_time=0.
    243244     annee_ref=anneeref
    244245     CALL iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
  • LMDZ6/trunk/libf/dyn3dmem/conf_gcm.F90

    r2665 r3579  
    2525  USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy, &
    2626                       alphax,alphay,taux,tauy
    27   USE temps_mod, ONLY: calend
     27  USE temps_mod, ONLY: calend, year_len
    2828
    2929  IMPLICIT NONE
     
    144144  !Config         
    145145  calend = 'earth_360d'
     146! initialize year_len for aquaplanets and 1D
    146147  CALL getin('calend', calend)
     148     if (calend == 'earth_360d') then
     149        year_len=360
     150      else if (calend == 'earth_365d') then
     151        year_len=365
     152      else if (calend == 'earth_366d') then
     153        year_len=366
     154      else
     155        year_len=1
     156      endif
     157 
    147158
    148159  !Config  Key  = dayref
  • LMDZ6/trunk/libf/dyn3dmem/gcm.F90

    r3435 r3579  
    233233       'GCM: AVANT iniacademic AVANT AVANT AVANT AVANT'
    234234  if (.not.read_start) then
     235     start_time=0.
    235236     annee_ref=anneeref
    236237     CALL iniacademic_loc(vcov,ucov,teta,q,masse,ps,phis,time_0)
  • LMDZ6/trunk/libf/dyn3dmem/temps_mod.F90

    r2601 r3579  
    1313  INTEGER   annee_ref
    1414  INTEGER   day_ref
     15  INTEGER   year_len
    1516  REAL      dt ! (dynamics) time step (changes if doing Matsuno or LF step)
    1617  REAL      jD_ref ! reference julian day date (beginning of experiment)
  • LMDZ6/trunk/libf/dynphy_lonlat/phylmd/iniphysiq_mod.F90

    r3435 r3579  
    3131  USE inifis_mod, ONLY: inifis
    3232  USE time_phylmdz_mod, ONLY: init_time
    33   USE temps_mod, ONLY: annee_ref, day_ini, day_ref, start_time, calend
     33  USE temps_mod, ONLY: annee_ref, day_ini, day_ref, start_time, calend, year_len
    3434  USE infotrac_phy, ONLY: init_infotrac_phy
    3535  USE phystokenc_mod, ONLY: init_phystokenc
     
    173173  ! Additional initializations for aquaplanets
    174174  IF (iflag_phys>=100) THEN
    175     CALL iniaqua(klon_omp,iflag_phys)
     175    CALL iniaqua(klon_omp,year_len,iflag_phys)
    176176  END IF
    177177
  • LMDZ6/trunk/libf/phylmd/phyaqua_mod.F90

    r3540 r3579  
    88CONTAINS
    99
    10   SUBROUTINE iniaqua(nlon, iflag_phys)
     10  SUBROUTINE iniaqua(nlon,year_len,iflag_phys)
    1111
    1212    ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    3737    USE mod_grid_phy_lmdz
    3838    USE ioipsl_getin_p_mod, ONLY : getin_p
    39     USE phys_cal_mod , ONLY: year_len
     39    USE phys_cal_mod , ONLY: calend, year_len_phy => year_len
    4040    IMPLICIT NONE
    4141
     
    4444    include "dimsoil.h"
    4545
    46     INTEGER, INTENT (IN) :: nlon, iflag_phys
     46    INTEGER, INTENT (IN) :: nlon, year_len, iflag_phys
    4747    ! IM ajout latfi, lonfi
    4848!    REAL, INTENT (IN) :: lonfi(nlon), latfi(nlon)
     
    129129    ! -------------------------------
    130130
    131 
     131    !IF (calend .EQ. "earth_360d") Then
     132      year_len_phy = year_len
     133    !END IF
     134   
    132135    if (year_len.ne.360) then
     136      write (*,*) year_len
    133137      write (*,*) 'iniaqua: 360 day calendar is required !'
    134138      stop
     
    351355    alp_bl =0.
    352356    treedrg(:,:,:)=0.
     357
     358    u10m = 0.
     359    v10m = 0.
     360
     361    ql_ancien   = 0.
     362    qs_ancien   = 0.
     363    u_ancien    = 0.
     364    v_ancien    = 0.
     365    prw_ancien  = 0.
     366    prlw_ancien = 0.
     367    prsw_ancien = 0. 
     368
     369    ale_wake    = 0.
     370    ale_bl_stat = 0. 
     371
    353372
    354373!ym error : the sub surface dimension is the third not second : forgotten for iniaqua
Note: See TracChangeset for help on using the changeset viewer.