Changeset 3540


Ignore:
Timestamp:
Jun 25, 2019, 4:50:13 PM (5 years ago)
Author:
Laurent Fairhead
Message:

Modifications needed for "real" calendar in 1D model
MPL/EM

Location:
LMDZ6/trunk/libf
Files:
5 edited

Legend:

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

    r2665 r3540  
    2121  USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy, &
    2222                       alphax,alphay,taux,tauy
    23   USE temps_mod, ONLY: calend
     23  USE temps_mod, ONLY: calend, year_len
    2424
    2525  IMPLICIT NONE
     
    115115  calend = 'earth_360d'
    116116  CALL getin('calend', calend)
     117! initialize year_len for aquaplanets and 1D
     118      if (calend == 'earth_360d') then
     119        year_len=360
     120      else if (calend == 'earth_365d') then
     121        year_len=365
     122      else if (calend == 'earth_366d') then
     123        year_len=366
     124      else
     125        year_len=1
     126      endif
    117127
    118128  !Config  Key  = dayref
  • LMDZ6/trunk/libf/dyn3d/temps_mod.F90

    r2601 r3540  
    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/phylmd/dyn1d/1DUTILS.h

    • Property svn:keywords set to Id
    r3513 r3540  
    22
    33!
    4 ! $Id: conf_unicol.F 1279 2010-08-04 17:20:56Z lahellec $
     4! $Id$
    55!
    66!
     
    826826      ENDDO
    827827
    828       modname = 'dyn1dredem'
    829       ierr = NF_OPEN(fichnom, NF_WRITE, nid)
    830       IF (ierr .NE. NF_NOERR) THEN
    831          abort_message="Pb. d ouverture "//fichnom
    832          CALL abort_gcm('Modele 1D',abort_message,1)
    833       ENDIF
     828!     modname = 'dyn1dredem'
     829!     ierr = NF_OPEN(fichnom, NF_WRITE, nid)
     830!     IF (ierr .NE. NF_NOERR) THEN
     831!        abort_message="Pb. d ouverture "//fichnom
     832!        CALL abort_gcm('Modele 1D',abort_message,1)
     833!     ENDIF
    834834
    835835      DO l=1,length
  • LMDZ6/trunk/libf/phylmd/dyn1d/lmdz1d.F90

    r3537 r3540  
    4646                          preff, aps, bps, pseudoalt, scaleheight
    4747   USE temps_mod, ONLY: annee_ref, calend, day_end, day_ini, day_ref, &
    48                         itau_dyn, itau_phy, start_time
     48                        itau_dyn, itau_phy, start_time, year_len
     49   USE phys_cal_mod, ONLY : year_len_phys_cal_mod => year_len
    4950
    5051      implicit none
     
    240241!  Initializations of boundary conditions
    241242!---------------------------------------------------------------------
    242       integer, parameter :: yd = 360
    243       real :: phy_nat (yd) = 0.0 ! 0=ocean libre,1=land,2=glacier,3=banquise
    244       real :: phy_alb (yd)  ! Albedo land only (old value condsurf_jyg=0.3)
    245       real :: phy_sst (yd)  ! SST (will not be used; cf read_tsurf1d.F)
    246       real :: phy_bil (yd) = 1.0 ! Ne sert que pour les slab_ocean
    247       real :: phy_rug (yd) ! Longueur rugosite utilisee sur land only
    248       real :: phy_ice (yd) = 0.0 ! Fraction de glace
    249       real :: phy_fter(yd) = 0.0 ! Fraction de terre
    250       real :: phy_foce(yd) = 0.0 ! Fraction de ocean
    251       real :: phy_fsic(yd) = 0.0 ! Fraction de glace
    252       real :: phy_flic(yd) = 0.0 ! Fraction de glace
     243      real, allocatable :: phy_nat (:)  ! 0=ocean libre,1=land,2=glacier,3=banquise
     244      real, allocatable :: phy_alb (:)  ! Albedo land only (old value condsurf_jyg=0.3)
     245      real, allocatable :: phy_sst (:)  ! SST (will not be used; cf read_tsurf1d.F)
     246      real, allocatable :: phy_bil (:)  ! Ne sert que pour les slab_ocean
     247      real, allocatable :: phy_rug (:) ! Longueur rugosite utilisee sur land only
     248      real, allocatable :: phy_ice (:) ! Fraction de glace
     249      real, allocatable :: phy_fter(:) ! Fraction de terre
     250      real, allocatable :: phy_foce(:) ! Fraction de ocean
     251      real, allocatable :: phy_fsic(:) ! Fraction de glace
     252      real, allocatable :: phy_flic(:) ! Fraction de glace
    253253
    254254!---------------------------------------------------------------------
     
    471471
    472472      call conf_gcm( 99, .TRUE. )
     473     
     474!-----------------------------------------------------------------------
     475      allocate( phy_nat (year_len))  ! 0=ocean libre,1=land,2=glacier,3=banquise
     476      phy_nat(:)=0.0
     477      allocate( phy_alb (year_len))  ! Albedo land only (old value condsurf_jyg=0.3)
     478      allocate( phy_sst (year_len))  ! SST (will not be used; cf read_tsurf1d.F)
     479      allocate( phy_bil (year_len))  ! Ne sert que pour les slab_ocean
     480      phy_bil(:)=1.0
     481      allocate( phy_rug (year_len)) ! Longueur rugosite utilisee sur land only
     482      allocate( phy_ice (year_len)) ! Fraction de glace
     483      phy_ice(:)=0.0
     484      allocate( phy_fter(year_len)) ! Fraction de terre
     485      phy_fter(:)=0.0
     486      allocate( phy_foce(year_len)) ! Fraction de ocean
     487      phy_foce(:)=0.0
     488      allocate( phy_fsic(year_len)) ! Fraction de glace
     489      phy_fsic(:)=0.0
     490      allocate( phy_flic(year_len)) ! Fraction de glace
     491      phy_flic(:)=0.0
    473492!-----------------------------------------------------------------------
    474493!   Choix du calendrier
     
    486505        write(*,*)'CALENDRIER CHOISI: Terrestre bissextile'
    487506      else if (calend == 'gregorian') then
     507        stop 'gregorian calend should not be used by normal user'
    488508        call ioconf_calendar('gregorian') ! not to be used by normal users
    489509        write(*,*)'CALENDRIER CHOISI: Gregorien'
     
    738758      rlon_rad(1)=xlon*rpi/180.
    739759
     760     ! iniphysiq will call iniaqua who needs year_len from phys_cal_mod
     761     year_len_phys_cal_mod=year_len
     762           
    740763     ! Ehouarn: iniphysiq requires arrays related to (3D) dynamics grid,
    741764     ! e.g. for cell boundaries, which are meaningless in 1D; so pad these
     
    936959!        phy_fter,phy_foce,phy_flic,phy_fsic)
    937960!------------------------------------------------------------------------
    938       do i=1,yd
     961      do i=1,year_len
    939962        phy_nat(i)  = nat_surf
    940963        phy_alb(i)  = albedo
  • LMDZ6/trunk/libf/phylmd/phyaqua_mod.F90

    • Property svn:keywords set to Id
    r3531 r3540  
     1!
     2! $Id$
     3!
    14MODULE phyaqua_mod
    25  ! Routines complementaires pour la physique planetaire.
     
    3437    USE mod_grid_phy_lmdz
    3538    USE ioipsl_getin_p_mod, ONLY : getin_p
     39    USE phys_cal_mod , ONLY: year_len
    3640    IMPLICIT NONE
    3741
     
    7276    CHARACTER *2 cnbl
    7377
    74     REAL phy_nat(nlon, 360)
    75     REAL phy_alb(nlon, 360)
    76     REAL phy_sst(nlon, 360)
    77     REAL phy_bil(nlon, 360)
    78     REAL phy_rug(nlon, 360)
    79     REAL phy_ice(nlon, 360)
    80     REAL phy_fter(nlon, 360)
    81     REAL phy_foce(nlon, 360)
    82     REAL phy_fsic(nlon, 360)
    83     REAL phy_flic(nlon, 360)
     78    REAL phy_nat(nlon, year_len)
     79    REAL phy_alb(nlon, year_len)
     80    REAL phy_sst(nlon, year_len)
     81    REAL phy_bil(nlon, year_len)
     82    REAL phy_rug(nlon, year_len)
     83    REAL phy_ice(nlon, year_len)
     84    REAL phy_fter(nlon, year_len)
     85    REAL phy_foce(nlon, year_len)
     86    REAL phy_fsic(nlon, year_len)
     87    REAL phy_flic(nlon, year_len)
    8488
    8589    INTEGER, SAVE :: read_climoz = 0 ! read ozone climatology
     
    125129    ! -------------------------------
    126130
     131
     132    if (year_len.ne.360) then
     133      write (*,*) 'iniaqua: 360 day calendar is required !'
     134      stop
     135    endif
    127136
    128137    type_aqua = iflag_phys/100
     
    223232    ! endif !alb_ocean
    224233
    225     DO i = 1, 360
     234    DO i = 1, year_len
    226235      ! IM Terraplanete   phy_sst(:,i) = 260.+50.*cos(rlatd(:))**2
    227236      ! IM ajout calcul profil sst selon le cas considere (cf. FBr)
     
    544553    USE mod_grid_phy_lmdz, ONLY: klon_glo
    545554    USE mod_phys_lmdz_transfert_para, ONLY: gather
     555    USE phys_cal_mod, ONLY: year_len
    546556    IMPLICIT NONE
    547557    include "netcdf.inc"
    548558
    549559    INTEGER, INTENT (IN) :: klon
    550     REAL, INTENT (IN) :: phy_nat(klon, 360)
    551     REAL, INTENT (IN) :: phy_alb(klon, 360)
    552     REAL, INTENT (IN) :: phy_sst(klon, 360)
    553     REAL, INTENT (IN) :: phy_bil(klon, 360)
    554     REAL, INTENT (IN) :: phy_rug(klon, 360)
    555     REAL, INTENT (IN) :: phy_ice(klon, 360)
    556     REAL, INTENT (IN) :: phy_fter(klon, 360)
    557     REAL, INTENT (IN) :: phy_foce(klon, 360)
    558     REAL, INTENT (IN) :: phy_flic(klon, 360)
    559     REAL, INTENT (IN) :: phy_fsic(klon, 360)
    560 
    561     REAL :: phy_glo(klon_glo, 360) ! temporary variable, to store phy_***(:)
     560    REAL, INTENT (IN) :: phy_nat(klon, year_len)
     561    REAL, INTENT (IN) :: phy_alb(klon, year_len)
     562    REAL, INTENT (IN) :: phy_sst(klon, year_len)
     563    REAL, INTENT (IN) :: phy_bil(klon, year_len)
     564    REAL, INTENT (IN) :: phy_rug(klon, year_len)
     565    REAL, INTENT (IN) :: phy_ice(klon, year_len)
     566    REAL, INTENT (IN) :: phy_fter(klon, year_len)
     567    REAL, INTENT (IN) :: phy_foce(klon, year_len)
     568    REAL, INTENT (IN) :: phy_flic(klon, year_len)
     569    REAL, INTENT (IN) :: phy_fsic(klon, year_len)
     570
     571    REAL :: phy_glo(klon_glo, year_len) ! temporary variable, to store phy_***(:)
    562572      ! on the whole physics grid
    563573    INTEGER :: k
     
    665675
    666676      ! write the 'times'
    667       DO k = 1, 360
     677      DO k = 1, year_len
    668678#ifdef NC_DOUBLE
    669679        ierr = nf_put_var1_double(nid, id_tim, k, dble(k))
     
    809819  SUBROUTINE profil_sst(nlon, rlatd, type_profil, phy_sst)
    810820    USE dimphy
     821    USE phys_cal_mod , ONLY: year_len
    811822    IMPLICIT NONE
    812823
    813824    INTEGER nlon, type_profil, i, k, j
    814     REAL :: rlatd(nlon), phy_sst(nlon, 360)
     825    REAL :: rlatd(nlon), phy_sst(nlon, year_len)
    815826    INTEGER imn, imx, amn, amx, kmn, kmx
    816827    INTEGER p, pplus, nlat_max
     
    825836    ENDIF
    826837    WRITE (*, *) ' profil_sst: type_profil=', type_profil
    827     DO i = 1, 360
     838    DO i = 1, year_len
    828839      ! phy_sst(:,i) = 260.+50.*cos(rlatd(:))**2
    829840
     
    10181029    imx = 1
    10191030    kmx = 1
    1020     DO k = 1, 360
     1031    DO k = 1, year_len
    10211032      DO i = 2, nlon
    10221033        IF (phy_sst(i,k)<amn) THEN
Note: See TracChangeset for help on using the changeset viewer.