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

Last change on this file since 171 was 38, checked in by emillour, 14 years ago

Ajout du modè Martien (mon LMDZ.MARS.BETA, du 28/01/2011) dans le rértoire mars, pour pouvoir suivre plus facilement les modifs.
EM

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