SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
latlonmask_lonlat_rot.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_lonlat_rot(KGRID_PAR,PGRID_PAR,OLATLONMASK)
7 ! ##################################
8 !
9 !!**** *LATLONMASK* builds the latiude and longitude mask including the grid
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !! METHOD
15 !! ------
16 !!
17 !! Two tests are performed:
18 !!
19 !! 1) test if the points of the mask are in the domain
20 !!
21 !! 2) fills the mask points corresponding to points scanning
22 !!
23 !! EXTERNAL
24 !! --------
25 !!
26 !!
27 !! IMPLICIT ARGUMENTS
28 !! ------------------
29 !!
30 !!
31 !! REFERENCE
32 !! ---------
33 !!
34 !! AUTHOR
35 !! ------
36 !!
37 !! P. Samuelsson SMHI
38 !!
39 !! MODIFICATION
40 !! ------------
41 !!
42 !! Original 12/2012
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 !
67 REAL :: zdlon ! Longitudal grid spacing (degrees)
68 REAL :: zdlat ! Latitudal grid spacing (degrees)
69 !
70 REAL :: zlon0
71 REAL :: zlonmin
72 REAL :: zlonmax
73 REAL :: zlatmin
74 REAL :: zlatmax
75 REAL, DIMENSION(:), ALLOCATABLE :: zlon
76 REAL, DIMENSION(:), ALLOCATABLE :: zlat
77 !
78 INTEGER :: jlat
79 INTEGER :: jlon
80 INTEGER :: zkl
81 !
82 REAL, DIMENSION(720,360) :: zlon_mask! mask points longitudes
83 REAL, DIMENSION(720,360) :: zlat_mask! mask points latitudes
84 REAL(KIND=JPRB) :: zhook_handle
85 !----------------------------------------------------------------------------
86 !
87 IF (lhook) CALL dr_hook('LATLONMASK_LONLAT_ROT',0,zhook_handle)
88 !
89  CALL get_gridtype_lonlat_rot(pgrid_par,pdlon=zdlon,pdlat=zdlat,kl=zkl)
90 !
91 ALLOCATE(zlon(zkl))
92 ALLOCATE(zlat(zkl))
93 !
94  CALL get_gridtype_lonlat_rot(pgrid_par,plon=zlon,plat=zlat)
95 !
96 zlonmin = minval(zlon) - zdlon
97 zlonmax = maxval(zlon) + zdlon
98 zlatmin = minval(zlat) - zdlat
99 zlatmax = maxval(zlat) + zdlat
100 !
101 !-------------------------------------------------------------------------------
102 !
103 olatlonmask(:,:) = .false.
104 !
105 !-------------------------------------------------------------------------------
106 !
107 !* 2. Definition of the coordinates at center of the mask meshes
108 ! ----------------------------------------------------------
109 !
110 !
111 zlon_mask(:,:)= spread( (/ ( jlon /2. - 0.25 , jlon=1,720 ) /) , dim=2, ncopies=360 )
112 zlat_mask(:,:)= spread( (/ ( (jlat-180)/2. - 0.25 , jlat=1,360 ) /) , dim=1, ncopies=720 )
113 !
114 !-------------------------------------------------------------------------------
115 !
116 !* 3. Set definition of longitudes according to grid
117 ! ----------------------------------------------
118 !
119 zlon0 = 0.5*(zlonmin + zlonmax)
120 zlon_mask(:,:)=zlon_mask(:,:)+nint((zlon0-zlon_mask(:,:))/360.)*360.
121 !
122 !-------------------------------------------------------------------------------
123 !
124 DO jlat=1,360
125  DO jlon=1,720
126  IF ( zlon_mask(jlon,jlat) + 0.25 >= zlonmin &
127  .AND. zlon_mask(jlon,jlat) - 0.25 <= zlonmax &
128  .AND. zlat_mask(jlon,jlat) + 0.25 >= zlatmin &
129  .AND. zlat_mask(jlon,jlat) - 0.25 <= zlatmax ) olatlonmask(jlon,jlat) = .true.
130  END DO
131 END DO
132 IF (lhook) CALL dr_hook('LATLONMASK_LONLAT_ROT',1,zhook_handle)
133 !
134 !-------------------------------------------------------------------------------
135 !
136 END SUBROUTINE latlonmask_lonlat_rot
subroutine get_gridtype_lonlat_rot(PGRID_PAR, PWEST, PSOUTH, PDLON, PDLAT, PPOLON, PPOLAT, KLON, KLAT, KL, PLON, PLAT)
subroutine latlonmask_lonlat_rot(KGRID_PAR, PGRID_PAR, OLATLONMASK)