SURFEX v8.1
General documentation of Surfex
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(UG,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 !
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 TYPE(surf_atm_grid_t), INTENT(INOUT) :: UG
62 !
63 INTEGER, INTENT(IN) :: KLUOUT ! output listing
64 INTEGER, INTENT(IN) :: KNBLINES
65 REAL, DIMENSION(:), INTENT(IN) :: PLAT ! latitude of the point
66 REAL, DIMENSION(:), INTENT(IN) :: PLON ! longitude of the point
67 INTEGER, DIMENSION(:,:), INTENT(OUT) :: KINDEX ! index of the grid mesh where the point is
68 !
69 REAL, DIMENSION(:), OPTIONAL, INTENT(IN) :: PVALUE ! value of the point to add
70 REAL, OPTIONAL, INTENT(IN) :: PNODATA
71 !
72 INTEGER, OPTIONAL, INTENT(IN) :: KSSO ! number of subgrid mesh in each direction
73 INTEGER, DIMENSION(:,:), OPTIONAL, INTENT(OUT) :: KISSOX ! X index of the subgrid mesh where the point is
74 INTEGER, DIMENSION(:,:), OPTIONAL, INTENT(OUT) :: KISSOY ! Y index of the subgrid mesh where the point is
75 !
76 !* 0.2 Declaration of other local variables
77 ! ------------------------------------
78 !
79 INTEGER :: ISSO
80 INTEGER, DIMENSION(NOVMX,SIZE(PLAT)) :: IISSOX
81 INTEGER, DIMENSION(NOVMX,SIZE(PLAT)) :: IISSOY
82 REAL(KIND=JPRB) :: ZHOOK_HANDLE
83 !----------------------------------------------------------------------------
84 !
85 !* 1. Get position
86 ! ------------
87 !
88 IF (lhook) CALL dr_hook('GET_MESH_INDEX',0,zhook_handle)
89 SELECT CASE (ug%G%CGRID)
90 !
91  CASE("CONF PROJ ","LONLAT REG","GAUSS ","IGN ","LONLATVAL ","LONLAT ROT")
92  IF (PRESENT(ksso) .AND. PRESENT(kissox) .AND. PRESENT(kissoy)) THEN
93  isso = ksso
94  ELSE
95  isso = 0
96  ENDIF
97  !
98  IF (ug%G%CGRID=="CONF PROJ ") THEN
99  CALL get_mesh_index_conf_proj(isso,ug%XGRID_FULL_PAR,plat,plon,kindex,iissox,iissoy)
100  ENDIF
101  IF (ug%G%CGRID=="LONLAT REG") THEN
102  IF (PRESENT(pvalue) .AND. PRESENT(pnodata)) THEN
103  CALL get_mesh_index_lonlat_reg(isso,ug%XGRID_FULL_PAR,plat,plon,kindex,iissox,iissoy, &
104  pvalue,pnodata)
105  ELSE
106  CALL get_mesh_index_lonlat_reg(isso,ug%XGRID_FULL_PAR,plat,plon,kindex,iissox,iissoy)
107  ENDIF
108  ENDIF
109  IF (ug%G%CGRID=="GAUSS ") THEN
110  IF (PRESENT(pvalue) .AND. PRESENT(pnodata)) THEN
111  CALL get_mesh_index_gauss(knblines,isso,ug%XGRID_FULL_PAR,plat,plon,kindex,iissox,iissoy, &
112  pvalue,pnodata)
113  ELSE
114  CALL get_mesh_index_gauss(knblines,isso,ug%XGRID_FULL_PAR,plat,plon,kindex,iissox,iissoy)
115  ENDIF
116  ENDIF
117  IF (ug%G%CGRID=="IGN ") THEN
118  IF (PRESENT(pvalue) .AND. PRESENT(pnodata)) THEN
119  CALL get_mesh_index_ign(isso,ug%XGRID_FULL_PAR,plat,plon,kindex,iissox,iissoy, &
120  pvalue,pnodata)
121  ELSE
122  CALL get_mesh_index_ign(isso,ug%XGRID_FULL_PAR,plat,plon,kindex,iissox,iissoy)
123  ENDIF
124  ENDIF
125  IF (ug%G%CGRID=="LONLATVAL ") &
126  CALL get_mesh_index_lonlatval(isso,ug%XGRID_FULL_PAR,plat,plon,kindex,iissox,iissoy)
127  IF (ug%G%CGRID=="LONLAT ROT") THEN
128  CALL get_mesh_index_lonlat_rot(SIZE(plat),ug%XGRID_FULL_PAR,plat,plon,kindex,isso,iissox,iissoy)
129  ENDIF
130  !
131  IF (PRESENT(ksso) .AND. PRESENT(kissox) .AND. PRESENT(kissoy)) THEN
132  kissox = iissox
133  kissoy = iissoy
134  ENDIF
135 
136  CASE DEFAULT
137  WRITE(kluout,*) 'error in physiographic fields computations (routine GET_MESH_INDEX)'
138  WRITE(kluout,*) 'It is impossible to retrieve geographical coordinates (latitude, longitude)'
139  WRITE(kluout,*) 'for the following grid type: CGRID = ', ug%G%CGRID
140  CALL abor1_sfx('GET_MESH_INDEX: IMPOSSIBLE TO RETRIEVE GEOGRAPHICAL COORDINATES')
141 END SELECT
142 IF (lhook) CALL dr_hook('GET_MESH_INDEX',1,zhook_handle)
143 !
144 !-------------------------------------------------------------------------------
145 !
146 END SUBROUTINE get_mesh_index
subroutine get_mesh_index_conf_proj(KSSO, PGRID_PAR, PLAT, PLON, KINDE
subroutine get_mesh_index_lonlat_reg(KSSO, PGRID_PAR, PLAT, PLON, KINDEX, KISSOX, KISSOY, PVALUE, PNODATA)
subroutine get_mesh_index_lonlatval(KSSO, PGRID_PAR, PLAT, PLON, KINDE
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:7
subroutine get_mesh_index_gauss(KNBLINES, KSSO, PGRID_PAR, PLAT, PLON,
integer, parameter jprb
Definition: parkind1.F90:32
subroutine get_mesh_index(UG, KLUOUT, KNBLINES, PLAT, PLON, KINDEX, PVAL
logical lhook
Definition: yomhook.F90:15
subroutine get_mesh_index_lonlat_rot(KL, PGRID_PAR, PLAT, PLON, KINDEX
subroutine get_mesh_index_ign(KSSO, PGRID_PAR, PLAT, PLON, KINDEX, KISSOX, KISSOY, PVALUE, PNODATA)