SURFEX v8.1
General documentation of Surfex
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(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 !
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) :: KSSO ! number of subgrid mesh in each direction
47 !
48 REAL, DIMENSION(:), INTENT(IN) :: PGRID_PAR ! grid parameters
49 REAL, DIMENSION(:), INTENT(IN) :: PLAT ! latitude of the point
50 REAL, DIMENSION(:), INTENT(IN) :: PLON ! longitude of the point
51 INTEGER, DIMENSION(:,:), INTENT(OUT) :: KINDEX ! index of the grid mesh where the point is
52 INTEGER, DIMENSION(:,:), INTENT(OUT) :: KISSOX ! X index of the subgrid mesh
53 INTEGER, DIMENSION(:,:), INTENT(OUT) :: KISSOY ! Y index of the subgrid mesh
54 !
55 !* 0.2 Declaration of other local variables
56 ! ------------------------------------
57 !
58 REAL, DIMENSION(SIZE(PLON)) :: ZLON ! longitude
59 !
60 REAL, DIMENSION(:), ALLOCATABLE :: ZX ! X conformal coordinate
61 REAL, DIMENSION(:), ALLOCATABLE :: ZY ! Y conformal coordinate
62 REAL, DIMENSION(:), ALLOCATABLE :: ZDX ! X grid mesh size
63 REAL, DIMENSION(:), ALLOCATABLE :: ZDY ! Y grid mesh size
64 REAL :: ZDXLIM ! X grid mesh size
65 REAL :: ZDYLIM ! Y grid mesh size
66 !
67 INTEGER :: JI ! loop counter in x
68 INTEGER :: JJ ! loop counter in y
69 INTEGER :: JL ! loop counter on input points
70 REAL(KIND=JPRB) :: ZHOOK_HANDLE
71 !----------------------------------------------------------------------------
72 !
73 IF (lhook) CALL dr_hook('GET_MESH_INDEX_CONF_PROJ',0,zhook_handle)
74 IF (.NOT. ALLOCATED(xxlim)) THEN
75 !
76 !* 1. Uncode parameters of the grid
77 ! -----------------------------
78 !
81 !
82  ALLOCATE(zx(nimax*njmax))
83  ALLOCATE(zy(nimax*njmax))
84  ALLOCATE(zdx(nimax*njmax))
85  ALLOCATE(zdy(nimax*njmax))
86 !
87  CALL get_gridtype_conf_proj(pgrid_par, &
88  px=zx,py=zy,pdx=zdx,pdy=zdy )
89 !
90 !* 2. Limits of grid meshes in x and y
91 ! --------------------------------
92 !
93  ALLOCATE(xxlim(nimax+1))
94  xxlim(1) = zx(1) - zdx(1)/2.
95  DO ji=2,nimax
96  jl = ji
97  xxlim(ji) = zx(jl) - (zdx(jl-1)+zdx(jl))/4.
98  END DO
99  xxlim(nimax+1) = zx(nimax) + zdx(nimax)/2.
100 
101  ALLOCATE(xylim(njmax+1))
102  xylim(1) = zy(1) - zdy(1)/2.
103  DO jj=2,njmax
104  jl = 1 + (jj-1) * nimax
105  xylim(jj) = zy(jl) - (zdy(jl-nimax)+zdy(jl))/4.
106  END DO
107  xylim(njmax+1) = zy(1+(njmax-1)*nimax) + zdy(1+(njmax-1)*nimax)/2.
108 !
109 !
110  DEALLOCATE(zx )
111  DEALLOCATE(zy )
112  DEALLOCATE(zdx)
113  DEALLOCATE(zdy)
114 END IF
115 !
116 zdxlim = xxlim(2) - xxlim(1)
117 zdylim = xylim(2) - xylim(1)
118 !
119 !* 2. Reshifts the longitudes with respect to projection reference point
120 ! ------------------------------------------------------------------
121 !
122 zlon(:) = plon(:)+nint((xlon0-plon(:)+180.0*xsurf_epsilon)/360.)*360.
123 !
124 !* 3. Projection
125 ! ----------
126 !
127 ALLOCATE(zx(SIZE(plat)))
128 ALLOCATE(zy(SIZE(plat)))
129 !
131  zx,zy,plat,zlon )
132 !
133 !
134 !
135 !* 5. Localisation of the data points on (x,y) grid
136 ! ---------------------------------------------
137 !
138 kindex(:,:) = 0
139 !
140 DO jl=1,SIZE(plon)
141  IF ( zx(jl)<xxlim(1) .OR. zx(jl)>=xxlim(nimax+1) &
142  .OR. zy(jl)<xylim(1) .OR. zy(jl)>=xylim(njmax+1) ) THEN
143  kindex(1,jl) = 0
144  IF (ksso/=0) THEN
145  kissox(1,jl) = 0
146  kissoy(1,jl) = 0
147  END IF
148  cycle
149  END IF
150  ji = min(int( (zx(jl) - xxlim(1))/zdxlim+1),nimax)
151  jj = min(int( (zy(jl) - xylim(1))/zdylim+1),njmax)
152 
153  kindex(1,jl) = (jj-1) * nimax + ji
154 !
155 !
156 !* 6. Localisation of the data points on in the subgrid of this mesh
157 ! --------------------------------------------------------------
158 !
159  IF (ksso/=0) THEN
160  kissox(1,jl) = 1 + int( float(ksso) * (zx(jl)-xxlim(ji))/(xxlim(ji+1)-xxlim(ji)) )
161  kissoy(1,jl) = 1 + int( float(ksso) * (zy(jl)-xylim(jj))/(xylim(jj+1)-xylim(jj)) )
162  END IF
163 END DO
164 !
165 !-------------------------------------------------------------------------------
166 DEALLOCATE(zx )
167 DEALLOCATE(zy )
168 IF (lhook) CALL dr_hook('GET_MESH_INDEX_CONF_PROJ',1,zhook_handle)
169 !-------------------------------------------------------------------------------
170 !
171 END SUBROUTINE get_mesh_index_conf_proj
subroutine get_mesh_index_conf_proj(KSSO, PGRID_PAR, PLAT, PLON, KINDE
subroutine xy_conf_proj(PLAT0, PLON0, PRPK, PBETA, PLATOR, PLONOR, PX, PY, PLAT, PLON)
integer, parameter jprb
Definition: parkind1.F90:32
real, save xsurf_epsilon
Definition: modd_csts.F90:88
real, dimension(:), allocatable xxlim
subroutine get_gridtype_conf_proj(PGRID_PAR, PLAT0, PLON0, PRPK, PBETA
logical lhook
Definition: yomhook.F90:15
real, dimension(:), allocatable xylim