source: trunk/LMDZ.MARS/libf/phymars/calldrag_noro.F @ 1242

Last change on this file since 1242 was 1047, checked in by emillour, 11 years ago

Mars GCM:

  • IMPORTANT CHANGE: Removed all reference/use of ngridmx (dimphys.h) in routines (necessary prerequisite to using parallel dynamics); in most cases this just means adding 'ngrid' as routine argument, and making local saved variables allocatable (and allocated at first call). In the process, had to convert many *.h files to equivalent modules: yomaer.h => yomaer_h.F90 , surfdat.h => surfdat_h.F90 , comsaison.h => comsaison_h.F90 , yomlw.h => yomlw_h.F90 , comdiurn.h => comdiurn_h.F90 , dimradmars.h => dimradmars_mod.F90 , comgeomfi.h => comgeomfi_h.F90, comsoil.h => comsoil_h.F90 , slope.h => slope_mod.F90
  • Also updated EOF routines, everything is now in eofdump_mod.F90
  • Removed unused routine lectfux.F (in dyn3d)

EM

File size: 5.6 KB
RevLine 
[38]1      SUBROUTINE calldrag_noro(ngrid,nlayer,ptimestep,
2     &                 pplay,pplev,pt,pu,pv,pdtgw,pdugw,pdvgw)
3
4
5
[1047]6       use surfdat_h, only: zstd, zsig, zgam, zthe
7       use dimradmars_mod, only: ndomainsz
[38]8       IMPLICIT NONE
9c=======================================================================
10c   subject:
11c   --------
12c   Subroutine designed to call SUBROUTINE drag_noro
13c   Interface for sub-grid scale orographic scheme
14c   The purpose of this subroutine is
15c      1) Make some initial calculation at first call
16c      2) Split the calculation in several sub-grid
17c        ("sub-domain") to save memory and
18c        be able run on a workstation at high resolution
[1047]19c        The sub-grid size is defined in dimradmars_mod.
[38]20c
21c   author:   
22c   ------
23c           Christophe Hourdin/ Francois Forget
24c
25c   changes:
26c   -------
27c   > J.-B. Madeleine 10W12
28c   This version uses the variable's splitting, which can be usefull
29c     when performing very high resolution simulation like LES.
30c
31c   input:
32c   -----
33c   ngrid                 number of gridpoint of horizontal grid
34c   nlayer                Number of layer
35c   ptimestep             Physical timestep (s)
36c   pplay(ngrid,nlayer)    pressure (Pa) in the middle of each layer
37c   pplev(ngrid,nlayer+1)  pressure (Pa) at boundaries of each layer
38c   pt(ngrid,nlayer)       atmospheric temperature  (K)
39c   pu(ngrid,nlayer)       zonal wind (m s-1)
40c   pv(ngrid,nlayer)       meridional wind (m s-1)
41c
42c   output:
43c   -------
44c   pdtgw(ngrid,nlayer)    Temperature trend (K.s-1)
45c   pdugw(ngrid,nlayer)    zonal wind trend  (m.s-2)
46c   pdvgw(ngrid,nlayer)    meridional wind trend  (m.s-2)
47c
48c
49c
50c
51c
52c=======================================================================
53c
54c    0.  Declarations :
55c    ------------------
56c
[1047]57!#include "dimensions.h"
58!#include "dimphys.h"
59!#include "dimradmars.h"
60!#include "surfdat.h"
[38]61
62c-----------------------------------------------------------------------
63c    Input/Output
64c    ------------
65      INTEGER ngrid,nlayer 
66
67      real ptimestep
68
69      REAL pplev(ngrid,nlayer+1),pplay(ngrid,nlayer)
70      REAL pt(ngrid,nlayer), pu(ngrid,nlayer),pv(ngrid,nlayer)
71      REAL pdtgw(ngrid,nlayer), pdugw(ngrid,nlayer),pdvgw(ngrid,nlayer)
72
73
74c
75c    Local variables :
76c    -----------------
77
[1047]78      REAL sigtest(nlayer+1)
79      INTEGER igwd,igwdim,itest(ngrid)
[38]80
[1047]81      INTEGER,SAVE :: ndomain
82!      parameter (ndomain = (ngrid-1) / ndomainsz + 1)
[38]83
84      INTEGER l,ig
85      INTEGER jd,ig0,nd
86
[1047]87      REAL zulow(ngrid),zvlow(ngrid)
88      REAL zustr(ngrid),zvstr(ngrid)
[38]89
[1047]90      REAL zplev(ndomainsz,nlayer+1)
91      REAL zplay(ndomainsz,nlayer)
92      REAL zt(ndomainsz,nlayer)
93      REAL zu(ndomainsz,nlayer)
94      REAL zv(ndomainsz,nlayer)
[38]95      INTEGER zidx(ndomainsz)
[1047]96      REAL zzdtgw(ndomainsz,nlayer)
97      REAL zzdugw(ndomainsz,nlayer)
98      REAL zzdvgw(ndomainsz,nlayer)
[38]99
100      logical ll
101
102
103c   local saved variables
104c   ---------------------
105
106      LOGICAL firstcall
107      DATA firstcall/.true./
108      SAVE firstcall
109
110
111c----------------------------------------------------------------------
112
113c     Initialisation
114c     --------------
115
116      IF (firstcall) THEN
[1047]117        ndomain = (ngrid-1) / ndomainsz + 1
118
119         do l=1,nlayer+1
[38]120           sigtest(l)=pplev(1,l)/pplev(1,1)
121         enddo
[1047]122         call sugwd(nlayer,sigtest)
[38]123
[1047]124         if (ngrid .EQ. 1) then
[38]125           if (ndomainsz .NE. 1) then
126             print*
127             print*,'ATTENTION !!!'
128             print*,'pour tourner en 1D, meme pour drag_noro '
[1047]129             print*,'fixer ndomainsz=1 dans phymars/dimradmars_mod'
[38]130             print*
131             call exit(1)
132           endif
133         endif
134
135         firstcall=.false.
136      END IF
137
138c     Starting loop on sub-domain
139c     ----------------------------
140
141      DO jd=1,ndomain
142        ig0=(jd-1)*ndomainsz
143        if (jd.eq.ndomain) then
[1047]144          nd=ngrid-ig0
[38]145        else
146          nd=ndomainsz
147        endif
148
149c       Detecting points concerned by the scheme
150c       ----------------------------------------
151
152        igwd=0
153        DO ig=ig0+1,ig0+nd
154          itest(ig)=0
155          ll=zstd(ig).gt.50.0
156          IF(ll) then
157            itest(ig)=1
158            igwd=igwd+1
159            zidx(igwd)=ig - ig0
160          ENDIF
161        ENDDO
162        IGWDIM=MAX(1,IGWD)
163
164c       Spliting input variable in sub-domain input variables
165c       ---------------------------------------------------
166
167        do l=1,nlayer+1
168          do ig = 1,nd
169           zplev(ig,l) = pplev(ig0+ig,l)
170          enddo
171        enddo
172
173        do l=1,nlayer
174          do ig = 1,nd
175            zplay(ig,l) = pplay(ig0+ig,l)
176            zt(ig,l) = pt(ig0+ig,l)
177            zu(ig,l) = pu(ig0+ig,l)
178            zv(ig,l) = pv(ig0+ig,l)
179          enddo
180        enddo
181
182c       Calling gravity wave and subgrid scale topo parameterization
183c       -------------------------------------------------------------
184
185        call drag_noro (nd,nlayer,ptimestep,zplay,zplev,
186     e        zstd(ig0+1),zsig(ig0+1),zgam(ig0+1),zthe(ig0+1),
187     e        igwd,igwdim,zidx,itest(ig0+1),
188     e        zt, zu, zv,
189     s        zulow(ig0+1),zvlow(ig0+1),zustr(ig0+1),zvstr(ig0+1),
190     s        zzdtgw,zzdugw,zzdvgw)
191
192c       Un-spliting output variable from sub-domain input variables
193c       ------------------------------------------------------------
194c       (and devide by ptimestep -> true tendancies)
195
196        do l=1,nlayer
197         do ig = 1,nd
198          pdtgw(ig0+ig,l) = zzdtgw(ig,l)/ptimestep
199          pdugw(ig0+ig,l) = zzdugw(ig,l)/ptimestep
200          pdvgw(ig0+ig,l) = zzdvgw(ig,l)/ptimestep
201         enddo
202        enddo
203
204      ENDDO         !   (boucle jd=1, ndomain)
205
206      return
207      end
208
Note: See TracBrowser for help on using the repository browser.