SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
get_mesh_index_conf_proj.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_conf_proj(KGRID_PAR,KSSO,PGRID_PAR,PLAT,PLON,KINDEX,KISSOX,KISSOY)
7 ! ###############################################################
8 !
9 !!**** *GET_MESH_INDEX_CONF_PROJ* get the grid mesh where point (lat,lon) is located
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !! AUTHOR
15 !! ------
16 !!
17 !! V. Masson Meteo-France
18 !!
19 !! MODIFICATION
20 !! ------------
21 !!
22 !! Original 12/09/95
23 !! J.Escobar 22/10/2011 : reintroduce optimisation for JI/JJ number of lines computation
24 !! J. Escobar 06/2013 : modif for REAL*4
25 !!
26 !----------------------------------------------------------------------------
27 !
28 !* 0. DECLARATION
29 ! -----------
30 !
31 USE modd_get_mesh_index_conf_proj, ONLY : xlat0, xlon0, xrpk, xbeta, &
32  xlator, xlonor, nimax, njmax, &
33  xxlim, xylim
35 !
36 !
37 USE yomhook ,ONLY : lhook, dr_hook
38 USE parkind1 ,ONLY : jprb
39 USE modd_csts ,ONLY : xsurf_epsilon
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) :: ksso ! number of subgrid mesh in each direction
48 !
49 REAL, DIMENSION(:), INTENT(IN) :: pgrid_par ! grid parameters
50 REAL, DIMENSION(:), INTENT(IN) :: plat ! latitude of the point
51 REAL, DIMENSION(:), INTENT(IN) :: plon ! longitude of the point
52 INTEGER, DIMENSION(:,:), INTENT(OUT) :: kindex ! index of the grid mesh where the point is
53 INTEGER, DIMENSION(:,:), INTENT(OUT) :: kissox ! X index of the subgrid mesh
54 INTEGER, DIMENSION(:,:), INTENT(OUT) :: kissoy ! Y index of the subgrid mesh
55 !
56 !* 0.2 Declaration of other local variables
57 ! ------------------------------------
58 !
59 REAL, DIMENSION(SIZE(PLON)) :: zlon ! longitude
60 !
61 REAL, DIMENSION(:), ALLOCATABLE :: zx ! X conformal coordinate
62 REAL, DIMENSION(:), ALLOCATABLE :: zy ! Y conformal coordinate
63 REAL, DIMENSION(:), ALLOCATABLE :: zdx ! X grid mesh size
64 REAL, DIMENSION(:), ALLOCATABLE :: zdy ! Y grid mesh size
65 REAL :: zdxlim ! X grid mesh size
66 REAL :: zdylim ! Y grid mesh size
67 !
68 INTEGER :: ji ! loop counter in x
69 INTEGER :: jj ! loop counter in y
70 INTEGER :: jl ! loop counter on input points
71 REAL(KIND=JPRB) :: zhook_handle
72 !----------------------------------------------------------------------------
73 !
74 IF (lhook) CALL dr_hook('GET_MESH_INDEX_CONF_PROJ',0,zhook_handle)
75 IF (.NOT. ALLOCATED(xxlim)) THEN
76 !
77 !* 1. Uncode parameters of the grid
78 ! -----------------------------
79 !
80  CALL get_gridtype_conf_proj(pgrid_par,xlat0,xlon0,xrpk,xbeta,&
81  xlator,xlonor,nimax,njmax )
82 !
83  ALLOCATE(zx(nimax*njmax))
84  ALLOCATE(zy(nimax*njmax))
85  ALLOCATE(zdx(nimax*njmax))
86  ALLOCATE(zdy(nimax*njmax))
87 !
88  CALL get_gridtype_conf_proj(pgrid_par, &
89  px=zx,py=zy,pdx=zdx,pdy=zdy )
90 !
91 !* 2. Limits of grid meshes in x and y
92 ! --------------------------------
93 !
94  ALLOCATE(xxlim(nimax+1))
95  xxlim(1) = zx(1) - zdx(1)/2.
96  DO ji=2,nimax
97  jl = ji
98  xxlim(ji) = zx(jl) - (zdx(jl-1)+zdx(jl))/4.
99  END DO
100  xxlim(nimax+1) = zx(nimax) + zdx(nimax)/2.
101 
102  ALLOCATE(xylim(njmax+1))
103  xylim(1) = zy(1) - zdy(1)/2.
104  DO jj=2,njmax
105  jl = 1 + (jj-1) * nimax
106  xylim(jj) = zy(jl) - (zdy(jl-nimax)+zdy(jl))/4.
107  END DO
108  xylim(njmax+1) = zy(1+(njmax-1)*nimax) + zdy(1+(njmax-1)*nimax)/2.
109 !
110 !
111  DEALLOCATE(zx )
112  DEALLOCATE(zy )
113  DEALLOCATE(zdx)
114  DEALLOCATE(zdy)
115 END IF
116 !
117 zdxlim = xxlim(2) - xxlim(1)
118 zdylim = xylim(2) - xylim(1)
119 !
120 !* 2. Reshifts the longitudes with respect to projection reference point
121 ! ------------------------------------------------------------------
122 !
123 zlon(:) = plon(:)+nint((xlon0-plon(:)+180.0*xsurf_epsilon)/360.)*360.
124 !
125 !* 3. Projection
126 ! ----------
127 !
128 ALLOCATE(zx(SIZE(plat)))
129 ALLOCATE(zy(SIZE(plat)))
130 !
131  CALL xy_conf_proj(xlat0,xlon0,xrpk,xbeta,xlator,xlonor, &
132  zx,zy,plat,zlon )
133 !
134 !
135 !
136 !* 5. Localisation of the data points on (x,y) grid
137 ! ---------------------------------------------
138 !
139 kindex(:,:) = 0
140 !
141 DO jl=1,SIZE(plon)
142  IF ( zx(jl)<xxlim(1) .OR. zx(jl)>=xxlim(nimax+1) &
143  .OR. zy(jl)<xylim(1) .OR. zy(jl)>=xylim(njmax+1) ) THEN
144  kindex(1,jl) = 0
145  IF (ksso/=0) THEN
146  kissox(1,jl) = 0
147  kissoy(1,jl) = 0
148  END IF
149  cycle
150  END IF
151  ji = min(int( (zx(jl) - xxlim(1))/zdxlim+1),nimax)
152  jj = min(int( (zy(jl) - xylim(1))/zdylim+1),njmax)
153 
154  kindex(1,jl) = (jj-1) * nimax + ji
155 !
156 !
157 !* 6. Localisation of the data points on in the subgrid of this mesh
158 ! --------------------------------------------------------------
159 !
160  IF (ksso/=0) THEN
161  kissox(1,jl) = 1 + int( float(ksso) * (zx(jl)-xxlim(ji))/(xxlim(ji+1)-xxlim(ji)) )
162  kissoy(1,jl) = 1 + int( float(ksso) * (zy(jl)-xylim(jj))/(xylim(jj+1)-xylim(jj)) )
163  END IF
164 END DO
165 !
166 !-------------------------------------------------------------------------------
167 DEALLOCATE(zx )
168 DEALLOCATE(zy )
169 IF (lhook) CALL dr_hook('GET_MESH_INDEX_CONF_PROJ',1,zhook_handle)
170 !-------------------------------------------------------------------------------
171 !
172 END SUBROUTINE get_mesh_index_conf_proj
subroutine xy_conf_proj(PLAT0, PLON0, PRPK, PBETA, PLATOR, PLONOR, PX, PY, PLAT, PLON)
subroutine get_mesh_index_conf_proj(KGRID_PAR, KSSO, PGRID_PAR, PLAT, PLON, KINDEX, KISSOX, KISSOY)
subroutine get_gridtype_conf_proj(PGRID_PAR, PLAT0, PLON0, PRPK, PBETA, PLATOR, PLONOR, KIMAX, KJMAX, PX, PY, PDX, PDY, KL)