SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
latlonmask_ign.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_ign(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 USE modd_ign, ONLY : xexpand
50 !
51 !
52 USE yomhook ,ONLY : lhook, dr_hook
53 USE parkind1 ,ONLY : jprb
54 !
55 IMPLICIT NONE
56 !
57 !* 0.1 Declaration of arguments
58 ! ------------------------
59 !
60 INTEGER, INTENT(IN) :: kgrid_par ! size of PGRID_PAR
61 REAL, DIMENSION(KGRID_PAR), INTENT(IN) :: pgrid_par ! parameters defining this grid
62 LOGICAL, DIMENSION(720,360), INTENT(OUT) :: olatlonmask ! mask where data are to be read
63 !
64 !* 0.2 Declaration of local variables
65 ! ------------------------------
66 !
67 REAL :: zxmin ! minimum of X for domain
68 REAL :: zxmax ! maximum of X for domain
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 :: ilambert ! Lambert projection type
81 INTEGER :: il ! Number og grid points
82 INTEGER :: jlat, jlon
83 REAL(KIND=JPRB) :: zhook_handle
84 !----------------------------------------------------------------------------
85 !
86 IF (lhook) CALL dr_hook('LATLONMASK_IGN',0,zhook_handle)
87 olatlonmask(:,:) = .false.
88 !
89 !-------------------------------------------------------------------------------
90 !
91 !* 1. Limits of the domain in Lambert IGN coordinates
92 ! (including expansion factor)
93 ! ------------------------------------------------
94 !
95  CALL get_gridtype_ign(pgrid_par,klambert=ilambert,kl=il)
96 !
97  ALLOCATE(zx(il))
98  ALLOCATE(zy(il))
99  ALLOCATE(zdx(il))
100  ALLOCATE(zdy(il))
101 !
102  CALL get_gridtype_ign(pgrid_par,px=zx,py=zy,pdx=zdx,pdy=zdy)
103 !
104 !* 2. Limits of grid meshes in x and y
105 ! --------------------------------
106 !
107  zxmin = minval(zx(:)-zdx(:)/2.) - xexpand
108  zxmax = maxval(zx(:)+zdx(:)/2.) + xexpand
109  zymin = minval(zy(:)-zdy(:)/2.) - xexpand
110  zymax = maxval(zy(:)+zdy(:)/2.) + xexpand
111  DEALLOCATE(zx )
112  DEALLOCATE(zy )
113  DEALLOCATE(zdx)
114  DEALLOCATE(zdy)
115 !
116 !-------------------------------------------------------------------------------
117 !
118 !* 2. Definition of the coordinates at center of the mask meshes
119 ! ----------------------------------------------------------
120 !
121 !
122 zlon_mask(:,:)= spread( (/ ( jlon /2. - 0.25 , jlon=1,720 ) /) , dim=2, ncopies=360 )
123 zlat_mask(:,:)= spread( (/ ( (jlat-180)/2. - 0.25 , jlat=1,360 ) /) , dim=1, ncopies=720 )
124 !
125 !* 3. Longitude correction (-180 /+180 )
126 ! --------------------------------
127 !
128 zlon_mask(:,:)=zlon_mask(:,:)+nint((-zlon_mask(:,:))/360.)*360.
129 !
130 !
131 !* 4. X and Y of the points of the mask
132 ! ---------------------------------
133 !
134  CALL get_gridtype_ign(pgrid_par, klambert=ilambert)
135 DO jlat=1,SIZE(zlat_mask,2)
136  CALL xy_ign(ilambert,zx_mask(:,jlat),zy_mask(:,jlat), &
137  zlat_mask(:,jlat),zlon_mask(:,jlat) )
138 
139 END DO
140 !
141 !* 5. Are the points in the domain?
142 ! ----------------------------
143 !
144 WHERE ( zx_mask(:,:) >= zxmin .AND. zx_mask(:,:) <= zxmax &
145  .AND. zy_mask(:,:) >= zymin .AND. zy_mask(:,:) <= zymax )
146  olatlonmask(:,:) = .true.
147 END WHERE
148 IF (lhook) CALL dr_hook('LATLONMASK_IGN',1,zhook_handle)
149 !
150 !-------------------------------------------------------------------------------
151 END SUBROUTINE latlonmask_ign
subroutine xy_ign(KLAMBERT, PX, PY, PLAT, PLON)
subroutine get_gridtype_ign(PGRID_PAR, KLAMBERT, KL, PX, PY, PDX, PDY, KDIMX, KDIMY, PXALL, PYALL)
subroutine latlonmask_ign(KGRID_PAR, PGRID_PAR, OLATLONMASK)