source: tags/ORCHIDEE/src_global/grid.f90 @ 6

Last change on this file since 6 was 6, checked in by orchidee, 14 years ago

import first tag equivalent to CVS orchidee_1_9_5 + OOL_1_9_5

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