Changeset 2037


Ignore:
Timestamp:
May 6, 2014, 4:56:20 PM (10 years ago)
Author:
lguez
Message:

PVteta computed by PVtheta was not used. Also there were a couple of
problems with PVtheta:

-- PVtheta calls tetalevel in phylmd, and interpolates at

Earth-specific values of potential temperature.

-- PVtheta calls tourabs, and the computation of rot in tourabs should

be modified (it is not correct when there is a zoom).

-- Even when there is no zoom, the computation of rot in tourabs

should probably be modified: directly combine vcov and ucov, as in
tourpot, instead of dividing by cv and cu.

Location:
LMDZ5/trunk/libf
Files:
4 deleted
7 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3d/calfis.F

    r1987 r2037  
    163163      REAL unskap, pksurcp
    164164c
    165 cIM diagnostique PVteta, Amip2
    166       INTEGER,PARAMETER :: ntetaSTD=3
    167       REAL,SAVE :: rtetaSTD(ntetaSTD)=(/350.,380.,405./) ! Earth-specific, beware !!
    168       REAL PVteta(ngridmx,ntetaSTD)
    169 c
    170165      REAL flxwfi(ngridmx,llm)  ! Flux de masse verticale sur la grille physiq
    171166c
     
    431426
    432427      ENDDO
    433 c
    434       if (planet_type=="earth") then
    435 #ifdef CPP_PHYS
    436 ! PVtheta calls tetalevel, which is in the physics
    437 cIM calcul PV a teta=350, 380, 405K
    438       CALL PVtheta(ngridmx,llm,pucov,pvcov,pteta,
    439      $           ztfi,zplay,zplev,
    440      $           ntetaSTD,rtetaSTD,PVteta)
    441 #endif
    442       endif
    443428c
    444429c On change de grille, dynamique vers physiq, pour le flux de masse verticale
     
    491476     .             zdqfi,
    492477     .             zdpsrf,
    493 cIM diagnostique PVteta, Amip2         
    494      .             pducov,
    495      .             PVteta)
     478     .             pducov)
    496479
    497480      else if ( planet_type=="generic" ) then
  • LMDZ5/trunk/libf/dyn3dmem/calfis_loc.F

    r1987 r2037  
    219219      REAL unskap, pksurcp
    220220c
    221 cIM diagnostique PVteta, Amip2
    222       INTEGER,PARAMETER :: ntetaSTD=3
    223       REAL,SAVE :: rtetaSTD(ntetaSTD)=(/350.,380.,405./) ! Earth-specific, beware !!
    224       REAL PVteta(klon,ntetaSTD)
    225      
    226      
    227221      REAL SSUM
    228222
     
    252246      klon=klon_mpi
    253247     
    254       PVteta(:,:)=0.
    255            
    256248c
    257249      IF ( firstcal )  THEN
     
    510502      endif
    511503
    512 
    513       IF (is_sequential.and.(planet_type=="earth")) THEN
    514 #ifdef CPP_PHYS
    515 ! PVtheta calls tetalevel, which is in the physics
    516 cIM calcul PV a teta=350, 380, 405K
    517         CALL PVtheta(ngridmx,llm,pucov,pvcov,pteta,
    518      $           ztfi,zplay,zplev,
    519      $           ntetaSTD,rtetaSTD,PVteta)
    520 c
    521 #endif
    522       ENDIF
    523 
    524504c On change de grille, dynamique vers physiq, pour le flux de masse verticale
    525505c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     
    707687     .             zdqfi_omp,
    708688     .             zdpsrf_omp,
    709 cIM diagnostique PVteta, Amip2         
    710      .             pducov,
    711      .             PVteta)
     689     .             pducov)
    712690
    713691      else if ( planet_type=="generic" ) then
  • LMDZ5/trunk/libf/dyn3dpar/calfis_p.F

    r1987 r2037  
    217217      REAL unskap, pksurcp
    218218c
    219 cIM diagnostique PVteta, Amip2
    220       INTEGER,PARAMETER :: ntetaSTD=3
    221       REAL,SAVE :: rtetaSTD(ntetaSTD)=(/350.,380.,405./) ! Earth-specific, beware !!
    222       REAL PVteta(klon,ntetaSTD)
    223      
    224219      REAL SSUM
    225220
     
    249244      klon=klon_mpi
    250245     
    251       PVteta(:,:)=0.
    252            
    253246c
    254247      IF ( firstcal )  THEN
     
    484477      endif
    485478
    486 
    487       IF (is_sequential.and.(planet_type=="earth")) THEN
    488 #ifdef CPP_PHYS
    489 ! PVtheta calls tetalevel, which is in the physics
    490 cIM calcul PV a teta=350, 380, 405K
    491         CALL PVtheta(ngridmx,llm,pucov,pvcov,pteta,
    492      $           ztfi,zplay,zplev,
    493      $           ntetaSTD,rtetaSTD,PVteta)
    494 c
    495 #endif
    496       ENDIF
    497 
    498479c On change de grille, dynamique vers physiq, pour le flux de masse verticale
    499480      CALL gr_dyn_fi_p(llm,iip1,jjp1,klon,flxw,flxwfi)
     
    668649     .             zdqfi_omp,
    669650     .             zdpsrf_omp,
    670 cIM diagnostique PVteta, Amip2         
    671      .             pducov,
    672      .             PVteta)
     651     .             pducov)
    673652
    674653      else if ( planet_type=="generic" ) then
  • LMDZ5/trunk/libf/phydev/physiq.F90

    r2002 r2037  
    88     &            flxmass_w, &
    99     &            d_u, d_v, d_t, d_qx, d_ps &
    10      &            , dudyn &
    11      &            , PVteta)
     10     &            , dudyn)
    1211
    1312      USE dimphy, only : klon,klev
     
    5958      real,intent(out) :: d_ps(klon) ! physics tendency on surface pressure
    6059      real,intent(in) :: dudyn(iim+1,jjmp1,klev) ! Not used
    61 !FH! REAL PVteta(klon,nbteta)
    62 !      REAL PVteta(klon,1)
    63       real,intent(in) :: PVteta(klon,3) ! Not used ; should match definition
    64                                         ! in calfis.F
    6560
    6661integer,save :: itau=0 ! counter to count number of calls to physics
  • LMDZ5/trunk/libf/phylmd/lmdz1d.F90

    r2023 r2037  
    209209      integer jjmp1
    210210      parameter (jjmp1=jjm+1-1/jjm)
    211       INTEGER nbteta
    212       PARAMETER(nbteta=3)
    213211      REAL dudyn(iim+1,jjmp1,llm)
    214       REAL PVteta(1,nbteta)
    215212      INTEGER read_climoz
    216213!Al1
     
    803800     &              u,v,temp,q,omega2,                                      &
    804801     &              du_phys,dv_phys,dt_phys,dq,dpsrf,                        &
    805      &              dudyn,PVteta)
     802     &              dudyn)
    806803        firstcall=.false.
    807804
  • LMDZ5/trunk/libf/phylmd/phys_output_mod.F90

    r2002 r2037  
    2626
    2727  SUBROUTINE phys_output_open(rlon,rlat,pim,tabij,ipt,jpt,plon,plat, &
    28        jjmp1,nlevSTD,clevSTD,rlevSTD,nbteta, &
    29        ctetaSTD, dtime, ok_veget, &
     28       jjmp1,nlevSTD,clevSTD,rlevSTD, dtime, ok_veget, &
    3029       type_ocean, iflag_pbl,ok_mensuel,ok_journe, &
    3130       ok_hf,ok_instan,ok_LES,ok_ade,ok_aie, read_climoz, &
     
    8281
    8382    INTEGER                               :: jjmp1
    84     INTEGER                               :: nbteta, nlevSTD, radpas
     83    INTEGER                               :: nlevSTD, radpas
    8584    LOGICAL                               :: ok_mensuel, ok_journe, ok_hf, ok_instan
    8685    LOGICAL                               :: ok_LES,ok_ade,ok_aie,flag_aerosol_strat
     
    106105    CHARACTER(LEN=2)                      :: bb3
    107106    CHARACTER(LEN=6)                      :: type_ocean
    108     CHARACTER(LEN=3)                      :: ctetaSTD(nbteta)
    109107    INTEGER, DIMENSION(iim*jjmp1)         ::  ndex2d
    110108    INTEGER, DIMENSION(iim*jjmp1*klev)    :: ndex3d
  • LMDZ5/trunk/libf/phylmd/physiq.F90

    r2009 r2037  
    88     flxmass_w, &
    99     d_u, d_v, d_t, d_qx, d_ps &
    10      , dudyn &
    11      , PVteta)
     10     , dudyn)
    1211
    1312  USE ioipsl, only: histbeg, histvert, histdef, histend, histsync, &
     
    104103  !! d_qx----output-R-tendance physique de "qx" (kg/kg/s)
    105104  !! d_ps----output-R-tendance physique de la pression au sol
    106   !!IM
    107   !! PVteta--output-R-vorticite potentielle a des thetas constantes
    108105  !!======================================================================
    109106  include "dimensions.h"
     
    250247  !IM definition dynamique o_trac dans phys_output_open
    251248  !      type(ctrl_out) :: o_trac(nqtot)
    252   !
    253   !IM Amip2 PV a theta constante
    254   !
    255   INTEGER nbteta
    256   PARAMETER(nbteta=3)
    257   CHARACTER*3 ctetaSTD(nbteta)
    258   DATA ctetaSTD/'350','380','405'/
    259   SAVE ctetaSTD
    260   !$OMP THREADPRIVATE(ctetaSTD)
    261   REAL rtetaSTD(nbteta)
    262   DATA rtetaSTD/350., 380., 405./
    263   SAVE rtetaSTD
    264   !$OMP THREADPRIVATE(rtetaSTD)     
    265   !
    266   REAL PVteta(klon,nbteta)
    267   !
    268   !MI Amip2 PV a theta constante
    269 
    270   !ym      INTEGER klevp1, klevm1
    271   !ym      PARAMETER(klevp1=klev+1,klevm1=klev-1)
    272   !ym      include "raddim.h"
    273   !
    274   !
    275   !IM Amip2
     249
    276250  ! variables a une pression donnee
    277251  !
     
    12561230     call phys_output_open(rlon,rlat,nCFMIP,tabijGCM, &
    12571231          iGCM,jGCM,lonGCM,latGCM, &
    1258           jjmp1,nlevSTD,clevSTD,rlevSTD, &
    1259           nbteta, ctetaSTD, dtime,ok_veget, &
     1232          jjmp1,nlevSTD,clevSTD,rlevSTD, dtime,ok_veget, &
    12601233          type_ocean,iflag_pbl,ok_mensuel,ok_journe, &
    12611234          ok_hf,ok_instan,ok_LES,ok_ade,ok_aie,  &
Note: See TracChangeset for help on using the changeset viewer.