/[MITgcm]/MITgcm/pkg/fizhi/fizhi_init_veg.F
ViewVC logotype

Contents of /MITgcm/pkg/fizhi/fizhi_init_veg.F

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


Revision 1.25 - (show annotations) (download)
Fri Mar 23 20:23:16 2012 UTC (12 years, 2 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, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, 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.24: +5 -1 lines
STOP if _BYTESWAPIO is defined (does not work for sequential acces file)

1 C $Header: /u/gcmpack/MITgcm/pkg/fizhi/fizhi_init_veg.F,v 1.24 2012/03/22 14:22:00 jmc Exp $
2 C $Name: $
3
4 #include "FIZHI_OPTIONS.h"
5
6 SUBROUTINE FIZHI_INIT_VEG(myThid,vegdata,im,jm,nSx,nSy,Nxg,Nyg,
7 & maxtyp,nchp,nchptot,nchpland,lons,lats,surftype,tilefrac,
8 & igrd,ityp,chfr,chlt,chlon)
9 C***********************************************************************
10 C Subroutine fizhi_init_veg - routine to read in the land surface types,
11 C interpolate to the models grid, and set up tile space for use by
12 C the land surface model, the albedo calculation and the surface
13 C roughness calculation.
14 C
15 C INPUT:
16 C
17 C myThid - thread number (processor number)
18 C vegdata - Character*40 Vegetation Dataset name
19 C im - longitude dimension
20 C jm - latitude dimension (number of lat. points)
21 C nSx - Number of processors in x-direction
22 C nSy - Number of processors in y-direction
23 C maxtyp - maximum allowable number of land surface types per grid box
24 C nchp - integer per-processor number of tiles in tile space
25 C lons - longitude in degrees [im,jm,nSx,nSy]
26 C lats - latitude in degrees [im,jm,nSx,nSy]
27 C
28 C OUTPUT:
29 C
30 C surftype - integer array of land surface types [im,jm,maxtyp,nSx,nSy]
31 C tilefrac - real array of corresponding land surface type fractions
32 C [im,jm,maxtyp,nSx,nSy]
33 C igrd - integer array in tile space of grid point number for each
34 C tile [nchp,nSx,nSy]
35 C ityp - integer array in tile space of land surface type for each
36 C tile [nchp,nSx,nSy]
37 C chfr - real array in tile space of land surface type fraction for
38 C each tile [nchp,nSx,nSy]
39 C
40 C NOTES:
41 C Vegetation type as follows:
42 C 1: BROADLEAF EVERGREEN TREES
43 C 2: BROADLEAF DECIDUOUS TREES
44 C 3: NEEDLELEAF TREES
45 C 4: GROUND COVER
46 C 5: BROADLEAF SHRUBS
47 C 6: DWARF TREES (TUNDRA)
48 C 7: BARE SOIL
49 C 8: DESERT
50 C 9: GLACIER
51 C 10: DARK DESERT
52 C 100: OCEAN
53 C***********************************************************************
54 IMPLICIT NONE
55 #include "EEPARAMS.h"
56
57 INTEGER myThid,im,jm,maxtyp,nchp,nSx,nSy,Nxg,Nyg
58 INTEGER nchptot(nSx,nSy), nchpland(nSx,nSy)
59 INTEGER surftype(im,jm,maxtyp,nSx,nSy)
60 INTEGER igrd(nchp,nSx,nSy),ityp(nchp,nSx,nSy)
61 _RL tilefrac(im,jm,maxtyp,nSx,nSy)
62 _RL lats(im,jm,nSx,nSy), lons(im,jm,nSx,nSy)
63 _RL chfr(nchp,nSx,nSy),chlt(nchp,nSx,nSy),chlon(nchp,nSx,nSy)
64
65 C- local variables:
66 CHARACTER*40 vegdata
67 INTEGER i,j,k,bi,bj
68
69 INTEGER imdata,jmdata,Nxgdata,Nygdata
70 INTEGER biglobal,bjglobal
71 INTEGER ierr1,kveg
72 INTEGER*4 im_32, jm_32, Nxg_32, Nyg_32
73 INTEGER*4 iveg_32(im,jm,maxtyp,Nxg,Nyg)
74 REAL*4 veg_32(im,jm,maxtyp,Nxg,Nyg)
75
76 WRITE(standardMessageUnit,'(2A)') ' FIZHI_INIT_VEG: ',
77 & 'defining surface type and fraction: ----------------------'
78
79 #ifdef _BYTESWAPIO
80 C using MDS_BYTESSWAP for sequential acces file does not work
81 STOP 'ABNORMAL END: S/R FIZHI_INIT_VEG'
82 #endif
83 CALL MDSFINDUNIT( kveg, myThid )
84 close(kveg)
85 open(kveg,file=vegdata,form='unformatted',access='sequential',
86 & iostat=ierr1)
87 if( ierr1.eq.0 ) then
88 rewind(kveg)
89 read(kveg)im_32,jm_32,Nxg_32,Nyg_32,iveg_32,veg_32
90 else
91 print *
92 print *, 'Veg Dataset: ',vegdata,' not found!'
93 print *
94 call exit(101)
95 endif
96 close(kveg)
97 #if defined( _BYTESWAPIO ) && defined( ALLOW_MDSIO )
98 CALL MDS_BYTESWAPI4(1,im_32)
99 CALL MDS_BYTESWAPI4(1,jm_32)
100 CALL MDS_BYTESWAPI4(1,nxg_32)
101 CALL MDS_BYTESWAPI4(1,nyg_32)
102 #endif
103
104 IF (myThid.EQ.1) THEN
105 imdata = im_32
106 jmdata = jm_32
107 Nxgdata = Nxg_32
108 Nygdata = Nyg_32
109 if( (imdata.ne.im) .or. (jmdata.ne.jm) .or.
110 & (Nxgdata.ne.Nxg) .or. (Nygdata.ne.Nyg) ) then
111 print *
112 print *, 'Veg Data Resolution is Incorrect! '
113 print *,' Model Res: ',im,'x',jm,' Data Res: ',imdata,'x',jmdata
114 print *,' Model Nxg Nyg: ',Nxg,' ',Nyg,
115 & ' Data Nxg Nyg: ',Nxgdata,' ',Nygdata
116 print *
117 call exit(102)
118 endif
119 ENDIF
120
121 DO bj = myByLo(myThid), myByHi(myThid)
122 DO bi = myBxLo(myThid), myBxHi(myThid)
123
124 biglobal=bi+(myXGlobalLo-1)/im
125 bjglobal=bj+(myYGlobalLo-1)/jm
126 #if defined( _BYTESWAPIO ) && defined( ALLOW_MDSIO )
127 CALL MDS_BYTESWAPR4( im*jm*maxtyp,
128 & veg_32(1,1,1,biglobal,bjglobal) )
129 CALL MDS_BYTESWAPI4( im*jm*maxtyp,
130 & iveg_32(1,1,1,biglobal,bjglobal) )
131 #endif
132 do k = 1,maxtyp
133 do j = 1,jm
134 do i = 1,im
135 surftype(i,j,k,bi,bj) = iveg_32(i,j,k,biglobal,bjglobal)
136 tilefrac(i,j,k,bi,bj) = veg_32(i,j,k,biglobal,bjglobal)
137 enddo
138 enddo
139 enddo
140
141 ENDDO
142 ENDDO
143
144 C create chip arrays for :
145 C igrd : grid index
146 C ityp : veg. type
147 C chfr : vegetation fraction
148 C chlon: chip longitude
149 C chlt : chip latitude
150
151 C nchpland<=nchptot is the actual number of land chips
152 WRITE(standardMessageUnit,'(2A)') ' FIZHI_INIT_VEG: ',
153 & 'setting surface Tiles:'
154
155 DO bj = myByLo(myThid), myByHi(myThid)
156 DO bi = myBxLo(myThid), myBxHi(myThid)
157
158 C- initialise grid index array:
159 do i=1,nchp
160 igrd(i,bi,bj) = 1
161 enddo
162
163 C- land points:
164 nchpland(bi,bj) = 0
165 do k=1,maxtyp
166 do j=1,jm
167 do i=1,im
168 if(surftype(i,j,k,bi,bj).lt.100 .and.
169 & tilefrac(i,j,k,bi,bj).gt.0.) then
170 nchpland(bi,bj) = nchpland(bi,bj) + 1
171 igrd (nchpland(bi,bj),bi,bj) = i + (j-1)*im
172 ityp (nchpland(bi,bj),bi,bj) = surftype(i,j,k,bi,bj)
173 chfr (nchpland(bi,bj),bi,bj) = tilefrac(i,j,k,bi,bj)
174 chlon(nchpland(bi,bj),bi,bj) = lons(i,j,bi,bj)
175 chlt (nchpland(bi,bj),bi,bj) = lats(i,j,bi,bj)
176 endif
177 enddo
178 enddo
179 enddo
180
181 C- ocean points:
182 nchptot(bi,bj) = nchpland(bi,bj)
183 do k=1,maxtyp
184 do j=1,jm
185 do i=1,im
186 if(surftype(i,j,k,bi,bj).ge.100 .and.
187 & tilefrac(i,j,k,bi,bj).gt.0.) then
188 nchptot(bi,bj) = nchptot(bi,bj) + 1
189 igrd (nchptot(bi,bj),bi,bj) = i + (j-1)*im
190 ityp (nchptot(bi,bj),bi,bj) = surftype(i,j,k,bi,bj)
191 chfr (nchptot(bi,bj),bi,bj) = tilefrac(i,j,k,bi,bj)
192 chlon(nchptot(bi,bj),bi,bj) = lons(i,j,bi,bj)
193 chlt (nchptot(bi,bj),bi,bj) = lats(i,j,bi,bj)
194 endif
195 enddo
196 enddo
197 enddo
198
199 WRITE(standardMessageUnit,'(2(A,I4),2(A,I10))') ' bi=', bi,
200 & ', bj=', bj, ', # of Land Tiles=', nchpland(bi,bj),
201 & ', Total # of Tiles=', nchptot(bi,bj)
202
203 ENDDO
204 ENDDO
205
206 WRITE(standardMessageUnit,'(2A)') ' FIZHI_INIT_VEG: done'
207
208 RETURN
209 END

  ViewVC Help
Powered by ViewVC 1.1.22