Changeset 3754


Ignore:
Timestamp:
May 5, 2025, 5:23:50 PM (7 weeks ago)
Author:
afalco
Message:

Pluto: imported orographic gravity waves from Mars.
AF

Location:
trunk
Files:
7 added
6 edited
1 copied

Legend:

Unmodified
Added
Removed
  • TabularUnified trunk/LMDZ.MARS/libf/phymars/sugwd.F90

    r2651 r3754  
    11      SUBROUTINE SUGWD(nlayer,sigtest)
    2 ! ==============================================================================   
    3 !     Initialize common variables in yoegwd.h to control the orographic 
    4 !     graivty wave drag parameterization. That means, all the tunable parameters
     2! ==============================================================================
     3!     Initialize common variables in yoegwd.h to control the orographic
     4!     gravity wave drag parameterization. That means, all the tunable parameters
    55!     for oro-GW scheme are in this subroutine.
    66!     MARTIN MILLER             *ECMWF*               ORIGINAL : 90-01-01 
  • TabularUnified trunk/LMDZ.PLUTO/libf/phypluto/callkeys_mod.F90

    r3684 r3754  
    44      logical,save :: callrad,corrk,calldifv,UseTurbDiff
    55!$OMP THREADPRIVATE(callrad,corrk,calldifv,UseTurbDiff)
    6       logical,save :: calladj,calltherm,n2cond,callsoil
    7 !$OMP THREADPRIVATE(calladj,calltherm,n2cond,callsoil)
     6      logical,save :: calladj,calltherm,n2cond,callsoil,calllott
     7!$OMP THREADPRIVATE(calladj,calltherm,n2cond,callsoil,calllott)
    88      logical,save :: callconduct,callmolvis,callmoldiff
    99!$OMP THREADPRIVATE(callconduct,callmolvis,callmoldiff)
     
    199199      real,save    :: deltap    ! width of transition to alpha_top (Pa)
    200200!$OMP THREADPRIVATE(alpha_top,pref,deltap)
    201      
     201
    202202!! Microphysics-specific variables
    203203      logical,save :: callmufi, call_haze_prod_pCH4
  • TabularUnified trunk/LMDZ.PLUTO/libf/phypluto/dimphy.F90

    r3184 r3754  
    11MODULE dimphy
    2  
     2
    33  INTEGER,SAVE :: klon   ! number of atmospheric columns (for this OpenMP subgrid)
    44  INTEGER,SAVE :: klev   ! number of atmospheric layers, read by master
     
    66  INTEGER,SAVE :: klevm1 ! number of atmospheric layers-1, read by master
    77!  INTEGER,SAVE :: kflev
     8  integer,save :: ndomainsz !=(ngrid-1)/20 + 1
    89
    910!$OMP THREADPRIVATE(klon)
    1011
    1112CONTAINS
    12  
     13
    1314  SUBROUTINE Init_dimphy(klon0,klev0)
    1415  IMPLICIT NONE
    15  
     16
    1617    INTEGER, INTENT(in) :: klon0
    1718    INTEGER, INTENT(in) :: klev0
    18    
     19
    1920    klon=klon0
    20    
    21 !$OMP MASTER 
     21
     22!$OMP MASTER
    2223    klev=klev0
    2324    klevp1=klev+1
    2425    klevm1=klev-1
    2526!    kflev=klev
    26 !$OMP END MASTER   
     27!$OMP END MASTER
    2728!$OMP BARRIER
    28    
     29
    2930  END SUBROUTINE Init_dimphy
    3031
    31  
     32
    3233END MODULE dimphy
  • TabularUnified trunk/LMDZ.PLUTO/libf/phypluto/inifis_mod.F90

    r3749 r3754  
    355355     if (is_master) write(*,*) trim(rname)//": callsoil = ",callsoil
    356356
     357     calllott=.true. ! default value
     358     call getin_p("calllott",calllott)
     359     write(*,*)" calllott = ",calllott
     360
    357361     if (is_master) write(*,*)trim(rname)//&
    358362       ": Rad transfer is computed every iradia", &
  • TabularUnified trunk/LMDZ.PLUTO/libf/phypluto/phys_state_var_mod.F90

    r3627 r3754  
    99!======================================================================
    1010! Declaration des variables
    11       USE dimphy, only : klon,klev
     11      USE dimphy, only : klon,klev,ndomainsz
    1212      USE comsoil_h, only : nsoilmx
    1313      use comsaison_h, only: mu0, fract
     
    117117!rugoro(:) ! longueur de rugosite de l'OESM
    118118
     119        ndomainsz=(klon-1)/20 + 1
    119120        ALLOCATE(phisfi(klon))
    120121        ALLOCATE(tsurf(klon))
  • TabularUnified trunk/LMDZ.PLUTO/libf/phypluto/physiq_mod.F90

    r3750 r3754  
    4444                            obliquit, z0, adjust, tpal
    4545      use comcstfi_mod, only: pi, g, rcp, r, rad, mugaz, cpp
     46      use calldrag_noro_mod, only: calldrag_noro
    4647      use time_phylmdz_mod, only: daysec
    4748      use callkeys_mod, only: albedo_spectral_mode, calladj, calldifv,        &
    48                               callrad, callsoil, nosurf,                      &
     49                              calllott, callrad, callsoil, nosurf,            &
    4950                              callconduct,callmolvis,callmoldiff,             &
    5051                              corrk,                                          &
     
    117118!         II.2.b Option 2 : Atmosphere has no radiative effect.
    118119!
     120!      II.3 Gravity wave and subgrid scale topography drag :
     121!
    119122!      III. Vertical diffusion (turbulent mixing)
    120123!
     
    385388      real zdhdif(ngrid,nlayer)                             ! Turbdiff/vdifc routines.
    386389      real zdhadj(ngrid,nlayer)                             ! Convadj routine.
     390      REAL zdtgw(ngrid,nlayer)                              ! Gravity waves (K/s)
     391      REAL zdugw(ngrid,nlayer),zdvgw(ngrid,nlayer)          ! Gravity waves (m.s-2)
    387392      REAL zdvc(ngrid,nlayer),zduc(ngrid,nlayer)            ! condense_n2 routine.
    388393
     
    11431148   endif
    11441149
     1150
     1151!-----------------------------------------------------------------------
     1152! II.3 Gravity wave and subgrid scale topography drag :
     1153!    -------------------------------------------------
     1154
     1155      IF(calllott)THEN
     1156        CALL calldrag_noro(ngrid,nlayer,ptimestep, &
     1157                           zplay,zplev,pt,pu,pv,zdtgw,zdugw,zdvgw)
     1158
     1159        DO l=1,nlayer
     1160          DO ig=1,ngrid
     1161            pdv(ig,l)=pdv(ig,l)+zdvgw(ig,l)
     1162            pdu(ig,l)=pdu(ig,l)+zdugw(ig,l)
     1163            pdt(ig,l)=pdt(ig,l)+zdtgw(ig,l)
     1164          ENDDO
     1165        ENDDO
     1166      ENDIF
     1167
     1168
    11451169!  --------------------------------------------
    11461170!  III. Vertical diffusion (turbulent mixing) :
  • TabularUnified trunk/LMDZ.PLUTO/libf/phypluto/sugwd.F90

    r3753 r3754  
    11      SUBROUTINE SUGWD(nlayer,sigtest)
    2 ! ==============================================================================   
    3 !     Initialize common variables in yoegwd.h to control the orographic 
    4 !     graivty wave drag parameterization. That means, all the tunable parameters
     2! ==============================================================================
     3!     Initialize common variables in yoegwd.h to control the orographic
     4!     gravity wave drag parameterization. That means, all the tunable parameters
    55!     for oro-GW scheme are in this subroutine.
    6 !     MARTIN MILLER             *ECMWF*               ORIGINAL : 90-01-01 
     6!     MARTIN MILLER             *ECMWF*               ORIGINAL : 90-01-01
    77!     Update:    Jiandong Liu     2022/03/15          Rewirite into .F90 and
    8 !                                                     comment.   
     8!                                                     comment.
    99!     REFERENCE.
    1010!     ----------
     
    2020      implicit none
    2121
    22       ! 0.1 Inputs:         
     22      ! 0.1 Inputs:
    2323      integer,intent(in):: nlayer                ! Number of model levels
    2424      REAL,intent(in):: sigtest(nlayer+1)        ! Vertical coordinate table
     
    3333      integer jk
    3434
    35 !-------------------------------------------------------------------------------     
    36 ! 1.   Set the values of the parameters 
    37 !-------------------------------------------------------------------------------   
     35!-------------------------------------------------------------------------------
     36! 1.   Set the values of the parameters
     37!-------------------------------------------------------------------------------
    3838!     PRINT *,' Dans sugwd nlayer=',nlayer,' SIG=',sigtest
    3939      GHMAX=10000.
    40    
     40
    4141!     old  ZSIGT=0.94
    4242!     old  ZPR=80000.
    4343      ZSIGT=0.85      ! Sigmal levels
    4444      ZPR=100000.     ! Surface (Reference) Pressure?
    45      
     45
    4646      ! ! Condition to find NKTOPG layer, which NKTOPG is a condition to set
    4747      ! 1*pvar and 2*pvar layers (OROSETUP)
     
    4949         ZPM1R=0.5*ZPR*(sigtest(JK)+sigtest(JK+1))
    5050         IF((ZPM1R/ZPR).GE.ZSIGT)THEN
    51             NKTOPG=JK   
     51            NKTOPG=JK
    5252         ENDIF
    5353      ENDDO
    5454      WRITE(*,*) 'In sugwd NKTOPG=',NKTOPG
    55    
    56       GSIGCR=0.80  ! Sigmal levels to found the top of low level flow height (OROSETUP) 
     55
     56      GSIGCR=0.80  ! Sigmal levels to found the top of low level flow height (OROSETUP)
    5757      GKDRAG= 0.1  ! used to be 0.1 for mcd Version 1 and 2 (before 10/2000) (OROSETUP)
    58                      
     58
    5959      GFRCRIT=1.0
    6060      GKWAKE=1.0   ! The G in equation (16)
    61       GRCRIT=0.25  ! Critical value for Mean flow richardson number(OROSETUP)     
     61      GRCRIT=0.25  ! Critical value for Mean flow richardson number(OROSETUP)
    6262      GKDRAGL=4.*GKDRAG
    6363      GRAHILO=1.
    64       GVCRIT =0.0   
    65 !------------------------------------------------------------------------------- 
    66 ! 2.    Set values of security parameters 
    67 !------------------------------------------------------------------------------- 
     64      GVCRIT =0.0
     65!-------------------------------------------------------------------------------
     66! 2.    Set values of security parameters
     67!-------------------------------------------------------------------------------
    6868      GVSEC=0.10      ! Security values for For normal wind (pu^2+pv^2)^0.5(OROSETUP,GWSTRESS)
    69       GSSEC=1.E-12    ! Security values for Brunt–Väisälä frequency N^2 (OROSETUP)   
     69      GSSEC=1.E-12    ! Security values for Brunt–Väisälä frequency N^2 (OROSETUP)
    7070      GTSEC=1.E-07    ! Security values for Sub-grid scale anisotropy(OROSETUP,GWSTRESS)
    7171
Note: See TracChangeset for help on using the changeset viewer.