/[MITgcm]/MITgcm/pkg/gridalt/make_phys_grid.F
ViewVC logotype

Annotation of /MITgcm/pkg/gridalt/make_phys_grid.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.12 - (hide annotations) (download)
Sun Aug 12 01:28:03 2012 UTC (11 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63r, checkpoint63s, checkpoint64, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, HEAD
Changes since 1.11: +107 -106 lines
includes GRIDALT_OPTIONS.h instead of CPP_OPTIONS.h

1 jmc 1.12 C $Header: /u/gcmpack/MITgcm/pkg/gridalt/make_phys_grid.F,v 1.11 2010/03/16 00:14:47 jmc Exp $
2 edhill 1.3 C $Name: $
3    
4 jmc 1.12 #include "GRIDALT_OPTIONS.h"
5 molod 1.1
6 jmc 1.12 SUBROUTINE MAKE_PHYS_GRID(drF,hfacC,im1,im2,jm1,jm2,Nr,
7     & nSx,nSy,i1,i2,j1,j2,bi,bj,Nrphys,Lbot,dpphys,numlevphys,nlperdyn)
8     C***********************************************************************
9     C SUBROUTINE MAKE_PHYS_GRID
10     C
11     C Purpose: Define the grid that the will be used to run the high-end
12     C atmospheric physics.
13     C
14     C Algorithm: Fit additional levels of some (~) known thickness in
15     C between existing levels of the grid used for the dynamics
16     C
17     C Need: Information about the dynamics grid vertical spacing
18     C
19     C Input: drF - delta r (p*) edge-to-edge
20     C hfacC - fraction of grid box above topography
21     C im1, im2 - beginning and ending i - dimensions
22     C jm1, jm2 - beginning and ending j - dimensions
23     C Nr - number of levels in dynamics grid
24     C nSx,nSy - number of processes in x and y direction
25     C i1, i2 - beginning and ending i - index to fill
26     C j1, j2 - beginning and ending j - index to fill
27     C bi, bj - x-dir and y-dir index of process
28     C Nrphys - number of levels in physics grid
29     C
30     C Output: dpphys - delta r (p*) edge-to-edge of physics grid
31     C numlevphys - number of levels used in the physics
32     C nlperdyn - physics level number atop each dynamics layer
33     C
34     C NOTES: 1) Pressure levs are built up from bottom, using p0, ps and dp:
35     C p(i,j,k)=p(i,j,k-1) + dp(k)*ps(i,j)/p0(i,j)
36     C 2) Output dp(s) are aligned to fit EXACTLY between existing
37     C levels of the dynamics vertical grid
38     C 3) IMPORTANT! This routine assumes the levels are numbered
39     C from the bottom up, ie, level 1 is the surface.
40     C IT WILL NOT WORK OTHERWISE!!!
41     C 4) This routine does NOT work for surface pressures less
42     C (ie, above in the atmosphere) than about 350 mb
43     C***********************************************************************
44    
45     IMPLICIT NONE
46    
47     integer im1,im2,jm1,jm2,Nr,nSx,nSy,Nrphys
48 molod 1.1 integer i1,i2,j1,j2,bi,bj
49     integer numlevphys
50 jmc 1.12 _RS hfacC(im1:im2,jm1:jm2,Nr,nSx,nSy)
51     _RL dpphys(im1:im2,jm1:jm2,Nrphys,nSx,nSy)
52 jmc 1.10 _RS drF(Nr)
53 jmc 1.12 integer Lbot(im1:im2,jm1:jm2,nSx,nSy)
54     integer nlperdyn(im1:im2,jm1:jm2,Nr,nSx,nSy)
55    
56 molod 1.1 integer i,j,L,Lbotij,Lnew
57 jmc 1.12 C Require 12 (or 15) levels near the surface (300 mb worth) for fizhi.
58     C the dp(s) are in the dptry arrays:
59 molod 1.4 integer ntry,ntry10,ntry40
60 molod 1.8 parameter (ntry10 = 12)
61     parameter (ntry40 = 12)
62     _RL dptry(15),dptry10(ntry10),dptry40(ntry40)
63     _RL bot_thick,bot_thick40
64 molod 1.4 _RL dptry_accum(15)
65     data dptry10/300.000,600.000,1000.000,1400.000,1700.000,2500.000,
66 jmc 1.12 & 2500.000,2500.000,2500.000,5000.000,5000.000,5000.000/
67 molod 1.8 data dptry40/300.000,600.000, 800.000, 800.000,1250.000,
68 jmc 1.12 & 1250.000,2500.000,2500.000,2500.000,2500.000,2500.000,
69     & 2500.000/
70 molod 1.8 data bot_thick40/20000.000/
71 molod 1.1 _RL deltap, dpstar_accum
72     integer nlbotmax, nstart, nlevs, nlphys, ndone
73 molod 1.9 _RL thindp
74 jmc 1.12
75 molod 1.4 if( (Nr.eq.10) .or. (Nr.eq.20) ) then
76     ntry = ntry10
77 molod 1.8 bot_thick = bot_thick40
78 molod 1.4 do L = 1,ntry
79     dptry(L) = dptry10(L)
80     enddo
81 molod 1.9 elseif((Nr.eq.40).or.(Nr.eq.46).or.(Nr.eq.70)) then
82 molod 1.4 ntry = ntry40
83 molod 1.8 bot_thick = bot_thick40
84 molod 1.4 do L = 1,ntry
85     dptry(L) = dptry40(L)
86     enddo
87     else
88     print *,' Dont know how to make fizhi grid '
89     stop
90     endif
91 molod 1.9
92     thindp=100.
93     if(Nr.eq.70)thindp=0.02
94 jmc 1.12
95 molod 1.1 do L = 1,Nr
96     do j = j1,j2
97     do i = i1,i2+1
98     nlperdyn(i,j,L,bi,bj) = 0
99     enddo
100     enddo
101     enddo
102 jmc 1.12
103     C Figure out how many physics levels there will be
104     C (need 12 between sfc and 300 mb above it - see how many
105     C there are in the dynamics if the surface pressure is at
106     C the sum of drF, ie, the maximum dynamics grid layers possible)
107 molod 1.1 nlevs = 0
108     dpstar_accum = 0.
109     do L = 1,Nr
110     dpstar_accum = dpstar_accum + drF(L)
111 molod 1.8 if(dpstar_accum.le.bot_thick) nlevs = nlevs+1
112 molod 1.1 enddo
113     numlevphys = Nr - nlevs + ntry + 1
114 jmc 1.12
115 molod 1.1 dptry_accum(1) = dptry(1)
116     do Lnew = 2,ntry
117     dptry_accum(Lnew) = dptry_accum(Lnew-1) + dptry(Lnew)
118     enddo
119 jmc 1.12
120     C do for each grid point:
121 molod 1.1 do j = j1,j2
122 molod 1.2 do i = i1,i2
123 molod 1.1 Lbotij = Lbot(i,j,bi,bj)
124 jmc 1.12
125     C Find the maximum number of physics levels to fit in the bottom level
126    
127 molod 1.1 nlbotmax = 0
128     do Lnew = 1,ntry
129 jmc 1.12 if ( (nlbotmax.eq.0) .and.
130     & (dptry_accum(Lnew).gt.(hfacC(i,j,Lbotij,bi,bj)*drF(Lbotij))))then
131 molod 1.1 nlbotmax = Lnew
132     endif
133     enddo
134     if(nlbotmax.eq.0)then
135     nlbotmax = ntry
136     endif
137 jmc 1.12
138     C See how many of the physics levs can fit in the bottom level
139    
140 molod 1.1 nlphys = 0
141     deltap = 0.
142     do Lnew = 1,nlbotmax
143 jmc 1.12 C Test to see if the next physics level fits, if yes, add it
144 molod 1.1 if((hfacC(i,j,Lbotij,bi,bj)*drF(Lbotij)).ge.
145 jmc 1.12 & deltap+dptry(Lnew))then
146 molod 1.1 nlphys = nlphys + 1
147     dpphys(i,j,nlphys,bi,bj) = dptry(Lnew)
148     deltap = deltap + dptry(Lnew)
149     else
150 jmc 1.12 C If the level does not fit, decide whether to make a new thinner
151     C one or make the one below a bit thicker
152 molod 1.1 if((dptry(Lnew-1)+(hfacC(i,j,Lbotij,bi,bj)*
153 jmc 1.12 & drF(Lbotij)-deltap)) .gt. (dptry(Lnew-1)*1.5) ) then
154     C Add a new thin layer
155 molod 1.1 nlphys = nlphys + 1
156 jmc 1.12 dpphys(i,j,nlphys,bi,bj) =
157     & (hfacC(i,j,Lbotij,bi,bj)*drF(Lbotij))-deltap
158 molod 1.1 else
159 jmc 1.12 C Make the one below thicker
160     dpphys(i,j,nlphys,bi,bj) = dpphys(i,j,nlphys,bi,bj) +
161     & (hfacC(i,j,Lbotij,bi,bj)*drF(Lbotij)-deltap)
162 molod 1.1 endif
163     deltap = deltap+(hfacC(i,j,Lbotij,bi,bj)*drF(Lbotij)-deltap)
164     endif
165     enddo
166 jmc 1.12
167 molod 1.1 nlperdyn(i,j,Lbotij,bi,bj) = nlphys
168 jmc 1.12
169     C Now proceed upwards - see how many physics levels fit in each
170     C subsequent dynamics level - go through all 12 required levels
171    
172 molod 1.1 do L = Lbotij+1,Nr
173     ndone = 0
174     if(nlphys.lt.ntry)then
175     deltap = 0.
176     nstart = nlphys + 1
177     do Lnew = nstart,ntry
178     if((hfacC(i,j,L,bi,bj)*drF(L)).ge.deltap+dptry(Lnew))then
179     nlphys = nlphys + 1
180     dpphys(i,j,nlphys,bi,bj) = dptry(Lnew)
181     deltap = deltap + dptry(Lnew)
182     ndone = 0
183     elseif (ndone.eq.0) then
184 jmc 1.12 C If the level does not fit, decide whether to make a new thinner
185     C one or make the one below a bit thicker
186 molod 1.1 ndone = 1
187     if( (dptry(Lnew-1)+(hfacC(i,j,L,bi,bj)*drF(L)-deltap))
188 jmc 1.12 & .gt. (dptry(Lnew-1)*1.5) ) then
189     C Add a new thin layer
190 molod 1.1 nlphys = nlphys + 1
191 jmc 1.12 dpphys(i,j,nlphys,bi,bj) =
192     & (hfacC(i,j,L,bi,bj)*drF(L))-deltap
193 molod 1.1 deltap = hfacC(i,j,L,bi,bj)*drF(L)
194     else
195 jmc 1.12 C Make the one below thicker
196 molod 1.1 dpphys(i,j,nlphys,bi,bj) = dpphys(i,j,nlphys,bi,bj) +
197 jmc 1.12 & (hfacC(i,j,L,bi,bj)*drF(L)-deltap)
198 molod 1.1 deltap = hfacC(i,j,L,bi,bj)*drF(L)
199     endif
200     endif
201     enddo
202 molod 1.2 C Need one more peice of logic - if we finished Lnew loop and
203     C now we are done adding new physics layers, we need to be sure
204     C that we are at the edge of a dynamics layer. if not, we need
205     C to add one more layer.
206     if(nlphys.ge.ntry)then
207     if(abs(deltap-hfacC(i,j,L-1,bi,bj)*drF(L-1)).gt.0.001)then
208     nlphys = nlphys + 1
209     dpphys(i,j,nlphys,bi,bj) = hfacC(i,j,L-1,bi,bj)*drF(L-1)
210 jmc 1.12 & - deltap
211 molod 1.2 endif
212     endif
213    
214 molod 1.1 elseif(nlphys.eq.ntry)then
215 jmc 1.12 C Mostly done with new layers - make sure we end at dynamics edge,
216     C if not, make one more thinner (thinner than dyn grid) layer
217 molod 1.1 if(abs(deltap-hfacC(i,j,L-1,bi,bj)*drF(L-1)).gt.0.001)then
218     nlphys = nlphys + 1
219 jmc 1.12 dpphys(i,j,nlphys,bi,bj) = hfacC(i,j,L-1,bi,bj)*drF(L-1)
220     & - deltap
221 molod 1.1 nlphys = nlphys + 1
222     dpphys(i,j,nlphys,bi,bj) = hfacC(i,j,L,bi,bj)*drF(L)
223     else
224     nlphys = nlphys + 1
225     dpphys(i,j,nlphys,bi,bj) = hfacC(i,j,L,bi,bj)*drF(L)
226     endif
227     else
228 jmc 1.12 C we are done adding new physics layers, just copy the rest
229     C of the dynamics grid onto the physics grid
230 molod 1.1 nlphys = nlphys + 1
231     dpphys(i,j,nlphys,bi,bj) = hfacC(i,j,L,bi,bj)*drF(L)
232     endif
233     nlperdyn(i,j,L,bi,bj) = nlphys
234     enddo
235 jmc 1.12
236     C All done adding layers - if we need more to make numlevphys, put
237     C them as thin (1 mb) layers near the top
238 molod 1.1 if(nlphys.lt.numlevphys)then
239     nlevs = numlevphys-nlphys
240 molod 1.9 dpphys(i,j,nlphys,bi,bj)=dpphys(i,j,nlphys,bi,bj)-thindp*nlevs
241 molod 1.1 do Lnew = nlphys+1,numlevphys
242 molod 1.9 dpphys(i,j,Lnew,bi,bj) = thindp
243 molod 1.1 enddo
244     nlperdyn(i,j,Nr,bi,bj) = numlevphys
245     endif
246 jmc 1.12 C END OF LOOP OVER GRID POINTS
247 molod 1.4
248 molod 1.1 enddo
249     enddo
250    
251     return
252     end

  ViewVC Help
Powered by ViewVC 1.1.22