source: branches/ORCHIDEE_EXT/ORCHIDEE/src_global/grid.f90 @ 183

Last change on this file since 183 was 64, checked in by didier.solyga, 14 years ago

Import first version of ORCHIDEE_EXT

File size: 16.9 KB
Line 
1
2!! This module define variables for the grid to gathered points.
3!!
4!! @call sechiba_main
5!! @Version : $Revision: 1.8 $, $Date: 2009/01/28 08:32:45 $
6!!
7!! $Header: /home/ssipsl/CVSREP/ORCHIDEE/src_global/grid.f90,v 1.8 2009/01/28 08:32:45 ssipsl Exp $
8!!
9!! @author Marie-Alice Foujols, Jan Polcher and Martial Mancip
10!!
11!!
12!f90doc MODULEgrid
13MODULE grid
14
15  USE defprec
16  USE constantes
17  USE parallel
18
19  IMPLICIT NONE
20
21  !
22  ! PARAMETERS
23  ! default resolution (m)
24  REAL(r_std), PARAMETER :: default_resolution = 250000.
25  !
26  !
27  ! VARIABLES
28  !
29  ! Global map or not.
30  ! There is little change that if iim <=2 and jjm <= 2 that we have global grid.
31  ! Furthermore using the second line allows to avoid pole problems for global grids
32  LOGICAL, SAVE                                      :: global = .FALSE.
33  !
34  !-
35  !- Variable to help describe the grid
36  !- once the points are gathered.
37  !-
38  !! Limits of the domain
39  REAL(r_std), SAVE                                   :: limit_west, limit_east, &
40       &                                                limit_north, limit_south
41  !-
42  !! Geographical coordinates
43  REAL(r_std), ALLOCATABLE, DIMENSION (:,:), SAVE     :: lalo
44  !! index  of land points
45  INTEGER, ALLOCATABLE, DIMENSION (:), SAVE          :: ilandindex,jlandindex
46  !-
47  !! Fraction of continents.
48  REAL(r_std), ALLOCATABLE, DIMENSION (:), SAVE       :: contfrac
49  !
50  ! indices of the 4 neighbours of each grid point (1=N, 2=E, 3=S, 4=W)
51  !   a zero or negative index means that this neighbour is not a land point
52  INTEGER(i_std), ALLOCATABLE, DIMENSION (:,:), SAVE :: neighbours
53  !
54  ! resolution at each grid point in m (1=E-W, 2=N-S)
55  ! (size in x an y of the grid)
56  REAL(r_std), ALLOCATABLE, DIMENSION (:,:), SAVE     :: resolution
57  REAL(r_std), DIMENSION(2), SAVE :: min_resol,max_resol
58  REAL(r_std), ALLOCATABLE, DIMENSION (:), SAVE     :: area
59  !
60  !
61  ! Get the direction of the grid
62  !
63  CHARACTER(LEN=2), DIMENSION(2), SAVE, PRIVATE      :: grid_dir
64  !
65  ! Rose gives the geographical direction for the various index increments
66  ! The following corespondences exist
67  !                       WE&NS  WE&SN and so on !
68  ! rose(1) = i+0 & j-1    NN     SS
69  ! rose(2) = i+1 & j-1    NE     SE
70  ! rose(3) = i+1 & j+0    EE     EE
71  ! rose(4) = i+1 & j+1    SE     NE
72  ! rose(5) = i+0 & j+1    SS     NN
73  ! rose(6) = i-1 & j+1    SW     NW
74  ! rose(7) = i-1 & j+0    WW     WW
75  ! rose(8) = i-1 & j-1    NW     SW
76  INTEGER(i_std), DIMENSION(8), SAVE, PRIVATE        :: rose
77  !
78  ! The calendar
79  CHARACTER(LEN=20), SAVE         :: calendar_str
80  !
81  ! The date
82  REAL(r_std)                     :: in_julian
83  ! Diff with day 0
84  REAL(r_std)                     :: julian_diff
85  !
86  INTEGER(i_std)                  :: year, month, day
87  REAL(r_std)                     :: sec
88  !
89  ! month_len (d)
90  INTEGER(i_std)                  :: month_len
91  !
92  ! year length (d)
93  INTEGER(i_std), SAVE            :: year_length=0
94  !
95  ! Ration between calendar year in days (ie 360d or 365d ...) to gregorian year length
96  REAL(r_std) :: year_spread
97  !
98CONTAINS
99  !
100  !f90doc CONTAINS
101  !
102  !
103  SUBROUTINE init_grid ( npts )
104    !
105    ! 0 interface
106    !
107    IMPLICIT NONE
108    !
109    ! 0.1 input  !
110   
111    ! Domain size
112    INTEGER(i_std), INTENT(in)                                 :: npts !! Number of local continental points
113    !
114    !  Create the internal coordinate table
115    !
116    IF ( (.NOT.ALLOCATED(lalo))) THEN
117       ALLOCATE(lalo(npts,2))
118       lalo(:,:) = val_exp
119    ENDIF
120    !-
121    !- Store variable to help describe the grid
122    !- once the points are gathered.
123    !-
124    IF ( (.NOT.ALLOCATED(neighbours))) THEN
125       ALLOCATE(neighbours(npts,8))
126       neighbours(:,:) = -999999
127    ENDIF
128    IF ( (.NOT.ALLOCATED(resolution))) THEN
129       ALLOCATE(resolution(npts,2))
130       resolution(:,:) = val_exp
131    ENDIF
132    IF ( (.NOT.ALLOCATED(area))) THEN
133       ALLOCATE(area(npts))
134       area(:) = val_exp
135    ENDIF
136    !
137    !- Store the fraction of the continents only once so that the user
138    !- does not change them afterwards.
139    !
140    IF ( (.NOT.ALLOCATED(contfrac))) THEN
141       ALLOCATE(contfrac(npts))
142       contfrac(:) = val_exp
143    ENDIF
144    !
145    ! Allocation of index coordinates
146    IF (.NOT. ALLOCATED(ilandindex)) THEN
147       ALLOCATE(ilandindex(npts),jlandindex(npts))
148       ilandindex(:) = -10000000
149       jlandindex(:) = -10000000
150    ENDIF
151    !
152  END SUBROUTINE init_grid
153
154  SUBROUTINE grid_stuff (npts_glo, iim, jjm, grid_lon, grid_lat, kindex)
155    !
156    ! 0 interface
157    !
158    IMPLICIT NONE
159    !
160    ! 0.1 input  !
161   
162    ! Domain size
163    INTEGER(i_std), INTENT(in)                                 :: npts_glo
164    ! Size of cartesian grid
165    INTEGER(i_std), INTENT(in)                                 :: iim, jjm
166    ! Longitudes on cartesian grid
167    REAL(r_std), DIMENSION(iim,jjm), INTENT(in)                 :: grid_lon
168    ! Latitudes on cartesian grid
169    REAL(r_std), DIMENSION(iim,jjm), INTENT(in)                 :: grid_lat
170    ! Index of land point on 2D map (in local position)
171    INTEGER(i_std), DIMENSION(:), INTENT(in)                :: kindex   
172    !
173    ! 0.3 local
174    !
175    ! Index of land point on 2D map (in global position)
176    INTEGER, ALLOCATABLE, DIMENSION (:)                        :: index_p
177    !
178    ! which STOMATE point corresponds to the given point on the cartesian grid
179    INTEGER(i_std), DIMENSION(iim,jjm)                   :: correspondance
180    ! cosine of the latitude
181    REAL(r_std)                                           :: coslat
182    ! number of points where default resolution is used
183    INTEGER(i_std)                                       :: ndefault_lon, ndefault_lat
184    ! Indices
185    INTEGER(i_std)                                       :: i,ip,jp, imm1, imp1, imm1l, imp1l, ii
186    !
187    INTEGER(i_std), SAVE                           :: bavard=2
188   
189    ! =========================================================================
190   
191
192
193    IF ( bavard .GE. 4 ) WRITE(numout,*) 'Entering grid_stuff'
194
195    ! default resolution
196    IF ( bavard .GT. 1 ) WRITE(numout,*) 'grid stuff: default resolution (m): ',default_resolution
197    !
198    !-
199    IF (is_root_prc) THEN
200       ! Check if we have a global map or not.
201       ! There is little change that if iim <=2 and jjm <= 2 that we have global grid.
202       ! Furthermore using the second line allows to avoid pole problems for global grids
203       IF (iim <= 2 .OR. jjm <= 2) THEN
204          global = .FALSE.
205       ELSE
206          ! We assume here that the longitude is in increasing order and in degrees.
207          IF ( grid_lon(iim,2)-grid_lon(1,2) >= 360. - (grid_lon(2,2)-grid_lon(1,2)) ) THEN
208             global = .TRUE.
209          ENDIF
210       ENDIF
211       !
212       ! Get the direction of the grid
213       !
214       IF ( iim > 1 ) THEN
215          IF ( grid_lon(1,1) <= grid_lon(2,1) ) THEN
216             grid_dir(1) = 'WE'
217          ELSE
218             grid_dir(1) = 'EW'
219          ENDIF
220       ELSE
221          grid_dir(1) = 'WE'
222       ENDIF
223       !
224       IF ( jjm > 1 ) THEN
225          IF ( grid_lat(1,1) >= grid_lat(1,2) ) THEN
226             grid_dir(2) = 'NS'
227          ELSE
228             grid_dir(2) = 'SN'
229          ENDIF
230       ELSE
231          grid_dir(2) = 'NS'
232       ENDIF
233       !
234       !! WRITE(numout,*) 'Longitude direction :', grid_dir(1)
235       !! WRITE(numout,*) 'Latitude  direction :', grid_dir(2)
236       !
237       ndefault_lon = 0
238       ndefault_lat = 0
239       ! initialize output
240       neighbours_g(:,:) = -1
241       resolution_g(:,:) = 0.
242       min_resol(:) = 1.e6
243       max_resol(:) = -1.
244       
245       correspondance(:,:) = -1
246       DO i = 1, npts_glo         
247          !
248          ! 1 find numbers of the latitude and longitude of each point
249          !
250         
251          ! index of latitude
252          jp = INT( (index_g(i)-1) /iim ) + 1
253         
254          ! index of longitude
255          ip = index_g(i) - ( jp-1 ) * iim
256          !
257          !correspondance(ip,jp) = kindex(i)
258          !
259          correspondance(ip,jp) = i
260
261       ENDDO
262 
263       !
264       ! Get the "wind rose" for the various orientation of the grid
265       !
266       IF ( grid_dir(1) .EQ. 'WE' .AND.  grid_dir(2) .EQ. 'NS' ) THEN
267          rose(1) = 1
268          rose(2) = 2
269          rose(3) = 3
270          rose(4) = 4
271          rose(5) = 5
272          rose(6) = 6
273          rose(7) = 7
274          rose(8) = 8
275       ELSE IF ( grid_dir(1) .EQ. 'EW' .AND.  grid_dir(2) .EQ. 'NS' ) THEN
276          rose(1) = 1
277          rose(2) = 8
278          rose(3) = 7
279          rose(4) = 6
280          rose(5) = 5
281          rose(6) = 4
282          rose(7) = 3
283          rose(8) = 2
284       ELSE IF ( grid_dir(1) .EQ. 'WE' .AND.  grid_dir(2) .EQ. 'SN' ) THEN
285          rose(1) = 5
286          rose(2) = 4
287          rose(3) = 3
288          rose(4) = 2
289          rose(5) = 1
290          rose(6) = 8
291          rose(7) = 7
292          rose(8) = 6
293       ELSE IF ( grid_dir(1) .EQ. 'EW' .AND.  grid_dir(2) .EQ. 'SN' ) THEN
294          rose(1) = 5
295          rose(2) = 6
296          rose(3) = 7
297          rose(4) = 8
298          rose(5) = 1
299          rose(6) = 2
300          rose(7) = 3
301          rose(8) = 4
302       ELSE
303          WRITE(numout,*) 'We can not be here'
304          STOP 'grid_stuff'
305       ENDIF
306
307       DO i = 1, npts_glo
308
309          ! index of latitude
310          jp = INT( (index_g(i)-1) /iim ) + 1
311         
312          ! index of longitude
313          ip = index_g(i) - ( jp-1 ) * iim
314         
315          !
316          ! 2 resolution
317          !
318         
319          !
320          ! 2.1 longitude
321          !
322         
323          ! prevent infinite resolution at the pole
324          coslat = MAX( COS( grid_lat(ip,jp) * pi/180. ), 0.001 )     
325          IF ( iim .GT. 1 ) THEN
326             
327             IF ( ip .EQ. 1 ) THEN
328                resolution_g(i,1) = &
329                     ABS( grid_lon(ip+1,jp) - grid_lon(ip,jp) ) * &
330                     pi/180. * R_Earth * coslat
331             ELSEIF ( ip .EQ. iim ) THEN
332                resolution_g(i,1) = &
333                     ABS( grid_lon(ip,jp) - grid_lon(ip-1,jp) ) * &
334                     pi/180. * R_Earth * coslat
335             ELSE
336                resolution_g(i,1) = &
337                     ABS( grid_lon(ip+1,jp) - grid_lon(ip-1,jp) )/2. *&
338                     pi/180. * R_Earth * coslat
339             ENDIF
340             
341          ELSE
342             
343             resolution_g(i,1) = default_resolution
344             
345             ndefault_lon = ndefault_lon + 1
346
347          ENDIF
348
349          !
350          ! 2.2 latitude
351          !
352         
353          IF ( jjm .GT. 1 ) THEN
354
355             IF ( jp .EQ. 1 ) THEN
356                resolution_g(i,2) = &
357                     ABS( grid_lat(ip,jp) - grid_lat(ip,jp+1) ) * &
358                     pi/180. * R_Earth
359             ELSEIF ( jp .EQ. jjm ) THEN
360                resolution_g(i,2) = &
361                     ABS( grid_lat(ip,jp-1) - grid_lat(ip,jp) ) * &
362                     pi/180. * R_Earth
363             ELSE
364                resolution_g(i,2) = &
365                     ABS( grid_lat(ip,jp-1) - grid_lat(ip,jp+1) )/2. *&
366                     pi/180. * R_Earth
367             ENDIF
368             
369          ELSE
370             
371             resolution_g(i,2) = default_resolution
372             
373             ndefault_lat = ndefault_lat + 1
374             
375          ENDIF
376          min_resol(1) = MIN(resolution_g(i,1),min_resol(1))
377          min_resol(2) = MIN(resolution_g(i,2),min_resol(2))
378          max_resol(1) = MAX(resolution_g(i,1),max_resol(1))
379          max_resol(2) = MAX(resolution_g(i,2),max_resol(2))
380
381          area_g(i) = resolution_g(i,1)*resolution_g(i,2)
382
383          !
384          ! 3 find neighbours
385          !     
386          imm1 = 0
387          IF ( ip .GT. 1 ) THEN
388             imm1 = ip - 1
389          ELSEIF ( global ) THEN
390             imm1 = iim
391          ENDIF
392         
393          imp1 = 0
394          IF ( ip .LT. iim ) THEN
395             imp1 = ip + 1
396          ELSEIF ( global ) THEN
397             imp1 = 1
398          ENDIF
399          !
400          ! East and West
401          !
402          IF ( imp1 > 0 ) THEN
403             neighbours_g(i,rose(3)) = correspondance(imp1,jp)
404          ELSE
405             neighbours_g(i,rose(3)) = -1
406          ENDIF
407          IF ( imm1 > 0 ) THEN
408             neighbours_g(i,rose(7)) = correspondance(imm1,jp)
409          ELSE
410             neighbours_g(i,rose(7)) = -1
411          ENDIF
412          !
413          ! North
414          !
415          IF ( jp .GT. 1 ) THEN
416
417             neighbours_g(i,rose(1)) = correspondance(ip,jp-1)
418             IF ( imp1 > 0 ) THEN
419                neighbours_g(i,rose(2)) = correspondance(imp1,jp-1)
420             ELSE
421                neighbours_g(i,rose(2)) = -1
422             ENDIF
423             IF ( imm1 > 0 ) THEN
424                neighbours_g(i,rose(8)) = correspondance(imm1,jp-1)
425             ELSE
426                neighbours_g(i,rose(8)) = -1
427             ENDIF
428
429          ELSE
430             IF ( global ) THEN
431               
432                ! special treatment for the pole if we are really in a 2d grid
433               
434                IF ( ( iim .GT. 1 ) .AND. ( jjm .GT. 1 ) ) THEN
435                   !
436                   ii = MOD(ip+iim/2-1,iim)+1
437                   imm1l = ii - 1
438                   IF ( imm1l .LT. 1 ) imm1l = iim
439                   imp1l = ii + 1
440                   IF ( imp1l .GT. iim ) imp1l = 1
441                   !
442                   IF ( ABS( ( grid_lat(ip,jp) ) - 90. ) .LT. min_sechiba ) THEN
443                      ! the grid point sits exactly on the pole. The neighbour is situated
444                   ! at a lower latitude.
445                      neighbours_g(i,rose(1)) = correspondance( ii, jp+1 )
446                      neighbours_g(i,rose(2)) = correspondance( imm1l, jp+1 )
447                      neighbours_g(i,rose(8)) = correspondance( imp1l, jp+1 )
448                   ELSE
449                      ! look across the North Pole
450                      neighbours_g(i,rose(1)) = correspondance( ii, jp )
451                      neighbours_g(i,rose(2)) = correspondance( imm1l, jp )
452                      neighbours_g(i,rose(8)) = correspondance( imp1l, jp )
453                   ENDIF
454                ENDIF
455
456             ELSE
457
458                neighbours_g(i,rose(1)) = -1
459                neighbours_g(i,rose(2)) = -1
460                neighbours_g(i,rose(8)) = -1
461               
462             ENDIF
463
464          ENDIF
465         
466          ! South
467          IF ( jp .LT. jjm ) THEN
468
469             neighbours_g(i,rose(5)) = correspondance(ip,jp+1)
470             IF ( imp1 > 0 ) THEN
471                neighbours_g(i,rose(4)) = correspondance(imp1,jp+1)
472             ELSE
473                neighbours_g(i,rose(4)) = -1
474             ENDIF
475             IF ( imm1 > 0 ) THEN
476                neighbours_g(i,rose(6)) = correspondance(imm1,jp+1)
477             ELSE
478                neighbours_g(i,rose(6)) = -1
479             ENDIF
480
481          ELSE
482             
483             IF ( global ) THEN
484
485                ! special treatment for the pole if we are really in a 2d grid
486               
487                IF ( ( iim .GT. 1 ) .AND. ( jjm .GT. 1 ) ) THEN
488                   !
489                   ii = MOD(ip+iim/2-1,iim)+1
490                   imm1l = ii - 1
491                   IF ( imm1l .LT. 1 ) imm1l = iim
492                   imp1l = ii + 1
493                   IF ( imp1l .GT. iim ) imp1l = 1
494                   !
495                   IF ( ( ABS( grid_lat(ip,jp) ) - 90. ) .LT. min_sechiba ) THEN
496                      ! the grid point sits exactly on the pole. The neighbour is situated
497                      ! at a lower latitude.
498                      neighbours_g(i,rose(5)) = correspondance( ii, jp-1 )
499                      neighbours_g(i,rose(4)) = correspondance( imm1l, jp-1 )
500                      neighbours_g(i,rose(6)) = correspondance( imp1l, jp-1 )
501                   ELSE
502                      ! look across the South Pole
503                      neighbours_g(i,rose(5)) = correspondance( ii, jp )
504                      neighbours_g(i,rose(4)) = correspondance( imm1l, jp )
505                      neighbours_g(i,rose(6)) = correspondance( imp1l, jp )
506                   ENDIF
507                ENDIF
508
509             ELSE
510               
511                neighbours_g(i,rose(5)) = -1
512                neighbours_g(i,rose(4)) = -1
513                neighbours_g(i,rose(6)) = -1
514               
515             ENDIF
516          ENDIF
517
518       ENDDO
519
520       IF ( bavard .GT. 1 ) THEN
521          WRITE(numout,*) '  > Total number of points: ',npts_glo
522          WRITE(numout,*) '  > Using default zonal resolution at',ndefault_lon,' points.'
523          WRITE(numout,*) '  > Using default meridional resolution at',ndefault_lat,' points.'
524       ENDIF
525       !
526    ENDIF ! (root_prc)
527
528    CALL scatter(neighbours_g,neighbours)
529    CALL scatter(resolution_g,resolution)
530    CALL scatter(area_g,area)
531    CALL bcast(min_resol)
532    CALL bcast(max_resol)
533    IF ( bavard .EQ. 5 ) THEN
534       WRITE(numout,*) '  > resolution  = ',resolution
535       WRITE(numout,*) '  > rose = ',rose
536       WRITE(numout,*) '  > neighbours  = ',neighbours
537    ENDIF
538    IF ( bavard .GT. 1 ) WRITE(numout,*) 'Leaving grid_stuff'
539   
540  END SUBROUTINE grid_stuff
541  !
542!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
543
544END MODULE grid
Note: See TracBrowser for help on using the repository browser.