SURFEX v8.1
General documentation of Surfex
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_cartesian
41 USE modi_get_mesh_corner_conf_proj
42 USE modi_get_mesh_corner_gauss
43 USE modi_get_mesh_corner_ign
44 USE modi_get_mesh_corner_lonlat_reg
45 USE modi_get_mesh_corner_lonlatval
46 !
47 USE modi_abor1_sfx
48 !
49 USE yomhook ,ONLY : lhook, dr_hook
50 USE parkind1 ,ONLY : jprb
51 !
52 IMPLICIT NONE
53 !
54 !* 0.1 Declaration of arguments
55 ! ------------------------
56 !
57 !
58 TYPE(surf_atm_grid_t), INTENT(INOUT) :: UG
59 !
60 INTEGER, INTENT(IN) :: KLUOUT ! output listing
61 REAL, DIMENSION(:,:), INTENT(OUT) :: PCORNER_LAT ! Grid corner Latitude
62 REAL, DIMENSION(:,:), INTENT(OUT) :: PCORNER_LON ! Grid corner Longitude
63 !
64 !* 0.2 Declaration of other local variables
65 ! ------------------------------------
66 !
67 INTEGER :: IL, IC
68 !
69 REAL(KIND=JPRB) :: ZHOOK_HANDLE
70 !
71 !----------------------------------------------------------------------------
72 !
73 !* 1. Get position
74 ! ------------
75 !
76 IF (lhook) CALL dr_hook('GET_MESH_CORNER',0,zhook_handle)
77 !
78 il = SIZE(pcorner_lat,1)
79 ic = SIZE(pcorner_lat,2)
80 !
81 SELECT CASE (ug%G%CGRID)
82 !
83  CASE("LONLAT REG")
84  CALL get_mesh_corner_lonlat_reg(ug%G%NGRID_PAR,il,ic,ug%G%XGRID_PAR,pcorner_lat,pcorner_lon)
85  CASE("CARTESIAN")
86  CALL get_mesh_corner_cartesian(ug%G%NGRID_PAR,il,ic,ug%G%XGRID_PAR,pcorner_lat,pcorner_lon)
87  CASE("CONF PROJ")
88  CALL get_mesh_corner_conf_proj(ug%G%NGRID_PAR,il,ic,ug%G%XGRID_PAR,pcorner_lat,pcorner_lon)
89  CASE("GAUSS ")
90  CALL get_mesh_corner_gauss(ug%G%NGRID_PAR,il,ic,ug%G%XGRID_PAR,pcorner_lat,pcorner_lon)
91  CASE("IGN ")
92  CALL get_mesh_corner_ign(ug%G%NGRID_PAR,il,ic,ug%G%XGRID_PAR,pcorner_lat,pcorner_lon)
93  CASE("LONLATVAL ")
94  CALL get_mesh_corner_lonlatval(ug%G%NGRID_PAR,il,ic,ug%G%XGRID_PAR,pcorner_lat,pcorner_lon)
95  CASE DEFAULT
96  WRITE(kluout,*) 'error in grid cell corner computations (routine GET_MESH_CORNER)'
97  WRITE(kluout,*) 'It is impossible to retrieve geographical coordinates (latitude, longitude)'
98  WRITE(kluout,*) 'for the following grid type: CGRID = ', ug%G%CGRID
99  CALL abor1_sfx('GET_MESH_CORNER: IMPOSSIBLE TO CALCULATE GRID CELL CORNER')
100 !
101 END SELECT
102 !
103 IF (lhook) CALL dr_hook('GET_MESH_CORNER',1,zhook_handle)
104 !
105 !-------------------------------------------------------------------------------
106 !
107 END SUBROUTINE get_mesh_corner
subroutine get_mesh_corner(UG, KLUOUT, PCORNER_LAT, PCORNER_LON)
subroutine get_mesh_corner_lonlat_reg(KGRID_PAR, KL, KC, PGRID_PAR, PC
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:7
subroutine get_mesh_corner_ign(KGRID_PAR, KL, KC, PGRID_PAR, PCORNER_L
integer, parameter jprb
Definition: parkind1.F90:32
subroutine get_mesh_corner_cartesian(KGRID_PAR, KL, KC, PGRID_PAR, PCO
subroutine get_mesh_corner_conf_proj(KGRID_PAR, KL, KC, PGRID_PAR, PCO
logical lhook
Definition: yomhook.F90:15
subroutine get_mesh_corner_gauss(KGRID_PAR, KL, KC, PGRID_PAR, PCORNER
subroutine get_mesh_corner_lonlatval(KGRID_PAR, KL, KC, PGRID_PAR, PCO