Ignore:
Timestamp:
Jan 25, 2017, 4:02:54 PM (8 years ago)
Author:
emillour
Message:

Dynamical core: Further adaptations to stick with LMDZ5 (up to rev r2750)

  • libf
  • makelmdz[_fcm] : added Earth-specific "dust" and "strataer" cases and

-arch_path option

  • bld.cfg : added dust and strataer cases
  • dyn3d[par]
  • conf_gcm.F90 : added read_orop parameter (Earth-related) for

loading subgrid orography parameters.

  • guide[_p]_mod.F90: added output of nudging coefficients for winds

and temperature

  • temps_mod.F90 : cosmetics/comments
  • logic_mod.F90 : cosmetics/comments
  • dyn3d_common
  • comconst_mod.F90 : cosmetics/comments + added year_day module variable
  • conf_planete.F90 : added year_day from comconst_mod as done in LMDZ5
  • comvert_mod.F90 : cosmetics/comments
  • infotrac.F90 : added "startAer" case to follow up with LMDZ5
  • misc
  • wxios.F90 : follow up on changes in LMDZ5

EM

Location:
trunk/LMDZ.COMMON/libf/dyn3d
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dyn3d/conf_gcm.F90

    r1593 r1650  
    2525  USE logic_mod, ONLY: tidal,purmats,ok_guide,read_start,iflag_phys,            &
    2626                iflag_trac,ok_strato,ok_gradsfile,ok_limit,ok_etat0,            &
    27                 moyzon_mu,moyzon_ch,ok_strato,fxyhypb,ysinus
     27                moyzon_mu,moyzon_ch,ok_strato,fxyhypb,ysinus,read_orop
    2828  USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy,             &
    2929                alphax,alphay,taux,tauy
     
    5353!   ------
    5454
    55   CHARACTER ch1*72,ch2*72,ch3*72,ch4*12
    5655  REAL clonn,clatt,grossismxx,grossismyy
    5756  REAL dzoomxx,dzoomyy, tauxx,tauyy
    5857  LOGICAL  fxyhypbb, ysinuss
    59   INTEGER i
    6058  LOGICAL use_filtre_fft
    6159!
     
    549547  IF (use_filtre_fft) THEN
    550548    write(lunout,*)'STOP !!!'
    551     write(lunout,*)'use_filtre_fft n est pas implemente dans dyn3d'
     549    write(lunout,*)'use_filtre_fft not implemented in dyn3d'
    552550    STOP 1
    553551  ENDIF
     
    597595  ok_etat0 = .TRUE.
    598596  CALL getin('ok_etat0',ok_etat0)
     597
     598!Config  Key  = read_orop
     599!Config  Desc = lecture du fichier de params orographiques sous maille
     600!Config  Def  = f
     601!Config  Help = lecture fichier plutot que grid_noro
     602
     603  read_orop = .FALSE.
     604  CALL getin('read_orop',read_orop)
    599605
    600606!----------------------------------------
     
    954960 write(lunout,*)' ok_limit = ', ok_limit
    955961 write(lunout,*)' ok_etat0 = ', ok_etat0
     962 write(lunout,*)' read_orop = ', read_orop
    956963 if (planet_type=="titan") then
    957964   write(lunout,*)' moyzon_mu = ', moyzon_mu
  • trunk/LMDZ.COMMON/libf/dyn3d/guide_mod.F90

    r1508 r1650  
    1313  use netcdf, only: nf90_nowrite, nf90_open, nf90_inq_varid, nf90_close
    1414  use pres2lev_mod
    15   USE serre_mod, ONLY: grossismx
    1615
    1716  IMPLICIT NONE
     
    3938
    4039  REAL, ALLOCATABLE, DIMENSION(:), PRIVATE, SAVE     :: alpha_u,alpha_v
    41   REAL, ALLOCATABLE, DIMENSION(:), PRIVATE, SAVE     :: alpha_T,alpha_Q
     40  REAL, ALLOCATABLE, DIMENSION(:, :), PRIVATE, SAVE     :: alpha_T,alpha_Q
    4241  REAL, ALLOCATABLE, DIMENSION(:), PRIVATE, SAVE     :: alpha_P,alpha_pcor
    4342 
     
    6463  SUBROUTINE guide_init
    6564
    66     USE control_mod
     65    USE control_mod, ONLY: day_step
     66    USE serre_mod, ONLY: grossismx
    6767
    6868    IMPLICIT NONE
     
    108108    CALL getpar('gamma4',.false.,gamma4,'Zone sans rappel elargie')
    109109    CALL getpar('guide_BL',.true.,guide_BL,'guidage dans C.Lim')
    110    
     110
    111111! Sauvegarde du for�age
    112112    CALL getpar('guide_sav',.false.,guide_sav,'sauvegarde guidage')
     
    147147
    148148    call fin_getparam
    149 
     149   
    150150! ---------------------------------------------
    151151! Determination du nombre de niveaux verticaux
     
    222222    ALLOCATE(alpha_v(ip1jm), stat = error)
    223223    IF (error /= 0) CALL abort_gcm(modname,abort_message,1)
    224     ALLOCATE(alpha_T(ip1jmp1), stat = error)
     224    ALLOCATE(alpha_T(iip1, jjp1), stat = error)
    225225    IF (error /= 0) CALL abort_gcm(modname,abort_message,1)
    226     ALLOCATE(alpha_Q(ip1jmp1), stat = error)
     226    ALLOCATE(alpha_Q(iip1, jjp1), stat = error)
    227227    IF (error /= 0) CALL abort_gcm(modname,abort_message,1)
    228228    ALLOCATE(alpha_P(ip1jmp1), stat = error)
     
    312312  SUBROUTINE guide_main(itau,ucov,vcov,teta,q,masse,ps)
    313313
    314     USE control_mod
    315     USE comvert_mod, ONLY: ap,bp,preff,presnivs
    316     USE comconst_mod, ONLY: daysec,dtvr
     314    USE control_mod, ONLY: day_step, iperiod
     315    USE comconst_mod, ONLY: dtvr, daysec
     316    USE comvert_mod, ONLY: ap, bp, preff, presnivs
    317317 
    318318    IMPLICIT NONE
     
    541541
    542542    USE comconst_mod, ONLY: pi
    543 
     543   
    544544    IMPLICIT NONE
    545545
     
    606606  use exner_hyb_m, only: exner_hyb
    607607  use exner_milieu_m, only: exner_milieu
    608   USE comvert_mod, ONLY: ap,bp,preff,pressure_exner
    609   USE comconst_mod, ONLY: cpp,kappa
    610 
     608  use comconst_mod, only: kappa, cpp
     609  use comvert_mod, only: preff, pressure_exner, bp, ap
    611610  IMPLICIT NONE
    612611
     
    777776            do j=1,jjp1
    778777                IF (guide_teta) THEN
    779                     do i=1,iim
    780                         ij=(j-1)*iip1+i
    781                         tgui1(ij,l)=zu1(i,j,l)
    782                         tgui2(ij,l)=zu2(i,j,l)
    783                     enddo
     778                    do i=1,iim
     779                        ij=(j-1)*iip1+i
     780                        tgui1(ij,l)=zu1(i,j,l)
     781                        tgui2(ij,l)=zu2(i,j,l)
     782                    enddo
    784783                ELSE
    785                     do i=1,iim
    786                         ij=(j-1)*iip1+i
    787                         tgui1(ij,l)=zu1(i,j,l)*cpp/pk(i,j,l)
    788                         tgui2(ij,l)=zu2(i,j,l)*cpp/pk(i,j,l)
    789                     enddo
     784                    do i=1,iim
     785                        ij=(j-1)*iip1+i
     786                        tgui1(ij,l)=zu1(i,j,l)*cpp/pk(i,j,l)
     787                        tgui2(ij,l)=zu2(i,j,l)*cpp/pk(i,j,l)
     788                    enddo
    790789                ENDIF
    791790                tgui1(j*iip1,l)=tgui1((j-1)*iip1+1,l)   
     
    855854! Calcul des constantes de rappel alpha (=1/tau)
    856855
    857     USE comconst_mod, ONLY: pi
    858     USE serre_mod, ONLY: clon,clat,grossismy
    859 
     856    use comconst_mod, only: pi
     857    use serre_mod, only: clon, clat, grossismx, grossismy
     858   
    860859    implicit none
    861860
     
    15171516  SUBROUTINE guide_out(varname,hsize,vsize,field)
    15181517
     1518    USE comconst_mod, ONLY: pi
    15191519    USE comvert_mod, ONLY: presnivs
    1520     USE comconst_mod, ONLY: pi
    1521 
     1520    use netcdf95, only: nf95_def_var, nf95_put_var
     1521    use netcdf, only: nf90_float
     1522   
    15221523    IMPLICIT NONE
    15231524
     
    15371538    INTEGER       :: nid, id_lonu, id_lonv, id_latu, id_latv, id_tim, id_lev
    15381539    INTEGER       :: vid_lonu,vid_lonv,vid_latu,vid_latv,vid_cu,vid_cv,vid_lev
    1539     INTEGER       :: vid_au,vid_av
     1540    INTEGER       :: vid_au,vid_av, varid_alpha_t, varid_alpha_q
    15401541    INTEGER, DIMENSION (3) :: dim3
    15411542    INTEGER, DIMENSION (4) :: dim4,count,start
     
    15681569        ierr=NF_DEF_VAR(nid,"cv",NF_FLOAT,2,(/id_lonv,id_latv/),vid_cv)
    15691570        ierr=NF_DEF_VAR(nid,"av",NF_FLOAT,2,(/id_lonv,id_latv/),vid_av)
     1571        call nf95_def_var(nid, "alpha_T", nf90_float, (/id_lonv, id_latu/), &
     1572             varid_alpha_t)
     1573        call nf95_def_var(nid, "alpha_q", nf90_float, (/id_lonv, id_latu/), &
     1574             varid_alpha_q)
    15701575       
    15711576        ierr=NF_ENDDEF(nid)
     
    15931598        ierr = NF_PUT_VAR_REAL(nid,vid_av,alpha_v)
    15941599#endif
     1600        call nf95_put_var(nid, varid_alpha_t, alpha_t)
     1601        call nf95_put_var(nid, varid_alpha_q, alpha_q)
    15951602! --------------------------------------------------------------------
    15961603! Cr�ation des variables sauvegard�es
  • trunk/LMDZ.COMMON/libf/dyn3d/logic_mod.F90

    r1593 r1650  
    33IMPLICIT NONE 
    44
    5       LOGICAL purmats,forward,leapf,apphys,statcl,conser,               &
    6      & apdiss,apdelq,saison,ecripar,fxyhypb,ysinus                      &
    7      &  ,read_start,ok_guide,ok_strato,tidal,ok_gradsfile               &
    8      &  ,ok_limit,ok_etat0
    9       logical hybrid ! vertical coordinate is hybrid if true (sigma otherwise)
    10                      ! (only used if disvert_type==2)
    11       logical moyzon_mu,moyzon_ch ! used for zonal averages in Titan
     5  LOGICAL purmats ! true if time stepping is purely Matsuno scheme
     6                  ! false implies Matsuno-Leapfrog time stepping scheme
     7  LOGICAL forward ! true if during forward phase of Matsuno step
     8  LOGICAL leapf ! true if during a leapfrog time stepping step
     9  LOGICAL apphys ! true if during a time step when physics will be called
     10  LOGICAL statcl
     11  LOGICAL conser
     12  LOGICAL apdiss ! true if during a time step when dissipation will be called
     13  LOGICAL apdelq
     14  LOGICAL saison
     15  LOGICAL ecripar
     16  LOGICAL fxyhypb ! true if using hyperbolic function discretization
     17                  ! for latitudinal grid
     18  LOGICAL ysinus ! true if using sine function discretiation
     19                 ! for latitudinal grid
     20  LOGICAL read_start ! true if reading a start.nc file to initialize fields
     21  LOGICAL ok_guide ! true if nudging
     22  LOGICAL ok_strato
     23  LOGICAL tidal  ! true if adding tidal forces (for Titan)
     24  LOGICAL ok_gradsfile
     25  LOGICAL ok_limit  ! true for boundary conditions file creation (limit.nc)
     26  LOGICAL ok_etat0  ! true for initial states creation (start.nc, startphy.nc)
     27  LOGICAL read_orop ! true for sub-cell scales orographic params read in file
     28  LOGICAL hybrid ! vertical coordinate is hybrid if true (sigma otherwise)
     29                 ! (only used if disvert_type==2)
     30  LOGICAL moyzon_mu,moyzon_ch ! used for zonal averages in Titan
    1231
    13       integer iflag_phys,iflag_trac
     32  INTEGER iflag_phys ! type of physics to call: 0 none, 1: phy*** package,
     33                     ! 2: Held & Suarez, 101-200: aquaplanets & terraplanets
     34  INTEGER iflag_trac
    1435
    1536END MODULE logic_mod
  • trunk/LMDZ.COMMON/libf/dyn3d/temps_mod.F90

    r1422 r1650  
    33IMPLICIT NONE 
    44
    5 ! jD_ref = jour julien de la date de reference (lancement de l'experience)
    6 ! hD_ref = "heure" julienne de la date de reference
    7 
    85      INTEGER   itaufin ! total number of dynamical steps for the run
    9       INTEGER   itau_dyn, itau_phy
     6      INTEGER   itau_dyn
     7      INTEGER   itau_phy
    108      INTEGER   day_ini ! initial day # of simulation sequence
    119      INTEGER   day_end ! final day # ; i.e. day # when this simulation ends
     
    1311      INTEGER   day_ref
    1412      REAL      dt ! (dynamics) time step (changes if doing Matsuno or LF step)
    15       REAL      jD_ref, jH_ref, start_time
    16       CHARACTER (len=10) :: calend
     13      REAL      jD_ref ! reference julian day date (beginning of experiment)
     14      REAL      jH_ref ! reference julian "hour" of reference julian date
     15      REAL      start_time
     16      CHARACTER (len=10) :: calend ! calendar type
    1717
    1818      ! Additionnal Mars stuff:
Note: See TracChangeset for help on using the changeset viewer.