SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
latlon_gridtype_lonlatval.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 latlon_gridtype_lonlatval(KGRID_PAR,KL,PGRID_PAR,PLAT,PLON,PMESH_SIZE,PDIR)
7 ! #########################################################################
8 !
9 !!**** *LATLON_GRIDTYPE_IGN* - routine to compute the horizontal geographic fields
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !!** METHOD
15 !! ------
16 !!
17 !! EXTERNAL
18 !! --------
19 !!
20 !!
21 !! IMPLICIT ARGUMENTS
22 !! ------------------
23 !!
24 !! REFERENCE
25 !! ---------
26 !!
27 !!
28 !! AUTHOR
29 !! ------
30 !! E. Martin *Meteo France*
31 !! M Lafaysse 08/2013 missing deallocate
32 !! MODIFICATIONS
33 !! -------------
34 !! Original 10/2007
35 !-------------------------------------------------------------------------------
36 !
37 !* 0. DECLARATIONS
38 ! ------------
39 !
40 USE modd_csts, ONLY : xpi, xradius
41 !
43 !
44 !
45 !
46 USE yomhook ,ONLY : lhook, dr_hook
47 USE parkind1 ,ONLY : jprb
48 !
49 IMPLICIT NONE
50 !
51 !* 0.1 Declarations of arguments
52 ! -------------------------
53 !
54 INTEGER, INTENT(IN) :: kgrid_par ! size of PGRID_PAR
55 INTEGER, INTENT(IN) :: kl ! number of points
56 REAL, DIMENSION(KGRID_PAR), INTENT(IN) :: pgrid_par ! parameters defining this grid
57 REAL, DIMENSION(KL), INTENT(OUT) :: plat ! latitude (degrees)
58 REAL, DIMENSION(KL), INTENT(OUT) :: plon ! longitude (degrees)
59 REAL, DIMENSION(KL), INTENT(OUT) :: pmesh_size ! mesh size (m2)
60 REAL, DIMENSION(KL), INTENT(OUT) :: pdir ! direction of main grid Y axis (deg. from N, clockwise)
61 !
62 !* 0.2 Declarations of local variables
63 ! -------------------------------
64 !
65 REAL, DIMENSION(:), ALLOCATABLE :: zx ! X Lambert coordinate
66 REAL, DIMENSION(:), ALLOCATABLE :: zy ! Y Lambertcoordinate
67 REAL, DIMENSION(:), ALLOCATABLE :: zdx ! size in X Lambert coordinate
68 REAL, DIMENSION(:), ALLOCATABLE :: zdy ! size in Y Lambert coordinate
69 REAL, DIMENSION(:), ALLOCATABLE :: zdlat ! grid size in latitude unit
70 REAL, DIMENSION(:), ALLOCATABLE :: zdlon ! grid size in longitude unit
71 REAL(KIND=JPRB) :: zhook_handle
72 !---------------------------------------------------------------------------
73 !
74 !* 1. Projection and 2D grid parameters
75 ! ---------------------------------
76 !
77 IF (lhook) CALL dr_hook('LATLON_GRIDTYPE_LONLATVAL',0,zhook_handle)
78 ALLOCATE(zx(SIZE(plat)))
79 ALLOCATE(zy(SIZE(plat)))
80 ALLOCATE(zdx(SIZE(plat)))
81 ALLOCATE(zdy(SIZE(plat)))
82 ALLOCATE(zdlon(SIZE(plat)))
83 ALLOCATE(zdlat(SIZE(plat)))
84 
85 !
86  CALL get_gridtype_lonlatval(pgrid_par,px=zx,py=zy,pdx=zdx,pdy=zdy )
87 !
88 !---------------------------------------------------------------------------
89 !
90 !* 2. Computation of latitude and longitude
91 ! -------------------------------------
92 !
93  CALL latlon_lonlatval(zx,zy,plat,plon)
94 !
95 !-----------------------------------------------------------------------------
96 !
97 !* 3. Compute grid size (2D array)
98 ! -----------------
99 !
100 !
101 zdlat = zdy
102 zdlon = zdx
103 !
104 pmesh_size(:) = xradius**2 * xpi/180.*(zdlon(:)) &
105  * (sin((plat(:)+zdlat(:)/2.)*xpi/180.)-sin((plat(:)-zdlat(:)/2.)*xpi/180.))
106 !
107 !-----------------------------------------------------------------------------
108 !
109 !* 4. Direction of Y axis (from North) for each grid point
110 ! ----------------------------------------------------
111 !
112 pdir(:) = 0.
113 
114 
115 
116 DEALLOCATE(zx)
117 DEALLOCATE(zy)
118 DEALLOCATE(zdx)
119 DEALLOCATE(zdy)
120 DEALLOCATE(zdlon)
121 DEALLOCATE(zdlat)
122 
123 
124 
125 IF (lhook) CALL dr_hook('LATLON_GRIDTYPE_LONLATVAL',1,zhook_handle)
126 !
127 !---------------------------------------------------------------------------
128 !
129 END SUBROUTINE latlon_gridtype_lonlatval
subroutine get_gridtype_lonlatval(PGRID_PAR, KL, PX, PY, PDX, PDY)
subroutine latlon_gridtype_lonlatval(KGRID_PAR, KL, PGRID_PAR, PLAT, PLON, PMESH_SIZE, PDIR)
subroutine latlon_lonlatval(PX, PY, PLAT, PLON)