SURFEX v8.1
General documentation of Surfex
get_mesh_index_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 get_mesh_index_lonlat_rot(KL,PGRID_PAR,PLAT,PLON,KINDEX,KSSO,KISSOX,KISSOY)
7 ! ###############################################################
8 !
9 !!**** *GET_MESH_INDEX_LONLAT_ROT* get the grid mesh where point (lat,lon) is located
10 !!
11 !! Note that this subroutine operates on the rotated grid. Thus incoming
12 !! PLON, PLAT on regular grid is rotated.
13 !!
14 !! PURPOSE
15 !! -------
16 !!
17 !! AUTHOR
18 !! ------
19 !!
20 !! P. Samuelsson SMHI
21 !!
22 !! MODIFICATION
23 !! ------------
24 !!
25 !! Original 12/2012
26 !!
27 !----------------------------------------------------------------------------
28 !
29 !* 0. DECLARATION
30 ! -----------
31 !
34 !
35 !
36 USE yomhook ,ONLY : lhook, dr_hook
37 USE parkind1 ,ONLY : jprb
38 !RJ: missing modi
39 USE modi_regrot_lonlat_rot
40 !
41 IMPLICIT NONE
42 !
43 !* 0.1 Declaration of arguments
44 ! ------------------------
45 !
46 INTEGER, INTENT(IN) :: KL ! number of points
47 REAL, DIMENSION(:), INTENT(IN) :: PGRID_PAR ! grid parameters
48 REAL, DIMENSION(KL), INTENT(IN) :: PLAT ! latitude of the point
49 REAL, DIMENSION(KL), INTENT(IN) :: PLON ! longitude of the point
50 INTEGER, DIMENSION(KL), INTENT(OUT) :: KINDEX ! index of the grid mesh where the point is
51 INTEGER, INTENT(IN) :: KSSO ! number of subgrid mesh in each direction
52 INTEGER, DIMENSION(KL), INTENT(OUT) :: KISSOX ! X index of the subgrid mesh
53 INTEGER, DIMENSION(KL), INTENT(OUT) :: KISSOY ! Y index of the subgrid mesh
54 !
55 !* 0.2 Declaration of other local variables
56 ! ------------------------------------
57 !
58 INTEGER :: JI ! loop counter in x
59 INTEGER :: JJ ! loop counter in y
60 INTEGER :: JL ! loop counter on input points
61 !
62 REAL :: ZWEST ! West longitude in rotated grid (degrees)
63 REAL :: ZSOUTH ! South latitude in rotated grid (degrees)
64 REAL :: ZDLON ! Longitudal grid spacing (degrees)
65 REAL :: ZDLAT ! Latitudal grid spacing (degrees)
66 !
67 REAL, DIMENSION(SIZE(PLON)) :: ZLON
68 REAL, DIMENSION(SIZE(PLAT)) :: ZLAT
69 REAL(KIND=JPRB) :: ZHOOK_HANDLE
70 !
71 !----------------------------------------------------------------------------
72 !
73 IF (lhook) CALL dr_hook('GET_MESH_INDEX_LONLAT_ROT',0,zhook_handle)
74 IF (.NOT. ALLOCATED(xlatlim)) THEN
75 !
76 !* 1. Uncode parameters of the grid
77 ! -----------------------------
78 !
79  CALL get_gridtype_lonlat_rot(pgrid_par, &
80  zwest,zsouth,zdlon,zdlat,xpolon,xpolat, &
81  nlon,nlat )
82 !
83 !----------------------------------------------------------------------------
84 !
85 !* 2. Limits of grid meshes
86 ! ---------------------
87 !
88  ALLOCATE(xlonlim(nlon+1))
89  DO ji=1,nlon+1
90  xlonlim(ji) = zwest + float(ji-1)*zdlon
91  END DO
92  xlonlim = xlonlim - zdlon/2.
93 
94  ALLOCATE(xlatlim(nlat+1))
95  DO ji=1,nlat+1
96  xlatlim(ji) = zsouth + float(ji-1)*zdlat
97  END DO
98  xlatlim = xlatlim - zdlat/2.
99 !
100  xlon0 = 0.5*(minval(xlonlim)+maxval(xlonlim))
101 !
102 END IF
103 !----------------------------------------------------------------------------
104 !
105 !* 3. Reshifts the longitudes with respect to projection reference point
106 ! ------------------------------------------------------------------
107 !
108 !
109  CALL regrot_lonlat_rot(plon,plat,zlon,zlat, &
110  kl,1,kl,1, &
111  xpolon,xpolat,1 )
112 !
113 WHERE (zlon(:)>180.) zlon(:)=zlon(:)-360.
114 WHERE (zlon(:)<-180.) zlon(:)=zlon(:)+360.
115 !
116 zlon(:) = zlon(:)+nint((xlon0-zlon(:))/360.)*360.
117 !
118 !----------------------------------------------------------------------------
119 !
120 !* 4. Localisation of the data points on (x,y) grid
121 ! ---------------------------------------------
122 !
123 IF (kl/=nlon*nlat) THEN
124  kindex = 0
125  kissox = 0
126  kissoy = 0
127 END IF
128 !
129 !
130 DO jl=1,SIZE(zlat)
131  IF ( zlon(jl)<xlonlim(1) .OR. zlon(jl)>=xlonlim(nlon+1) &
132  .OR. zlat(jl)<xlatlim(1) .OR. zlat(jl)>=xlatlim(nlat+1) ) THEN
133  kindex(jl) = 0
134  IF (ksso/=0) THEN
135  kissox(jl) = 0
136  kissoy(jl) = 0
137  END IF
138  cycle
139  END IF
140  ji = count(zlon(jl)>=xlonlim(:))
141  jj = count(zlat(jl)>=xlatlim(:))
142  kindex(jl) = (jj-1) * nlon + ji
143 !
144 !
145 !* 6. Localisation of the data points on in the subgrid of this mesh
146 ! --------------------------------------------------------------
147 !
148  IF (ksso/=0) THEN
149  kissox(jl) = 1 + int( float(ksso) * (zlon(jl)-xlonlim(ji))/(xlonlim(ji+1)-xlonlim(ji)) )
150  kissoy(jl) = 1 + int( float(ksso) * (zlat(jl)-xlatlim(jj))/(xlatlim(jj+1)-xlatlim(jj)) )
151  END IF
152 END DO
153 IF (lhook) CALL dr_hook('GET_MESH_INDEX_LONLAT_ROT',1,zhook_handle)
154 !
155 !-------------------------------------------------------------------------------
156 !
157 END SUBROUTINE get_mesh_index_lonlat_rot
integer, parameter jprb
Definition: parkind1.F90:32
subroutine regrot_lonlat_rot(PXREG, PYREG, PXROT, PYROT, KXDIM, KYDIM, KX, KY, PXCEN, PYCEN, KCALL)
subroutine get_gridtype_lonlat_rot(PGRID_PAR,
logical lhook
Definition: yomhook.F90:15
real, dimension(:), allocatable xlatlim
subroutine get_mesh_index_lonlat_rot(KL, PGRID_PAR, PLAT, PLON, KINDEX
real, dimension(:), allocatable xlonlim
static int count
Definition: memory_hook.c:21