SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
latlon_gridtype_lonlat_rot.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_lonlat_rot(KGRID_PAR,KL,PGRID_PAR,PLAT,PLON,PMESH_SIZE,PDIR)
7 ! #########################################################################
8 !
9 !!**** *LATLON_GRIDTYPE_LONLAT_ROT* - 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 !! P. Samuelsson SMHI
31 !!
32 !! MODIFICATIONS
33 !! -------------
34 !! Original 12/2012
35 !-------------------------------------------------------------------------------
36 !
37 !* 0. DECLARATIONS
38 ! ------------
39 !
40 USE modd_csts, ONLY : xpi, xradius
41 !
43 !RJ: missing modi
44 USE modi_regrot_lonlat_rot
45 !
46 !
47 !
48 USE yomhook ,ONLY : lhook, dr_hook
49 USE parkind1 ,ONLY : jprb
50 !
51 IMPLICIT NONE
52 !
53 !* 0.1 Declarations of arguments
54 ! -------------------------
55 !
56 INTEGER, INTENT(IN) :: kgrid_par ! size of PGRID_PAR
57 INTEGER, INTENT(IN) :: kl ! number of points
58 REAL, DIMENSION(KGRID_PAR), INTENT(IN) :: pgrid_par ! parameters defining this grid
59 REAL, DIMENSION(KL), INTENT(OUT) :: plat ! latitude (degrees)
60 REAL, DIMENSION(KL), INTENT(OUT) :: plon ! longitude (degrees)
61 REAL, DIMENSION(KL), INTENT(OUT) :: pmesh_size ! mesh size (m2)
62 REAL, DIMENSION(KL), INTENT(OUT) :: pdir ! direction of main grid Y axis (deg. from N, clockwise)
63 !
64 !* 0.2 Declarations of local variables
65 ! -------------------------------
66 !
67 REAL :: zwest ! West longitude in rotated grid (degrees)
68 REAL :: zsouth ! South latitude in rotated grid (degrees)
69 REAL :: zdlon ! Longitudal grid spacing (degrees)
70 REAL :: zdlat ! Latitudal grid spacing (degrees)
71 REAL :: zpolon ! Longitude of rotated pole (degrees)
72 REAL :: zpolat ! Latitude of rotated pole (degrees)
73 INTEGER :: ilon ! number of points in longitude
74 INTEGER :: ilat ! number of points in latitude
75 !
76 REAL, DIMENSION(KL) :: zlon, zlat ! rotated longitude, latitude
77 INTEGER :: jlon, jlat, jl
78 !
79 REAL(KIND=JPRB) :: zhook_handle
80 !---------------------------------------------------------------------------
81 !
82 !* 1. Grid parameters
83 ! ---------------
84 !
85 IF (lhook) CALL dr_hook('LATLON_GRIDTYPE_LONLAT_ROT',0,zhook_handle)
86 !
87  CALL get_gridtype_lonlat_rot(pgrid_par, &
88  zwest,zsouth,zdlon,zdlat,zpolon,zpolat, &
89  ilon,ilat,plon=plon,plat=plat )
90 !
91 !-----------------------------------------------------------------------------
92 !
93 !* 2. Compute grid size
94 ! -----------------
95 !
96  CALL regrot_lonlat_rot(plon,plat,zlon,zlat, &
97  kl,1,kl,1, &
98  zpolon,zpolat,1 )
99 !
100 pmesh_size(:) = ( xpi * xradius /180. )**2 * zdlat * zdlon * cos(zlat(:)*xpi/180.)
101 !
102 !-----------------------------------------------------------------------------
103 !
104 !* 4. Direction of of grid from North for each grid point
105 ! ---------------------------------------------------
106 !
107 pdir(:) = 0.
108 IF (lhook) CALL dr_hook('LATLON_GRIDTYPE_LONLAT_ROT',1,zhook_handle)
109 !
110 !---------------------------------------------------------------------------
111 !
112 END SUBROUTINE latlon_gridtype_lonlat_rot
113 
subroutine get_gridtype_lonlat_rot(PGRID_PAR, PWEST, PSOUTH, PDLON, PDLAT, PPOLON, PPOLAT, KLON, KLAT, KL, PLON, PLAT)
subroutine regrot_lonlat_rot(PXREG, PYREG, PXROT, PYROT, KXDIM, KYDIM, KX, KY, PXCEN, PYCEN, KCALL)
subroutine latlon_gridtype_lonlat_rot(KGRID_PAR, KL, PGRID_PAR, PLAT, PLON, PMESH_SIZE, PDIR)