SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
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(KGRID_PAR,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 !
32 USE modd_get_mesh_index_lonlat_rot, ONLY : xlonlim, xlatlim, nlat, nlon, xlon0, xpolon, xpolat
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) :: kgrid_par ! size of PGRID_PAR
47 INTEGER, INTENT(IN) :: kl ! number of points
48 REAL, DIMENSION(KGRID_PAR), INTENT(IN) :: pgrid_par ! grid parameters
49 REAL, DIMENSION(KL), INTENT(IN) :: plat ! latitude of the point
50 REAL, DIMENSION(KL), INTENT(IN) :: plon ! longitude of the point
51 INTEGER, DIMENSION(KL), INTENT(OUT) :: kindex ! index of the grid mesh where the point is
52 INTEGER, INTENT(IN) :: ksso ! number of subgrid mesh in each direction
53 INTEGER, DIMENSION(KL), INTENT(OUT) :: kissox ! X index of the subgrid mesh
54 INTEGER, DIMENSION(KL), INTENT(OUT) :: kissoy ! Y index of the subgrid mesh
55 !
56 !* 0.2 Declaration of other local variables
57 ! ------------------------------------
58 !
59 INTEGER :: ji ! loop counter in x
60 INTEGER :: jj ! loop counter in y
61 INTEGER :: jl ! loop counter on input points
62 !
63 REAL :: zwest ! West longitude in rotated grid (degrees)
64 REAL :: zsouth ! South latitude in rotated grid (degrees)
65 REAL :: zdlon ! Longitudal grid spacing (degrees)
66 REAL :: zdlat ! Latitudal grid spacing (degrees)
67 !
68 REAL, DIMENSION(SIZE(PLON)) :: zlon
69 REAL, DIMENSION(SIZE(PLAT)) :: zlat
70 REAL(KIND=JPRB) :: zhook_handle
71 !
72 !----------------------------------------------------------------------------
73 !
74 IF (lhook) CALL dr_hook('GET_MESH_INDEX_LONLAT_ROT',0,zhook_handle)
75 IF (.NOT. ALLOCATED(xlatlim)) THEN
76 !
77 !* 1. Uncode parameters of the grid
78 ! -----------------------------
79 !
80  CALL get_gridtype_lonlat_rot(pgrid_par, &
81  zwest,zsouth,zdlon,zdlat,xpolon,xpolat, &
82  nlon,nlat )
83 !
84 !----------------------------------------------------------------------------
85 !
86 !* 2. Limits of grid meshes
87 ! ---------------------
88 !
89  ALLOCATE(xlonlim(nlon+1))
90  DO ji=1,nlon+1
91  xlonlim(ji) = zwest + float(ji-1)*zdlon
92  END DO
93  xlonlim = xlonlim - zdlon/2.
94 
95  ALLOCATE(xlatlim(nlat+1))
96  DO ji=1,nlat+1
97  xlatlim(ji) = zsouth + float(ji-1)*zdlat
98  END DO
99  xlatlim = xlatlim - zdlat/2.
100 !
101  xlon0 = 0.5*(minval(xlonlim)+maxval(xlonlim))
102 !
103 END IF
104 !----------------------------------------------------------------------------
105 !
106 !* 3. Reshifts the longitudes with respect to projection reference point
107 ! ------------------------------------------------------------------
108 !
109 !
110  CALL regrot_lonlat_rot(plon,plat,zlon,zlat, &
111  kl,1,kl,1, &
112  xpolon,xpolat,1 )
113 !
114 WHERE (zlon(:)>180.) zlon(:)=zlon(:)-360.
115 WHERE (zlon(:)<-180.) zlon(:)=zlon(:)+360.
116 !
117 zlon(:) = zlon(:)+nint((xlon0-zlon(:))/360.)*360.
118 !
119 !----------------------------------------------------------------------------
120 !
121 !* 4. Localisation of the data points on (x,y) grid
122 ! ---------------------------------------------
123 !
124 IF (kl/=nlon*nlat) THEN
125  kindex = 0
126  kissox = 0
127  kissoy = 0
128 END IF
129 !
130 !
131 DO jl=1,SIZE(zlat)
132  IF ( zlon(jl)<xlonlim(1) .OR. zlon(jl)>=xlonlim(nlon+1) &
133  .OR. zlat(jl)<xlatlim(1) .OR. zlat(jl)>=xlatlim(nlat+1) ) THEN
134  kindex(jl) = 0
135  IF (ksso/=0) THEN
136  kissox(jl) = 0
137  kissoy(jl) = 0
138  END IF
139  cycle
140  END IF
141  ji = count(zlon(jl)>=xlonlim(:))
142  jj = count(zlat(jl)>=xlatlim(:))
143  kindex(jl) = (jj-1) * nlon + ji
144 !
145 !
146 !* 6. Localisation of the data points on in the subgrid of this mesh
147 ! --------------------------------------------------------------
148 !
149  IF (ksso/=0) THEN
150  kissox(jl) = 1 + int( float(ksso) * (zlon(jl)-xlonlim(ji))/(xlonlim(ji+1)-xlonlim(ji)) )
151  kissoy(jl) = 1 + int( float(ksso) * (zlat(jl)-xlatlim(jj))/(xlatlim(jj+1)-xlatlim(jj)) )
152  END IF
153 END DO
154 IF (lhook) CALL dr_hook('GET_MESH_INDEX_LONLAT_ROT',1,zhook_handle)
155 !
156 !-------------------------------------------------------------------------------
157 !
158 END SUBROUTINE get_mesh_index_lonlat_rot
subroutine get_gridtype_lonlat_rot(PGRID_PAR, PWEST, PSOUTH, PDLON, PDLAT, PPOLON, PPOLAT, KLON, KLAT, KL, PLON, PLAT)
subroutine get_mesh_index_lonlat_rot(KGRID_PAR, KL, PGRID_PAR, PLAT, PLON, KINDEX, KSSO, KISSOX, KISSOY)
subroutine regrot_lonlat_rot(PXREG, PYREG, PXROT, PYROT, KXDIM, KYDIM, KX, KY, PXCEN, PYCEN, KCALL)