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

Last change on this file since 257 was 257, checked in by didier.solyga, 13 years ago

Externalized version merged with the trunk

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