source: CPL/oasis3/trunk/src/mod/oasis3/src/glored.f @ 1677

Last change on this file since 1677 was 1677, checked in by aclsce, 12 years ago

Imported oasis3 (tag ipslcm5a) from cvs server to svn server (igcmg project).

File size: 5.2 KB
Line 
1      SUBROUTINE glored (pzgg, pworkgr, klon, klat, ktronca)
2C*****
3C               *****************************
4C               * OASIS ROUTINE  -  LEVEL 3 *
5C               * -------------     ------- *
6C               *****************************
7C
8C**** *glored* - Global gaussian grid transformation 
9C
10C     Purpose:
11C     -------
12C     Linear interpolation of field from full gaussian grid to reduced grid
13C
14C     N.B: It is assumed that a preprocessing of the field on the full grid
15C          was done to allocate ocean values to land points as no mask is used
16C          in this routine. 
17C
18C**   Interface:
19C     ---------
20C       *CALL*  *glored (pzgg, pworkgr, klon, klat, ktronca)*
21C
22C     Input:
23C     -----
24C                pzgg    : field on global grid (real 2D)
25C                pworkgr : array to store field on global grid (real 2D)
26C                klon    : number of longitudes of global grid
27C                klat    : number of latitudes of both grids
28C                ktronca : truncature of gaussian grid
29C                   
30C     Output:
31C     ------
32C                pzgg: field on reduced grid (real 2D)
33C
34C     Workspace:
35C     ---------
36C     inip
37C
38C     Externals:
39C     ---------
40C     None
41C
42C     Reference:
43C     ---------
44C     See OASIS manual (1995)
45C
46C     History:
47C     -------
48C       Version   Programmer     Date      Description
49C       -------   ----------     ----      ----------- 
50C       1.0       L. Terray      94/01/01  created
51C       2.0       L. Terray      95/09/01  modified
52C       2.3       L. terray      99/03/01  bug corrected: inip DIMENSION
53C       2.3       S. Valcke      99/03/16  modified for T213 and T319
54C       2.3       S. Valcke      99/03/26  changed troncature for number of 
55C                                          latitude between equator and pole
56C       2.3       S. Valcke      99/04/30  added: printing levels
57C
58C %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
59C
60C* ---------------------------- Include files ---------------------------
61C
62      USE mod_kinds_oasis
63      USE mod_unit
64      USE mod_gauss
65      USE mod_printing
66C
67C* ---------------------------- Argument declarations -------------------
68C
69
70      REAL (kind=ip_realwp_p) pzgg(klon,klat), pworkgr(klon*klat)
71      INTEGER (kind=ip_intwp_p) inip(320)
72C
73C* ---------------------------- Poema verses ----------------------------
74C
75C %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
76C
77C*    1. Initialization
78C        --------------
79C
80      IF (nlogprt .GE. 2) THEN
81          WRITE (UNIT = nulou,FMT = *) ' '
82          WRITE (UNIT = nulou,FMT = *) ' '
83          WRITE (UNIT = nulou,FMT = *) 
84     $    '           ROUTINE glored  -  Level 3'
85          WRITE (UNIT = nulou,FMT = *) 
86     $    '           **************     *******'
87          WRITE (UNIT = nulou,FMT = *) ' '
88          WRITE (UNIT = nulou,FMT = *) ' Go from global to reduced grid'
89          WRITE (UNIT = nulou,FMT = *) ' '
90          WRITE (UNIT = nulou,FMT = *) ' '
91      ENDIF
92      CALL izero(inip,320)
93C
94C
95C*    2. Full to reduced linear interpolation 
96C        ------------------------------------
97C
98C
99C* get number of longitudes by latitude circle
100C
101      IF (ktronca .EQ. 16) THEN
102          DO 210 ji = 1, ktronca
103            inip(ji) = ninip16(ji)
104 210      CONTINUE
105        ELSE IF (ktronca .EQ. 24)  THEN
106          DO 220 ji = 1, ktronca
107            inip(ji) = ninip24(ji)
108 220      CONTINUE
109        ELSE IF (ktronca .EQ. 32)  THEN
110          DO 230 ji = 1, ktronca 
111            inip(ji) = ninip32(ji)
112 230      CONTINUE
113        ELSE IF (ktronca .EQ. 48)  THEN
114          DO 240 ji = 1, ktronca 
115            inip(ji) = ninip48(ji)
116 240      CONTINUE   
117        ELSE IF (ktronca .EQ. 80)  THEN
118          DO 250 ji = 1, ktronca 
119            inip(ji) = ninip80(ji)
120 250      CONTINUE
121        ELSE IF (ktronca .EQ. 160)  THEN
122          DO 255 ji = 1, ktronca 
123            inip(ji) = ninip160(ji)
124 255      CONTINUE
125        ELSE
126          CALL prtout
127     $          ('WARNING!!! Oasis cannot treat this grid with 2*NO
128     $          latitude lines with NO = ', ktronca, 2)
129          CALL prtout('Implement data for NO =', ktronca, 2)
130          CALL HALTE('STOP in glored')
131      ENDIF
132C
133C* Extend inip array to both hemispheres
134C
135      DO 260 ji = klat/2 + 1, klat
136        inip(ji) = inip(klat - ji + 1)
137 260  CONTINUE
138C
139C* Do the interpolation global to reduced
140C
141      indice = 0
142      DO 270 jk = 1, klat
143        DO 280 ji = 1, inip(jk)
144          zxi = 1 + ((ji - 1) * klon) / FLOAT(inip(jk))
145          im = INT(zxi)
146          zdx = zxi - im
147          im = 1 + MOD(im + klon - 1,klon)
148          ip = 1 + MOD(im,klon)
149          pworkgr(indice + ji) = pzgg(im,jk) * (1.-zdx) 
150     $                      + pzgg(ip,jk) * zdx
151 280    CONTINUE
152        indice = indice + inip(jk)
153 270  CONTINUE
154C
155C* Assign reduced grid values to array pzgg
156C
157      DO 290 jj = 1, klat
158        DO 295 ji = 1, klon
159         pzgg(ji,jj) = pworkgr(klon*(jj-1)+ji) 
160 295   CONTINUE
161 290  CONTINUE
162C
163C
164C*    3. End of routine
165C        --------------
166C
167      IF (nlogprt .GE. 2) THEN
168          WRITE (UNIT = nulou,FMT = *) ' '
169          WRITE (UNIT = nulou,FMT = *) 
170     $    '          --------- End of routine glored ---------'
171          CALL FLUSH (nulou)
172      ENDIF
173      RETURN
174      END
175 
Note: See TracBrowser for help on using the repository browser.