SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
latlonmask_lonlatval.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! ##################################
6  SUBROUTINE latlonmask_lonlatval(KGRID_PAR,PGRID_PAR,OLATLONMASK)
7 ! ##################################
8 !
9 !!**** *LATLONMASK* builds the latitude and longitude mask including the grid
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !! METHOD
15 !! ------
16 !!
17 !! A simple method is used :
18 !!
19 !! XMIN, XMAX, YMIN, YMAX are calculated for the grid
20 !! This domain is extended to account for deformation between lambert and lat lon.
21 !! All lat lon values in this extended domains are set to true in the mask.
22 !!
23 !! EXTERNAL
24 !! --------
25 !!
26 !!
27 !! IMPLICIT ARGUMENTS
28 !! ------------------
29 !!
30 !!
31 !! REFERENCE
32 !! ---------
33 !!
34 !! AUTHOR
35 !! ------
36 !!
37 !! E. Martin Meteo-France
38 !!
39 !! MODIFICATION
40 !! ------------
41 !!
42 !! Original 10/2007
43 !----------------------------------------------------------------------------
44 !
45 !* 0. DECLARATION
46 ! -----------
47 !
49 !
50 !
51 USE yomhook ,ONLY : lhook, dr_hook
52 USE parkind1 ,ONLY : jprb
53 !
54 IMPLICIT NONE
55 !
56 !* 0.1 Declaration of arguments
57 ! ------------------------
58 !
59 INTEGER, INTENT(IN) :: kgrid_par ! size of PGRID_PAR
60 REAL, DIMENSION(KGRID_PAR), INTENT(IN) :: pgrid_par ! parameters defining this grid
61 LOGICAL, DIMENSION(720,360), INTENT(OUT) :: olatlonmask ! mask where data are to be read
62 !
63 !* 0.2 Declaration of local variables
64 ! ------------------------------
65 !
66 REAL :: zxmin ! minimum of X for domain
67 REAL :: zxmax ! maximum of X for domain
68 REAL :: zlon0
69 REAL :: zymin ! minimum of Y for domain
70 REAL :: zymax ! maximum of Y for domain
71 REAL, DIMENSION(720,360) :: zx_mask ! mask points X value
72 REAL, DIMENSION(720,360) :: zy_mask ! mask points Y value
73 REAL, DIMENSION(720,360) :: zlon_mask! mask points longitudes
74 REAL, DIMENSION(720,360) :: zlat_mask! mask points latitudes
75 REAL, DIMENSION(:), ALLOCATABLE :: zx ! X Lambert coordinate
76 REAL, DIMENSION(:), ALLOCATABLE :: zy ! Y Lambert coordinate
77 REAL, DIMENSION(:), ALLOCATABLE :: zdx ! Grid dimension in X
78 REAL, DIMENSION(:), ALLOCATABLE :: zdy ! Grid dimension in Y
79 !
80 INTEGER :: il ! Number og grid points
81 INTEGER :: jlat, jlon
82 REAL(KIND=JPRB) :: zhook_handle
83 !----------------------------------------------------------------------------
84 !
85 IF (lhook) CALL dr_hook('LATLONMASK_LONLATVAL',0,zhook_handle)
86 olatlonmask(:,:) = .false.
87 !
88 !-------------------------------------------------------------------------------
89 !
90 !* 1. Limits of the domain in lonlatval coordinates
91 ! ------------------------------------------------
92 !
93  CALL get_gridtype_lonlatval(pgrid_par,kl=il)
94 !
95  ALLOCATE(zx(il))
96  ALLOCATE(zy(il))
97  ALLOCATE(zdx(il))
98  ALLOCATE(zdy(il))
99 !
100  CALL get_gridtype_lonlatval(pgrid_par,px=zx,py=zy,pdx=zdx,pdy=zdy)
101 !
102 !* 2. Limits of grid meshes in x and y
103 ! --------------------------------
104 !
105  zxmin = minval(zx(:)-zdx(:)/2.)
106  zxmax = maxval(zx(:)+zdx(:)/2.)
107  zymin = minval(zy(:)-zdy(:)/2.)
108  zymax = maxval(zy(:)+zdy(:)/2.)
109  DEALLOCATE(zx )
110  DEALLOCATE(zy )
111  DEALLOCATE(zdx)
112  DEALLOCATE(zdy)
113 !
114 !-------------------------------------------------------------------------------
115 !
116 !* 2. Definition of the coordinates at center of the mask meshes
117 ! ----------------------------------------------------------
118 !
119 !
120 zlon_mask(:,:)= spread( (/ ( jlon /2. - 0.25 , jlon=1,720 ) /) , dim=2, ncopies=360 )
121 zlat_mask(:,:)= spread( (/ ( (jlat-180)/2. - 0.25 , jlat=1,360 ) /) , dim=1, ncopies=720 )
122 !
123 !* 3. Longitude correction (-180 /+180 )
124 ! --------------------------------
125 !
126 zlon0 = 0.5 * (zxmin+zxmax)
127 zlon_mask(:,:)=zlon_mask(:,:)+nint((zlon0-zlon_mask(:,:))/360.)*360.
128 !
129 !* 5. Are the points in the domain?
130 ! ----------------------------
131 !
132 WHERE ((zlon_mask(:,:) >= zxmin .AND. zlon_mask(:,:) <= zxmax &
133  .OR. zlon_mask(:,:) <= zxmin .AND. zlon_mask(:,:)+0.25 >= zxmin &
134  .OR. zlon_mask(:,:) >= zxmax .AND. zlon_mask(:,:)-0.25 <= zxmax &
135  .OR. zlon_mask(:,:)-0.25 <=zxmin .AND. zlon_mask(:,:)+0.25 >= zxmax) .AND. &
136  (zlat_mask(:,:) >= zymin .AND. zlat_mask(:,:) <= zymax &
137  .OR. zlat_mask(:,:) <= zymin .AND. zlat_mask(:,:)+0.25 >= zymin &
138  .OR. zlat_mask(:,:) >= zymax .AND. zlat_mask(:,:)-0.25 <= zymax &
139  .OR. zlat_mask(:,:)-0.25 <=zymin .AND. zlat_mask(:,:)+0.25 >= zymax))
140  olatlonmask(:,:) = .true.
141 END WHERE
142 IF (lhook) CALL dr_hook('LATLONMASK_LONLATVAL',1,zhook_handle)
143 !
144 !-------------------------------------------------------------------------------
145 END SUBROUTINE latlonmask_lonlatval
subroutine get_gridtype_lonlatval(PGRID_PAR, KL, PX, PY, PDX, PDY)
subroutine latlonmask_lonlatval(KGRID_PAR, PGRID_PAR, OLATLONMASK)