SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
latlon_gridtype_ign.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_ign(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 !!
32 !! MODIFICATIONS
33 !! -------------
34 !! Original 10/2007
35 !-------------------------------------------------------------------------------
36 !
37 !* 0. DECLARATIONS
38 ! ------------
39 !
40 USE modd_csts, ONLY : xpi
41 USE modd_ign, ONLY : xa, xdelty
42 !
44 !
45 !
46 !
47 USE yomhook ,ONLY : lhook, dr_hook
48 USE parkind1 ,ONLY : jprb
49 !
50 IMPLICIT NONE
51 !
52 !* 0.1 Declarations of arguments
53 ! -------------------------
54 !
55 INTEGER, INTENT(IN) :: kgrid_par ! size of PGRID_PAR
56 INTEGER, INTENT(IN) :: kl ! number of points
57 REAL, DIMENSION(KGRID_PAR), INTENT(IN) :: pgrid_par ! parameters defining this grid
58 REAL, DIMENSION(KL), INTENT(OUT) :: plat ! latitude (degrees)
59 REAL, DIMENSION(KL), INTENT(OUT) :: plon ! longitude (degrees)
60 REAL, DIMENSION(KL), INTENT(OUT) :: pmesh_size ! mesh size (m2)
61 REAL, DIMENSION(KL), INTENT(OUT) :: pdir ! direction of main grid Y axis (deg. from N, clockwise)
62 !
63 !* 0.2 Declarations of local variables
64 ! -------------------------------
65 !
66 REAL, DIMENSION(:), ALLOCATABLE :: zx ! X Lambert coordinate
67 REAL, DIMENSION(:), ALLOCATABLE :: zy ! Y Lambertcoordinate
68 REAL, DIMENSION(:), ALLOCATABLE :: zmap ! map factor
69 REAL, DIMENSION(:), ALLOCATABLE :: zdx ! size in X Lambert coordinate
70 REAL, DIMENSION(:), ALLOCATABLE :: zdy ! size in Y Lambert coordinate
71 REAL, DIMENSION(:), ALLOCATABLE :: zydelty ! Y + DELTY Lambert coordinate
72 REAL, DIMENSION(:), ALLOCATABLE :: zlatdy ! latitude
73 REAL, DIMENSION(:), ALLOCATABLE :: zlondy ! longitude
74 !
75 INTEGER :: ilambert ! Lambert type
76 REAL(KIND=JPRB) :: zhook_handle
77 !---------------------------------------------------------------------------
78 !
79 !* 1. Projection and 2D grid parameters
80 ! ---------------------------------
81 !
82 IF (lhook) CALL dr_hook('LATLON_GRIDTYPE_IGN',0,zhook_handle)
83 ALLOCATE(zx(SIZE(plat)))
84 ALLOCATE(zy(SIZE(plat)))
85 ALLOCATE(zdx(SIZE(plat)))
86 ALLOCATE(zdy(SIZE(plat)))
87 !
88  CALL get_gridtype_ign(pgrid_par,klambert=ilambert,px=zx,py=zy,pdx=zdx,pdy=zdy )
89 !
90 !---------------------------------------------------------------------------
91 !
92 !* 2. Computation of latitude and longitude
93 ! -------------------------------------
94 !
95  CALL latlon_ign(ilambert,zx,zy,plat,plon)
96 !
97 !-----------------------------------------------------------------------------
98 !
99 !* 3. Compute grid size (2D array)
100 ! -----------------
101 !
102 ! 3.1 Map factor
103 ! ----------
104 !
105 ALLOCATE(zmap(SIZE(plat)))
106 !
107  CALL map_factor_ign(ilambert,zx,zy,zmap)
108 !
109 ! 3.2 Grid size
110 ! ---------
111 !
112 pmesh_size(:) = zdx(:) * zdy(:) / zmap(:)**2
113 !
114 !-----------------------------------------------------------------------------
115 !
116 !* 4. Direction of Y axis (from North) for each grid point
117 ! ----------------------------------------------------
118 !
119 !* the following formulae is given for clockwise angles.
120 ALLOCATE(zydelty(SIZE(plat)))
121 ALLOCATE(zlatdy(SIZE(plat)))
122 ALLOCATE(zlondy(SIZE(plat)))
123 zydelty=zy+xdelty
124  CALL latlon_ign(ilambert,zx,zydelty,zlatdy,zlondy)
125 !
126 pdir(:)= atan( (xa(ilambert)*(zlondy(:)-plon(:))*xpi/180.) / xdelty) * xpi/180.
127 !
128 !---------------------------------------------------------------------------
129 DEALLOCATE(zx)
130 DEALLOCATE(zy)
131 DEALLOCATE(zmap)
132 DEALLOCATE(zdx)
133 DEALLOCATE(zdy)
134 DEALLOCATE(zydelty)
135 DEALLOCATE(zlatdy)
136 DEALLOCATE(zlondy)
137 IF (lhook) CALL dr_hook('LATLON_GRIDTYPE_IGN',1,zhook_handle)
138 !---------------------------------------------------------------------------
139 !
140 END SUBROUTINE latlon_gridtype_ign
141 
subroutine latlon_gridtype_ign(KGRID_PAR, KL, PGRID_PAR, PLAT, PLON, PMESH_SIZE, PDIR)
subroutine get_gridtype_ign(PGRID_PAR, KLAMBERT, KL, PX, PY, PDX, PDY, KDIMX, KDIMY, PXALL, PYALL)
subroutine latlon_ign(KLAMBERT, PX, PY, PLAT, PLON)
subroutine map_factor_ign(KLAMBERT, PX, PY, PMAP)