Changeset 1912


Ignore:
Timestamp:
Apr 3, 2018, 8:13:24 AM (7 years ago)
Author:
emillour
Message:

Mars GCM:
Tidying the gravity wave routines by turning them into modules:
orodrag.F -> orodrag_mod.F : note that the declared size of pvar(), which is
used in call to gwstress was wrong.
calldrag_noro.F -> calldrag_noro_mod.F
drag_noro.F -> drag_noro_mod.F
gwstress.F -> gwstress_mod.F
EM

Location:
trunk/LMDZ.MARS
Files:
2 edited
4 moved

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/README

    r1911 r1912  
    25372537- in improvedCO2clouds : change of the names of input and output variables according to their names in co2cloud in order to not confuse them (in improvedCO2clouds "ptimestep" corresponds actually to "microtimestep").
    25382538
     2539== 03/04/2018 == EM
     2540Tidying the gravity wave routines by turning them into modules:
     2541orodrag.F -> orodrag_mod.F : note that the declared size of pvar(), which is
     2542used in call to gwstress was wrong.
     2543calldrag_noro.F -> calldrag_noro_mod.F
     2544drag_noro.F -> drag_noro_mod.F
     2545gwstress.F -> gwstress_mod.F
  • trunk/LMDZ.MARS/libf/phymars/calldrag_noro_mod.F

    r1911 r1912  
     1      MODULE calldrag_noro_mod
     2     
     3      IMPLICIT NONE
     4     
     5      CONTAINS
     6     
    17      SUBROUTINE calldrag_noro(ngrid,nlayer,ptimestep,
    28     &                 pplay,pplev,pt,pu,pv,pdtgw,pdugw,pdvgw)
     
    612       use surfdat_h, only: zstd, zsig, zgam, zthe
    713       use dimradmars_mod, only: ndomainsz
     14       use drag_noro_mod, only: drag_noro
    815       IMPLICIT NONE
    916c=======================================================================
     
    202209      ENDDO         !   (boucle jd=1, ndomain)
    203210
    204       return
    205       end
    206 
     211      END SUBROUTINE calldrag_noro
     212     
     213      END MODULE calldrag_noro_mod
     214
  • trunk/LMDZ.MARS/libf/phymars/drag_noro_mod.F

    r1911 r1912  
     1      MODULE drag_noro_mod
     2     
     3      IMPLICIT NONE
     4     
     5      CONTAINS
     6     
    17      SUBROUTINE drag_noro (klon,klev,dtime,pplay,pplev,
    28     e                   pvar, psig, pgam, pthe,
     
    5157c
    5258      use dimradmars_mod, only:  ndlo2
    53       USE comcstfi_h
     59      USE orodrag_mod, ONLY: orodrag
     60      USE comcstfi_h, ONLY: g, r
    5461      IMPLICIT none
    5562c======================================================================
     
    160167      ENDDO
    161168c
    162       RETURN
    163       END
     169
     170      END SUBROUTINE drag_noro
     171     
     172      END MODULE drag_noro_mod
  • trunk/LMDZ.MARS/libf/phymars/gwstress_mod.F

    r1911 r1912  
     1      MODULE gwstress_mod
     2     
     3      IMPLICIT NONE
     4     
     5      CONTAINS
     6
    17      SUBROUTINE GWSTRESS
    28     *         (  klon  , klev
     
    4955      integer klon,klev,kidia,kfdia
    5056
    51 #include "yoegwd.h"
     57      include "yoegwd.h"
    5258
    5359C-----------------------------------------------------------------------
     
    129135  301 CONTINUE
    130136C
    131       RETURN
    132       END
     137
     138      END SUBROUTINE GWSTRESS
     139     
     140      END MODULE gwstress_mod
  • trunk/LMDZ.MARS/libf/phymars/orodrag_mod.F

    r1911 r1912  
     1      MODULE orodrag_mod
     2     
     3      IMPLICIT NONE
     4     
     5      CONTAINS
     6     
    17      SUBROUTINE ORODRAG( klon,klev
    28     I                 , KGWD, KGWDIM, KDX, KTEST
     
    7177C-----------------------------------------------------------------------
    7278      use dimradmars_mod, only: ndlo2
    73       USE comcstfi_h
     79      USE gwstress_mod, ONLY: gwstress
     80      USE comcstfi_h, ONLY: g, cpp
    7481      implicit none
    7582C
     
    7986      integer, save :: kfdia ! =NDLO2
    8087
    81 #include "yoegwd.h"
     88      include "yoegwd.h"
    8289C-----------------------------------------------------------------------
    8390C
     
    116123      integer ji,jk,jl,klevm1,ilevp1
    117124C      real gkwake
    118       real ztmst,pvar,ztauf,zrtmst,zdelp,zb,zc,zbet
     125      real ztmst,pvar(NDLO2,4),ztauf,zrtmst,zdelp,zb,zc,zbet
    119126      real zconb,zabsv,zzd1,ratio,zust,zvst,zdis,ztemp
    120127C
     
    283290C
    284291C
    285       RETURN
    286       END
     292
     293      END SUBROUTINE ORODRAG
     294     
     295      END MODULE orodrag_mod
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r1818 r1912  
    4646     &                     obliquit
    4747      USE comcstfi_h, only: r, cpp, mugaz, g, rcp, pi, rad
     48      USE calldrag_noro_mod, ONLY: calldrag_noro
    4849      use param_v4_h, only: nreact,n_avog,
    4950     &                      fill_data_thermos, allocate_param_thermos
Note: See TracChangeset for help on using the changeset viewer.