Ignore:
Timestamp:
Apr 25, 2014, 12:20:14 PM (10 years ago)
Author:
lguez
Message:

Removed unused variables pks, pk, pkf from main program unit gcm.

Encapsulated procedures exner_hyb, exner_hyb_p, exner_hyb_loc,
exner_milieu, exner_milieu_p and exner_milieu_loc into
modules. (Compulsory to allow optional arguments.)

In the procedures exner_hyb, exner_hyb_p, exner_hyb_loc, donwgraded
arguments alpha and beta to local variables. In exner_milieu,
exner_milieu_p and exner_milieu_loc, removed beta altogether. In the
six procedures exner_*, made pkf an optional argument. Made some
cosmetic modifications in order to keep the six procedures exner_* as
close as possible.

In the six procedures exner_*, removed the averaging of pks at the
poles: this is not useful because ps is already the same at all
longitudes at the poles. This modification changes the results of the
program. Motivation: had to do this for exner_hyb because we call it
from test_disvert with a few surface pressure values.

In all the procedures calling exner_*, removed the variables alpha and
beta. Also removed variables alpha and beta from module leapfrog_mod
and from module call_calfis_mod.

Removed actual argument pkf in call to exner_hyb* and exner_milieu*
from guide_interp, guide_main, iniacademic and iniacademic_loc (pkf
was not used in those procedures).

Argument workvar of startget_dyn is used only if varname is tpot or

  1. When varname is tpot or q, the actual argument associated to

workvar in etat0_netcdf is not y. So y in etat0_netcdf is a
place-holder, never used. So we remove optional argument y in the
calls to exner_hyb and exner_milieu from etat0_netcdf.

Created procedure test_disvert, called only by etat0_netcdf. This
procedure tests the order of pressure values at half-levels and full
levels.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3dmem/guide_loc_mod.F90

    r1907 r2021  
    329329!=======================================================================
    330330  SUBROUTINE guide_main(itau,ucov,vcov,teta,q,masse,ps)
     331    use exner_hyb_loc_m, only: exner_hyb_loc
     332    use exner_milieu_loc_m, only: exner_milieu_loc
    331333    USE parallel_lmdz
    332334    USE control_mod
     
    353355    REAL, ALLOCATABLE, SAVE, DIMENSION (:,:) :: f_addv ! var aux: champ de guidage
    354356    ! Variables pour fonction Exner (P milieu couche)
    355     REAL, ALLOCATABLE, SAVE, DIMENSION (:,:,:)    :: pk, pkf
    356     REAL, ALLOCATABLE, SAVE, DIMENSION (:,:,:)    :: alpha, beta
     357    REAL, ALLOCATABLE, SAVE, DIMENSION (:,:,:)    :: pk
    357358    REAL, ALLOCATABLE, SAVE, DIMENSION (:,:)        :: pks   
    358359    REAL                               :: unskap
     
    399400        ALLOCATE(f_addv(ijb_v:ije_v,llm) )
    400401        ALLOCATE(pk(iip1,jjb_u:jje_u,llm)  )
    401         ALLOCATE(pkf(iip1,jjb_u:jje_u,llm)  )
    402         ALLOCATE(alpha(iip1,jjb_u:jje_u,llm)  )
    403         ALLOCATE(beta(iip1,jjb_u:jje_u,llm)  )
    404402        ALLOCATE(pks(iip1,jjb_u:jje_u)  )
    405403        ALLOCATE(p(ijb_u:ije_u,llmp1) )
     
    539537        CALL pression_loc( ijnb_u, ap, bp, ps, p )
    540538        if (pressure_exner) then
    541           CALL exner_hyb_loc(ip1jmp1,ps,p,alpha,beta,pks,pk,pkf)
     539          CALL exner_hyb_loc(ip1jmp1,ps,p,pks,pk)
    542540        else
    543           CALL exner_milieu_loc(ip1jmp1,ps,p,beta,pks,pk,pkf)
     541          CALL exner_milieu_loc(ip1jmp1,ps,p,pks,pk)
    544542        endif
    545543!$OMP BARRIER       
     
    894892!=======================================================================
    895893  SUBROUTINE guide_interp(psi,teta)
     894    use exner_hyb_loc_m, only: exner_hyb_loc
     895    use exner_milieu_loc_m, only: exner_milieu_loc
    896896  USE parallel_lmdz
    897897  USE mod_hallo
     
    919919  REAL, ALLOCATABLE, SAVE,DIMENSION (:,:,:)     :: pbary
    920920  ! Variables pour fonction Exner (P milieu couche)
    921   REAL, ALLOCATABLE, SAVE,DIMENSION (:,:,:)    :: pk, pkf
    922   REAL, ALLOCATABLE, SAVE, DIMENSION (:,:,:)    :: alpha, beta
     921  REAL, ALLOCATABLE, SAVE,DIMENSION (:,:,:)    :: pk
    923922  REAL ,ALLOCATABLE, SAVE, DIMENSION (:,:)        :: pks   
    924923  REAL                               :: unskap
     
    949948      ALLOCATE(pbary(iip1,jjb_v:jje_v,llm) )   
    950949      ALLOCATE(pk(iip1,jjb_u:jje_u,llm) )   
    951       ALLOCATE(pkf(iip1,jjb_u:jje_u,llm)  )   
    952       ALLOCATE(alpha(iip1,jjb_u:jje_u,llm) )   
    953       ALLOCATE(beta(iip1,jjb_u:jje_u,llm) )   
    954950      ALLOCATE(pks (iip1,jjb_u:jje_u) )   
    955951      ALLOCATE(qsat(ijb_u:ije_u,llm) )   
     
    10321028        CALL pression_loc( ijnb_u, ap, bp, psi, p )
    10331029        if (disvert_type==1) then
    1034           CALL exner_hyb_loc(ijnb_u,psi,p,alpha,beta,pks,pk,pkf)
     1030          CALL exner_hyb_loc(ijnb_u,psi,p,pks,pk)
    10351031        else ! we assume that we are in the disvert_type==2 case
    1036           CALL exner_milieu_loc(ijnb_u,psi,p,beta,pks,pk,pkf)
     1032          CALL exner_milieu_loc(ijnb_u,psi,p,pks,pk)
    10371033        endif
    10381034        unskap=1./kappa
Note: See TracChangeset for help on using the changeset viewer.