SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
get_mesh_index.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(KLUOUT,KNBLINES,PLAT,PLON,KINDEX,PVALUE,PNODATA,KSSO,KISSOX,KISSOY)
7 ! ##############################################################
8 !
9 !!**** *GET_MESH_INDEX* get the grid mesh where point (lat,lon) is located
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !! METHOD
15 !! ------
16 !!
17 !! REFERENCE
18 !! ---------
19 !!
20 !! AUTHOR
21 !! ------
22 !!
23 !! V. Masson Meteo-France
24 !!
25 !! MODIFICATION
26 !! ------------
27 !!
28 !! Original 12/09/95
29 !! P. Samuelsson SMHI 10/2014 Rotated lonlat
30 !!
31 !----------------------------------------------------------------------------
32 !
33 !* 0. DECLARATION
34 ! -----------
35 !
36 USE modd_pgd_grid, ONLY : cgrid, xgrid_par, ngrid_par
38 !
39 !
40 USE yomhook ,ONLY : lhook, dr_hook
41 USE parkind1 ,ONLY : jprb
42 !
43 USE modi_abor1_sfx
44 !
45 USE modi_get_mesh_index_conf_proj
46 !
47 USE modi_get_mesh_index_gauss
48 !
49 USE modi_get_mesh_index_ign
50 !
51 USE modi_get_mesh_index_lonlat_reg
52 !
53 USE modi_get_mesh_index_lonlatval
54 !
55 USE modi_get_mesh_index_lonlat_rot
56 IMPLICIT NONE
57 !
58 !* 0.1 Declaration of arguments
59 ! ------------------------
60 !
61 INTEGER, INTENT(IN) :: kluout ! output listing
62 INTEGER, INTENT(IN) :: knblines
63 REAL, DIMENSION(:), INTENT(IN) :: plat ! latitude of the point
64 REAL, DIMENSION(:), INTENT(IN) :: plon ! longitude of the point
65 INTEGER, DIMENSION(:,:), INTENT(OUT) :: kindex ! index of the grid mesh where the point is
66 !
67 REAL, DIMENSION(:), OPTIONAL, INTENT(IN) :: pvalue ! value of the point to add
68 REAL, OPTIONAL, INTENT(IN) :: pnodata
69 !
70 INTEGER, OPTIONAL, INTENT(IN) :: ksso ! number of subgrid mesh in each direction
71 INTEGER, DIMENSION(:,:), OPTIONAL, INTENT(OUT) :: kissox ! X index of the subgrid mesh where the point is
72 INTEGER, DIMENSION(:,:), OPTIONAL, INTENT(OUT) :: kissoy ! Y index of the subgrid mesh where the point is
73 !
74 !* 0.2 Declaration of other local variables
75 ! ------------------------------------
76 !
77 INTEGER :: isso
78 INTEGER, DIMENSION(NOVMX,SIZE(PLAT)) :: iissox
79 INTEGER, DIMENSION(NOVMX,SIZE(PLAT)) :: iissoy
80 REAL(KIND=JPRB) :: zhook_handle
81 !----------------------------------------------------------------------------
82 !
83 !* 1. Get position
84 ! ------------
85 !
86 IF (lhook) CALL dr_hook('GET_MESH_INDEX',0,zhook_handle)
87 SELECT CASE (cgrid)
88 !
89  CASE("CONF PROJ ","LONLAT REG","GAUSS ","IGN ","LONLATVAL ","LONLAT ROT")
90  IF (present(ksso) .AND. present(kissox) .AND. present(kissoy)) THEN
91  isso = ksso
92  ELSE
93  isso = 0
94  ENDIF
95  !
96  IF (cgrid=="CONF PROJ ") THEN
97  CALL get_mesh_index_conf_proj(ngrid_par,isso,xgrid_par,plat,plon,kindex,iissox,iissoy)
98  ENDIF
99  IF (cgrid=="LONLAT REG") THEN
100  IF (present(pvalue) .AND. present(pnodata)) THEN
101  CALL get_mesh_index_lonlat_reg(ngrid_par,isso,xgrid_par,plat,plon,kindex,iissox,iissoy, &
102  pvalue,pnodata)
103  ELSE
104  CALL get_mesh_index_lonlat_reg(ngrid_par,isso,xgrid_par,plat,plon,kindex,iissox,iissoy)
105  ENDIF
106  ENDIF
107  IF (cgrid=="GAUSS ") THEN
108  IF (present(pvalue) .AND. present(pnodata)) THEN
109  CALL get_mesh_index_gauss(knblines,ngrid_par,isso,xgrid_par,plat,plon,kindex,iissox,iissoy, &
110  pvalue,pnodata)
111  ELSE
112  CALL get_mesh_index_gauss(knblines,ngrid_par,isso,xgrid_par,plat,plon,kindex,iissox,iissoy)
113  ENDIF
114  ENDIF
115  IF (cgrid=="IGN ") THEN
116  IF (present(pvalue) .AND. present(pnodata)) THEN
117  CALL get_mesh_index_ign(ngrid_par,isso,xgrid_par,plat,plon,kindex,iissox,iissoy, &
118  pvalue,pnodata)
119  ELSE
120  CALL get_mesh_index_ign(ngrid_par,isso,xgrid_par,plat,plon,kindex,iissox,iissoy)
121  ENDIF
122  ENDIF
123  IF (cgrid=="LONLATVAL ") &
124  CALL get_mesh_index_lonlatval(ngrid_par,isso,xgrid_par,plat,plon,kindex,iissox,iissoy)
125  IF (cgrid=="LONLAT ROT") THEN
126  CALL get_mesh_index_lonlat_rot(ngrid_par,SIZE(plat),xgrid_par,plat,plon,kindex,isso,iissox,iissoy)
127  ENDIF
128  !
129  IF (present(ksso) .AND. present(kissox) .AND. present(kissoy)) THEN
130  kissox = iissox
131  kissoy = iissoy
132  ENDIF
133 
134  CASE default
135  WRITE(kluout,*) 'error in physiographic fields computations (routine GET_MESH_INDEX)'
136  WRITE(kluout,*) 'It is impossible to retrieve geographical coordinates (latitude, longitude)'
137  WRITE(kluout,*) 'for the following grid type: CGRID = ', cgrid
138  CALL abor1_sfx('GET_MESH_INDEX: IMPOSSIBLE TO RETRIEVE GEOGRAPHICAL COORDINATES')
139 END SELECT
140 IF (lhook) CALL dr_hook('GET_MESH_INDEX',1,zhook_handle)
141 !
142 !-------------------------------------------------------------------------------
143 !
144 END SUBROUTINE get_mesh_index
subroutine get_mesh_index(KLUOUT, KNBLINES, PLAT, PLON, KINDEX, PVALUE, PNODATA, KSSO, KISSOX, KISSOY)
subroutine get_mesh_index_lonlat_rot(KGRID_PAR, KL, PGRID_PAR, PLAT, PLON, KINDEX, KSSO, KISSOX, KISSOY)
subroutine get_mesh_index_ign(KGRID_PAR, KSSO, PGRID_PAR, PLAT, PLON, KINDEX, KISSOX, KISSOY, PVALUE, PNODATA)
subroutine get_mesh_index_lonlatval(KGRID_PAR, KSSO, PGRID_PAR, PLAT, PLON, KINDEX, KISSOX, KISSOY)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine get_mesh_index_gauss(KNBLINES, KGRID_PAR, KSSO, PGRID_PAR, PLAT, PLON, KINDEX, KISSOX, KISSOY, PVALUE, PNODATA)
subroutine get_mesh_index_conf_proj(KGRID_PAR, KSSO, PGRID_PAR, PLAT, PLON, KINDEX, KISSOX, KISSOY)
subroutine get_mesh_index_lonlat_reg(KGRID_PAR, KSSO, PGRID_PAR, PLAT, PLON, KINDEX, KISSOX, KISSOY, PVALUE, PNODATA)