SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_nam_grid_cartesian.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 read_nam_grid_cartesian(HPROGRAM,KGRID_PAR,KL,PGRID_PAR)
7 ! ################################################################
8 !
9 !!**** *READ_NAM_GRID_CARTESIAN* - routine to read in namelist the horizontal grid
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 !! V. Masson *Meteo France*
31 !!
32 !! MODIFICATIONS
33 !! -------------
34 !! Original 01/2004
35 !-------------------------------------------------------------------------------
36 !
37 !* 0. DECLARATIONS
38 ! ------------
39 !
40 USE mode_pos_surf
41 !
42 USE modi_open_namelist
43 USE modi_close_namelist
44 USE modi_get_luout
45 !
47 !
48 !
49 USE yomhook ,ONLY : lhook, dr_hook
50 USE parkind1 ,ONLY : jprb
51 !
52 IMPLICIT NONE
53 !
54 !* 0.1 Declarations of arguments
55 ! -------------------------
56 !
57  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! calling program
58 INTEGER, INTENT(INOUT) :: kgrid_par ! size of PGRID_PAR
59 INTEGER, INTENT(OUT) :: kl ! number of points
60 REAL, DIMENSION(KGRID_PAR), INTENT(OUT) :: pgrid_par ! parameters defining this grid
61 !
62 !* 0.2 Declarations of local variables
63 ! -------------------------------
64 !
65 INTEGER :: iluout ! output listing logical unit
66 INTEGER :: ilunam ! namelist file logical unit
67 INTEGER :: ji, jj ! loop counters
68 INTEGER :: jl ! loop counter
69 
70 REAL, DIMENSION(:), ALLOCATABLE :: zx ! X conformal coordinate of grid mesh
71 REAL, DIMENSION(:), ALLOCATABLE :: zy ! Y conformal coordinate of grid mesh
72 REAL, DIMENSION(:), ALLOCATABLE :: zdx ! X grid mesh size
73 REAL, DIMENSION(:), ALLOCATABLE :: zdy ! Y grid mesh size
74 !
75 !* 0.3 Declarations of namelist
76 ! ------------------------
77 !
78 REAL :: xlat0 ! reference latitude
79 REAL :: xlon0 ! reference longitude
80 INTEGER :: nimax ! number of points in I direction
81 INTEGER :: njmax ! number of points in J direction
82 REAL :: xdx ! increment in X direction (in meters)
83 REAL :: xdy ! increment in Y direction (in meters)
84 !
85 REAL, DIMENSION(:), POINTER :: zgrid_par
86 !
87 LOGICAL :: gfound
88 REAL(KIND=JPRB) :: zhook_handle
89 !
90 namelist/nam_cartesian/xlat0, xlon0, nimax, njmax, xdx, xdy
91 !
92 !------------------------------------------------------------------------------
93 !
94 !* 1. opening of namelist
95 !
96 IF (lhook) CALL dr_hook('READ_NAM_GRID_CARTESIAN',0,zhook_handle)
97  CALL get_luout(hprogram,iluout)
98 !
99  CALL open_namelist(hprogram,ilunam)
100 !
101 !---------------------------------------------------------------------------
102 !
103 !* 2. Reading of projection parameters
104 ! --------------------------------
105 !
106  CALL posnam(ilunam,'NAM_CARTESIAN',gfound,iluout)
107 IF (gfound) READ(unit=ilunam,nml=nam_cartesian)
108 !
109 !---------------------------------------------------------------------------
110  CALL close_namelist(hprogram,ilunam)
111 !---------------------------------------------------------------------------
112 !
113 !* 3. Number of points
114 ! ----------------
115 !
116 kl = nimax * njmax
117 !
118 !---------------------------------------------------------------------------
119 !
120 !* 3. Array of X and Y coordinates
121 ! ----------------------------
122 !
123 !
124 ALLOCATE(zx(kl))
125 ALLOCATE(zy(kl))
126 DO jj=1,njmax
127  DO ji=1,nimax
128  jl = ji + (jj-1) * nimax
129  zx(jl) = float(ji) * xdx
130  zy(jl) = float(jj) * xdy
131  END DO
132 END DO
133 !
134 !---------------------------------------------------------------------------
135 !
136 !* 4. Array of X and Y increments
137 ! ---------------------------
138 !
139 ALLOCATE(zdx(kl))
140 ALLOCATE(zdy(kl))
141 zdx(:) = xdx
142 zdy(:) = xdy
143 !
144 !---------------------------------------------------------------------------
145 !
146 !* 8. All this information stored into pointer PGRID_PAR
147 ! --------------------------------------------------
148 !
149  CALL put_gridtype_cartesian(zgrid_par,xlat0,xlon0, &
150  nimax,njmax, &
151  zx,zy,zdx,zdy )
152 !
153 !---------------------------------------------------------------------------
154 DEALLOCATE(zx)
155 DEALLOCATE(zy)
156 DEALLOCATE(zdx)
157 DEALLOCATE(zdy)
158 !---------------------------------------------------------------------------
159 !
160 !* 1st call : initializes dimension
161 !
162 IF (kgrid_par==0) THEN
163  kgrid_par = SIZE(zgrid_par)
164 !
165 ELSE
166 !
167 !* 2nd call : initializes grid array
168 !
169  pgrid_par(:) = 0.
170  pgrid_par(:) = zgrid_par
171 END IF
172 !
173 DEALLOCATE(zgrid_par)
174 IF (lhook) CALL dr_hook('READ_NAM_GRID_CARTESIAN',1,zhook_handle)
175 !
176 !---------------------------------------------------------------------------
177 !
178 END SUBROUTINE read_nam_grid_cartesian
subroutine put_gridtype_cartesian(PGRID_PAR, PLAT0, PLON0, KIMAX, KJMAX, PX, PY, PDX, PDY)
subroutine close_namelist(HPROGRAM, KLUNAM)
subroutine posnam(KULNAM, HDNAML, OFOUND, KLUOUT)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine read_nam_grid_cartesian(HPROGRAM, KGRID_PAR, KL, PGRID_PAR)
subroutine open_namelist(HPROGRAM, KLUNAM, HFILE)