Ignore:
Timestamp:
Feb 24, 2014, 4:05:47 PM (10 years ago)
Author:
Ehouarn Millour
Message:

Add updating pressure, mass and Exner function (ie: all variables which depend on surface pressure) after adding physics tendencies (which include a surface pressure tendency).
Note that this change induces slight changes in GCM results with respect to previous svn version of the code, even if surface pressure tendency is zero (because of recomputation of polar values as an average over polar points on the dynamics grid).
EM

File:
1 edited

Legend:

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

    r1907 r1987  
    1717       USE vampir
    1818       USE timer_filtre, ONLY : print_filtre_timer
    19        USE infotrac
     19       USE infotrac, ONLY: nqtot
    2020       USE guide_p_mod, ONLY : guide_main
    2121       USE getparam
    22        USE control_mod
    23 
     22       USE control_mod, ONLY: nday, day_step, planet_type, offline,
     23     &                       iconser, iphysiq, iperiod, dissip_period,
     24     &                       iecri, ip_ebil_dyn, ok_dynzon, ok_dyn_ins,
     25     &                       periodav, ok_dyn_ave, output_grads_dyn,
     26     &                       iapp_tracvl
    2427      IMPLICIT NONE
    2528
     
    7073#include "academic.h"
    7174     
    72       INTEGER         longcles
    73       PARAMETER     ( longcles = 20 )
    74       REAL  clesphy0( longcles )
     75      INTEGER,PARAMETER :: longcles = 20
     76      REAL,INTENT(IN) :: clesphy0( longcles ) ! not used
     77      REAL,INTENT(IN) :: time_0 ! not used
     78
     79c   dynamical variables:
     80      REAL,INTENT(INOUT) :: ucov(ip1jmp1,llm)    ! zonal covariant wind
     81      REAL,INTENT(INOUT) :: vcov(ip1jm,llm)      ! meridional covariant wind
     82      REAL,INTENT(INOUT) :: teta(ip1jmp1,llm)    ! potential temperature
     83      REAL,INTENT(INOUT) :: ps(ip1jmp1)          ! surface pressure (Pa)
     84      REAL,INTENT(INOUT) :: masse(ip1jmp1,llm)   ! air mass
     85      REAL,INTENT(INOUT) :: phis(ip1jmp1)        ! geopotentiat at the surface
     86      REAL,INTENT(INOUT) :: q(ip1jmp1,llm,nqtot) ! advected tracers
     87
     88      REAL,SAVE :: p (ip1jmp1,llmp1  )       ! interlayer pressure
     89      REAL,SAVE :: pks(ip1jmp1)              ! exner at the surface
     90      REAL,SAVE :: pk(ip1jmp1,llm)           ! exner at mid-layer
     91      REAL,SAVE :: pkf(ip1jmp1,llm)          ! filtered exner at mid-layer
     92      REAL,SAVE :: phi(ip1jmp1,llm)          ! geopotential
     93      REAL,SAVE :: w(ip1jmp1,llm)            ! vertical velocity
    7594
    7695      real zqmin,zqmax
    77 
    78 c   variables dynamiques
    79       REAL :: vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
    80       REAL :: teta(ip1jmp1,llm)                 ! temperature potentielle
    81       REAL :: q(ip1jmp1,llm,nqtot)              ! champs advectes
    82       REAL :: ps(ip1jmp1)                       ! pression  au sol
    83       REAL,SAVE :: p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
    84       REAL,SAVE :: pks(ip1jmp1)                      ! exner au  sol
    85       REAL,SAVE :: pk(ip1jmp1,llm)                   ! exner au milieu des couches
    86       REAL,SAVE :: pkf(ip1jmp1,llm)                  ! exner filt.au milieu des couches
    87       REAL :: masse(ip1jmp1,llm)                ! masse d'air
    88       REAL :: phis(ip1jmp1)                     ! geopotentiel au sol
    89       REAL,SAVE :: phi(ip1jmp1,llm)                  ! geopotentiel
    90       REAL,SAVE :: w(ip1jmp1,llm)                    ! vitesse verticale
    9196
    9297c variables dynamiques intermediaire pour le transport
     
    123128
    124129      REAL  SSUM
    125       REAL time_0
    126130!      REAL,SAVE :: finvmaold(ip1jmp1,llm)
    127131
     
    603607
    604608      IF( forward. OR . leapf )  THEN
    605 cc$OMP PARALLEL DEFAULT(SHARED)
    606 c
     609! Ehouarn: NB: fields sent to advtrac are those at the beginning of the time step
    607610         CALL caladvtrac_p(q,pbaru,pbarv,
    608611     *        p, masse, dq,  teta,
     
    616619
    617620      ENDIF ! of IF( forward. OR . leapf )
    618 cc$OMP END PARALLEL
    619621
    620622c-----------------------------------------------------------------------
     
    907909     $                  ucov, vcov, teta , q   ,ps ,
    908910     $                 dufi, dvfi, dtetafi , dqfi ,dpfi  )
    909 
     911          ! since addfi updates ps(), also update p(), masse() and pk()
     912          CALL pression_p(ip1jmp1,ap,bp,ps,p)
     913c$OMP BARRIER
     914          CALL massdair_p(p,masse)
     915c$OMP BARRIER
     916          if (pressure_exner) then
     917            CALL exner_hyb_p(ip1jmp1,ps,p,alpha,beta,pks,pk,pkf)
     918          else
     919            CALL exner_milieu_p(ip1jmp1,ps,p,beta,pks,pk,pkf)
     920          endif
     921c$OMP BARRIER
     922         
    910923         IF (ok_strato) THEN
    911924           CALL top_bound_p(vcov,ucov,teta,masse,dtphys)
     
    10441057          CALL exner_milieu_p( ip1jmp1, ps, p, beta, pks, pk, pkf )
    10451058        endif
     1059c$OMP BARRIER
     1060        CALL massdair_p(p,masse)
    10461061c$OMP BARRIER
    10471062
Note: See TracChangeset for help on using the changeset viewer.