SURFEX v8.1
General documentation of Surfex
modd_grid_conf_projn.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 ! ################
7 ! ################
8 !
9 !!**** *MODD_GRID_CONF_PROJ_n - declaration of Arome gris characteristics
10 !!
11 !! PURPOSE
12 !! -------
13 ! Used if CINGRID_TYPE = 'CONF PROJ '
14 !
15 !!
16 !!** IMPLICIT ARGUMENTS
17 !! ------------------
18 !! None
19 !!
20 !! REFERENCE
21 !! ---------
22 !!
23 !! AUTHOR
24 !! ------
25 !! V. Masson *Meteo France*
26 !!
27 !! MODIFICATIONS
28 !! -------------
29 !! Original 20/09/02
30 !
31 !* 0. DECLARATIONS
32 ! ------------
33 !
34 USE yomhook ,ONLY : lhook, dr_hook
35 USE parkind1 ,ONLY : jprb
36 !
37 IMPLICIT NONE
38 !
39 REAL, DIMENSION(:), ALLOCATABLE :: xx ! X coordinate (meters)
40 REAL, DIMENSION(:), ALLOCATABLE :: xy ! Y coordinate (meters)
41 !
42 REAL, DIMENSION(:,:), ALLOCATABLE :: xcx
43 REAL, DIMENSION(:,:), ALLOCATABLE :: xcy
44 INTEGER, DIMENSION(:,:), ALLOCATABLE :: ncij
45 !
47 !
48 INTEGER :: nx ! number of points in X direction
49 INTEGER :: ny ! number of points in Y direction
50 !
51 REAL :: xlat0 ! reference latitude
52 REAL :: xlon0 ! reference longitude
53 REAL :: xlatori! origin latitude
54 REAL :: xlonori! origin longitude
55 REAL :: xrpk ! projection parameter for the conformal projection
56 REAL :: xbeta ! rotation parameter for the conformal projection
57 REAL :: xlatc ! centre latitude
58 REAL :: xlonc ! centre longitude
59 !
60 END TYPE grid_conf_proj_t
61 !
62 CONTAINS
63 !
64 SUBROUTINE grid_conf_proj_init(YGRIDCONF)
65 TYPE(grid_conf_proj_t), INTENT(INOUT) :: YGRIDCONF
66 REAL(KIND=JPRB) :: ZHOOK_HANDLE
67 IF (lhook) CALL dr_hook("MODD_GRID_CONF_PROJ_n:GRID_CONF_PROJ_INIT",0,zhook_handle)
68 ygridconf%NX = 0
69 ygridconf%NY = 0
70 ygridconf%XLAT0 = 0.
71 ygridconf%XLON0 = 0.
72 ygridconf%XLATORI = 0.
73 ygridconf%XLONORI = 0.
74 ygridconf%XRPK = 0.
75 ygridconf%XBETA = 0.
76 ygridconf%XLATC = 0.
77 ygridconf%XLONC = 0.
78 IF (lhook) CALL dr_hook("MODD_GRID_CONF_PROJ_n:GRID_CONF_PROJ_INIT",1,zhook_handle)
79 END SUBROUTINE grid_conf_proj_init
80 !
81 !
82 END MODULE modd_grid_conf_proj_n
real, dimension(:,:), allocatable xcx
real, dimension(:), allocatable xy
real, dimension(:), allocatable xx
integer, dimension(:,:), allocatable ncij
integer, parameter jprb
Definition: parkind1.F90:32
real, dimension(:,:), allocatable xcy
logical lhook
Definition: yomhook.F90:15
subroutine grid_conf_proj_init(YGRIDCONF)