SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
get_mesh_corner.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_corner (UG, &
7  kluout,pcorner_lat,pcorner_lon)
8 ! ##############################################################
9 !
10 !!**** *GET_MESH_CORNER* get the grid cell corner for each (lat,lon)
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !! METHOD
16 !! ------
17 !!
18 !! REFERENCE
19 !! ---------
20 !!
21 !! AUTHOR
22 !! ------
23 !!
24 !! B. Decharme Meteo-France
25 !!
26 !! MODIFICATION
27 !! ------------
28 !!
29 !! Original 10/2013
30 !!
31 !----------------------------------------------------------------------------
32 !
33 !* 0. DECLARATION
34 ! -----------
35 !
36 !
37 !
39 !
40 USE modi_get_mesh_corner_conf_proj
41 USE modi_get_mesh_corner_gauss
42 USE modi_get_mesh_corner_ign
43 USE modi_get_mesh_corner_lonlat_reg
44 USE modi_get_mesh_corner_lonlatval
45 !
46 USE modi_abor1_sfx
47 !
48 USE yomhook ,ONLY : lhook, dr_hook
49 USE parkind1 ,ONLY : jprb
50 !
51 IMPLICIT NONE
52 !
53 !* 0.1 Declaration of arguments
54 ! ------------------------
55 !
56 !
57 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
58 !
59 INTEGER, INTENT(IN) :: kluout ! output listing
60 REAL, DIMENSION(:,:), INTENT(OUT) :: pcorner_lat ! Grid corner Latitude
61 REAL, DIMENSION(:,:), INTENT(OUT) :: pcorner_lon ! Grid corner Longitude
62 !
63 !* 0.2 Declaration of other local variables
64 ! ------------------------------------
65 !
66 INTEGER :: il, ic
67 !
68 REAL(KIND=JPRB) :: zhook_handle
69 !
70 !----------------------------------------------------------------------------
71 !
72 !* 1. Get position
73 ! ------------
74 !
75 IF (lhook) CALL dr_hook('GET_MESH_CORNER',0,zhook_handle)
76 !
77 il = SIZE(pcorner_lat,1)
78 ic = SIZE(pcorner_lat,2)
79 !
80 SELECT CASE (ug%CGRID)
81 !
82  CASE("LONLAT REG")
83  CALL get_mesh_corner_lonlat_reg(ug%NGRID_PAR,il,ic,ug%XGRID_PAR,pcorner_lat,pcorner_lon)
84  CASE("CONF PROJ")
85  CALL get_mesh_corner_conf_proj(ug%NGRID_PAR,il,ic,ug%XGRID_PAR,pcorner_lat,pcorner_lon)
86  CASE("GAUSS ")
87  CALL get_mesh_corner_gauss(ug%NGRID_PAR,il,ic,ug%XGRID_PAR,pcorner_lat,pcorner_lon)
88  CASE("IGN ")
89  CALL get_mesh_corner_ign(ug%NGRID_PAR,il,ic,ug%XGRID_PAR,pcorner_lat,pcorner_lon)
90  CASE("LONLATVAL ")
91  CALL get_mesh_corner_lonlatval(ug%NGRID_PAR,il,ic,ug%XGRID_PAR,pcorner_lat,pcorner_lon)
92  CASE default
93  WRITE(kluout,*) 'error in grid cell corner computations (routine GET_MESH_CORNER)'
94  WRITE(kluout,*) 'It is impossible to retrieve geographical coordinates (latitude, longitude)'
95  WRITE(kluout,*) 'for the following grid type: CGRID = ', ug%CGRID
96  CALL abor1_sfx('GET_MESH_CORNER: IMPOSSIBLE TO CALCULATE GRID CELL CORNER')
97 !
98 END SELECT
99 !
100 IF (lhook) CALL dr_hook('GET_MESH_CORNER',1,zhook_handle)
101 !
102 !-------------------------------------------------------------------------------
103 !
104 END SUBROUTINE get_mesh_corner
subroutine get_mesh_corner_gauss(KGRID_PAR, KL, KC, PGRID_PAR, PCORNER_LAT, PCORNER_LON)
subroutine get_mesh_corner_lonlatval(KGRID_PAR, KL, KC, PGRID_PAR, PCORNER_LAT, PCORNER_LON)
subroutine get_mesh_corner(UG, KLUOUT, PCORNER_LAT, PCORNER_LON)
subroutine get_mesh_corner_ign(KGRID_PAR, KL, KC, PGRID_PAR, PCORNER_LAT, PCORNER_LON)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine get_mesh_corner_conf_proj(KGRID_PAR, KL, KC, PGRID_PAR, PCORNER_LAT, PCORNER_LON)
subroutine get_mesh_corner_lonlat_reg(KGRID_PAR, KL, KC, PGRID_PAR, PCORNER_LAT, PCORNER_LON)