source: CPL/oasis3/trunk/src/mod/oasis3/src/coasts.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: 7.0 KB
Line 
1      SUBROUTINE coasts (plon, plat, kmsk, kmskval, klon, klat, kmesh)
2C
3C               *****************************
4C               * OASIS ROUTINE  -  LEVEL 3 *
5C               * -------------     ------- *
6C               *****************************
7C
8C**** *coasts* - locate coastal points where SST must be extrapolated
9C                when using surfmesh interpolation.
10C
11C     Purpose:
12C     -------
13C     This routine is designed to detect coastal points where there is
14C     mismatch between the atmosphere and ocean land sea masks and
15C     where this mismatch could result in the atmosphere (undesirably)
16C     'seeing' climatological SST's directly adjacent to ocean model SST's.
17C     Where this situation arises, suitable neighbours from where
18C     ocean model SST's may be extrapolated are located.
19C     
20C     NB: This is only for use with 'SURFMESH' interpolation of SST's.
21C
22C**   Interface:
23C     ---------
24C       *CALL*  *coasts*(plon, plat, kmsk, kmskval, klon, klat, kmesh)*
25C
26C     Input:
27C     -----
28C                plon    : target grid longitude array (real 2D) 
29C                plat    : target grid latitude array (real 2D) 
30C                klon    : number of longitude for target grid (integer)
31C                klat    : number of latitude for target grid (integer)
32C                kmsk    : target grid sea-land mask (integer 2D)
33C                kmskval : sea-land mask value (integer)
34C                kmesh   : overlap array (integer 2D)
35C
36C     Output:
37C     ------
38C     None
39C
40C     Workspace:
41C     ---------
42C         indx(4) - stores indices for neighbours
43C
44C     Externals:
45C     ---------
46C     None
47C
48C     History:
49C     -------
50C       Version   Programmer     Date      Description
51C       -------   ----------     ----      ----------- 
52C       1.1       R. Sutton      24/11/95  Original
53C       2.0       L. Terray      26/12/95  Modified: to suit OASIS 2.0
54C       2.3       S. Valcke      99/04/30  added: printing levels
55C
56C %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
57C
58C* --------------- Include files and USE of modules ---------------------------
59C
60      USE mod_kinds_oasis
61      USE mod_parameter
62      USE mod_coast
63      USE mod_unit
64      USE mod_smooth
65      USE mod_printing
66C
67C* ---------------------------- Argument declarations -------------------
68C
69      REAL (kind=ip_realwp_p) plon(klon,klat), plat(klon,klat)
70      INTEGER (kind=ip_intwp_p) kmsk(klon,klat), kmesh(klon,klat)
71C
72C* ---------------------------- Local declarations ----------------------
73C
74      INTEGER (kind=ip_intwp_p) indx(4)
75C
76C* ---------------------------- Poema verses ----------------------------
77C
78C %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
79C
80C
81C*    1. Initialization
82C        --------------
83C
84      IF (nlogprt .GE. 2) THEN
85          WRITE (UNIT = nulou,FMT = *) ' '
86          WRITE (UNIT = nulou,FMT = *) ' '
87          WRITE (UNIT = nulou,FMT = *) 
88     $    '           ROUTINE coasts  -  Level 3'
89          WRITE (UNIT = nulou,FMT = *) 
90     $    '           **************     *******'
91          WRITE (UNIT = nulou,FMT = *) ' '
92          WRITE (UNIT = nulou,FMT = *)
93     $     ' locate any coastal points where SST must be extrapolated'
94          WRITE (UNIT = nulou,FMT = *) ' '
95          WRITE (UNIT = nulou,FMT = *) ' '
96      ENDIF
97      ncoast = 0
98      indx(:)=0
99C
100C
101C*    2. Locate coastal points and neighbours from where to do extrapolation 
102C        -------------------------------------------------------------------
103C
104C* Loop between southern and northern boundaries   
105C (Range of latitude is set by parameters defined in blkdata.)
106C
107      DO 210 jj = nsltb+1, nnltb-1
108        DO 220 ji = 1, klon 
109C
110C* Find all grid squares which are ocean on the atmosphere grid but
111C  have no ocean underlying them on the ocean grid
112C
113          IF (kmsk(ji,jj) .NE.  kmskval .AND. 
114     $        kmesh(ji,jj) .EQ. 0) THEN
115              is = jj-1
116              in = jj+1
117              iw = ji-1
118              ie = ji+1
119C
120C* For an atmospheric domain that is periodic in longitude
121C
122              IF (iw .EQ. 0) iw = klon
123              IF (ie .GT. klon) ie = ie - klon
124C
125C* For a domain that is not periodic in longitude
126C          if (iw .eq. 0) iw=1
127C          if (ie .gt. klon) ie=klon
128C
129C* Search for neighbours from which ocean model SST may be extrapolated.
130C     
131              inbor = 0
132              IF (kmsk(iw,jj) .EQ. 0 .AND. kmesh(iw,jj) .NE. 0) THEN
133                  inbor = inbor + 1
134                  indx(inbor) = iw + (jj-1) * klon
135              ENDIF
136              IF (kmsk(ie,jj) .EQ. 0 .AND. kmesh(ie,jj) .NE. 0) THEN
137                  inbor = inbor + 1
138                  indx(inbor)= ie + (jj-1) * klon
139              ENDIF
140              IF (kmsk(ji,is) .EQ. 0 .AND. kmesh(ji,is) .NE. 0) THEN
141                  inbor = inbor + 1
142                  indx(inbor) = ji + (is-1) * klon
143              ENDIF
144              IF (kmsk(ji,in) .EQ. 0 .AND. kmesh(ji,in) .NE. 0) THEN
145                  inbor = inbor + 1
146                  indx(inbor) = ji + (in-1) * klon
147              ENDIF
148C
149C* Store location of coastal point, number of suitable
150C  neighbours and their locations.
151C  Note that if there are no neighbours the point must
152C  be an inland sea on the atmosphere grid for which 
153C  we do not want to extrapolate the ocean SST's
154C
155              IF (inbor .GT. 0) THEN
156                  ncoast = ncoast + 1
157                  npcoast(ncoast,1) = ji + (jj-1) * klon
158                  npcoast(ncoast,2) = inbor
159                  DO 230 jkbor = 1, inbor
160                    npcoast(ncoast,2+jkbor) = indx(jkbor)
161 230              CONTINUE
162              ENDIF
163          ENDIF
164 220    CONTINUE
165 210  CONTINUE
166C
167C
168C*    3. Writing results
169C        ---------------
170C
171      IF (nlogprt .GE. 2) THEN
172          WRITE (UNIT = nulou,FMT = *)
173     $    'Number of coastal ocean squares on the atmosphere grid '//
174     $    'for which there'
175          WRITE (UNIT = nulou,FMT = *)
176     $    'are no underlying ocean squares on the ocean grid = ',ncoast
177          WRITE (UNIT = nulou,FMT = *) ' '
178          WRITE (UNIT = nulou,FMT = *) ' '
179          WRITE (UNIT = nulou,FMT = *)
180     $    'Coordinates  nbor  Coordinates of neighbours '
181          do 310 jn = 1, ncoast
182            ii = icoor(npcoast(jn,1),klon)
183            ij = jcoor(npcoast(jn,1),klon)
184            WRITE (UNIT = nulou,FMT = 3100)
185     $       plon(ii,ij),plat(ii,ij),npcoast(jn,2),
186     $       (plon(icoor(npcoast(jn,jkbor),klon),
187     $            jcoor(npcoast(jn,jkbor),klon)),
188     $        plat(icoor(npcoast(jn,jkbor),klon),   
189     $            jcoor(npcoast(jn,jkbor),klon)),
190     $       jkbor=3,2+npcoast(jn,2))
191 310      CONTINUE
192      ENDIF
193C
194C* Formats
195C
196 3100 FORMAT (1X,'(',F5.1,',',F5.1,')  ',I1,
197     $       4X,4('(',F5.1,',',F5.1,') '))
198C
199C
200C*    4. End of routine
201C        --------------
202C
203      IF (nlogprt .GE. 2) THEN
204          WRITE (UNIT = nulou,FMT = *) ' '
205          WRITE (UNIT = nulou,FMT = *)
206     $    '           --------- End of routine coasts ---------'
207          CALL FLUSH (nulou)
208      ENDIF
209      RETURN
210      END
211
212
Note: See TracBrowser for help on using the repository browser.