SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
latlonmask_lonlat_reg.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_reg(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 !! V. Masson Meteo-France
38 !!
39 !! MODIFICATION
40 !! ------------
41 !!
42 !! Original 19/07/95
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 :: zlonmin
67 REAL :: zlonmax
68 REAL :: zlatmin
69 REAL :: zlatmax
70 REAL :: zlon0
71 !
72 INTEGER :: jlat
73 INTEGER :: jlon
74 !
75 REAL, DIMENSION(720,360) :: zlon_mask! mask points longitudes
76 REAL, DIMENSION(720,360) :: zlat_mask! mask points latitudes
77 REAL(KIND=JPRB) :: zhook_handle
78 !----------------------------------------------------------------------------
79 !
80 IF (lhook) CALL dr_hook('LATLONMASK_LONLAT_REG',0,zhook_handle)
81  CALL get_gridtype_lonlat_reg(pgrid_par,zlonmin,zlonmax, &
82  zlatmin,zlatmax )
83 !
84 !-------------------------------------------------------------------------------
85 !
86 olatlonmask(:,:) = .false.
87 !
88 !-------------------------------------------------------------------------------
89 !
90 !* 2. Definition of the coordinates at center of the mask meshes
91 ! ----------------------------------------------------------
92 !
93 !
94 zlon_mask(:,:)= spread( (/ ( jlon /2. - 0.25 , jlon=1,720 ) /) , dim=2, ncopies=360 )
95 zlat_mask(:,:)= spread( (/ ( (jlat-180)/2. - 0.25 , jlat=1,360 ) /) , dim=1, ncopies=720 )
96 !
97 !-------------------------------------------------------------------------------
98 !
99 !* 3. Set definition of longitudes according to grid
100 ! ----------------------------------------------
101 !
102 zlon0 = 0.5*(zlonmin+zlonmax)
103 zlon_mask(:,:)=zlon_mask(:,:)+nint((zlon0-zlon_mask(:,:))/360.)*360.
104 !
105 !-------------------------------------------------------------------------------
106 !
107 DO jlat=1,360
108  DO jlon=1,720
109  IF ( zlon_mask(jlon,jlat) + 0.25 >= zlonmin &
110  .AND. zlon_mask(jlon,jlat) - 0.25 <= zlonmax &
111  .AND. zlat_mask(jlon,jlat) + 0.25 >= zlatmin &
112  .AND. zlat_mask(jlon,jlat) - 0.25 <= zlatmax ) olatlonmask(jlon,jlat) = .true.
113  END DO
114 END DO
115 IF (lhook) CALL dr_hook('LATLONMASK_LONLAT_REG',1,zhook_handle)
116 !
117 !-------------------------------------------------------------------------------
118 !
119 END SUBROUTINE latlonmask_lonlat_reg
subroutine latlonmask_lonlat_reg(KGRID_PAR, PGRID_PAR, OLATLONMASK)
subroutine get_gridtype_lonlat_reg(PGRID_PAR, PLONMIN, PLONMAX, PLATMIN, PLATMAX, KLON, KLAT, KL, PLON, PLAT)