SURFEX v8.1
General documentation of Surfex
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(PGRID_FULL_PAR,KDIM_FULL,HPROGRAM,KGRID_PAR,KL,PGRID_PAR,HDIR)
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 modd_surfex_mpi, ONLY : nrank, nsize_task
41 !
42 USE mode_pos_surf
43 !
44 USE modi_open_namelist
45 USE modi_close_namelist
46 USE modi_get_luout
47 !
50 !
51 USE yomhook ,ONLY : lhook, dr_hook
52 USE parkind1 ,ONLY : jprb
53 !
54 IMPLICIT NONE
55 !
56 !* 0.1 Declarations of arguments
57 ! -------------------------
58 !
59 REAL, DIMENSION(:), POINTER :: PGRID_FULL_PAR
60 INTEGER, INTENT(IN) :: KDIM_FULL
61 !
62  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! calling program
63 INTEGER, INTENT(INOUT) :: KGRID_PAR ! size of PGRID_PAR
64 INTEGER, INTENT(OUT) :: KL ! number of points
65 REAL, DIMENSION(KGRID_PAR), INTENT(OUT) :: PGRID_PAR ! parameters defining this grid
66  CHARACTER(LEN=1), INTENT(IN) :: HDIR
67 !
68 !* 0.2 Declarations of local variables
69 ! -------------------------------
70 !
71 INTEGER :: ILUOUT ! output listing logical unit
72 INTEGER :: ILUNAM ! namelist file logical unit
73 INTEGER :: JI, JJ ! loop counters
74 INTEGER :: JL ! loop counter
75 
76 REAL, DIMENSION(:), ALLOCATABLE :: ZX, ZX0 ! X conformal coordinate of grid mesh
77 REAL, DIMENSION(:), ALLOCATABLE :: ZY, ZY0 ! Y conformal coordinate of grid mesh
78 REAL, DIMENSION(:), ALLOCATABLE :: ZDX, ZDX0 ! X grid mesh size
79 REAL, DIMENSION(:), ALLOCATABLE :: ZDY, ZDY0 ! Y grid mesh size
80 !
81 !* 0.3 Declarations of namelist
82 ! ------------------------
83 !
84 REAL :: XLAT0 ! reference latitude
85 REAL :: XLON0 ! reference longitude
86 INTEGER :: NIMAX ! number of points in I direction
87 INTEGER :: NJMAX ! number of points in J direction
88 REAL :: XDX ! increment in X direction (in meters)
89 REAL :: XDY ! increment in Y direction (in meters)
90 !
91 REAL, DIMENSION(:), POINTER :: ZGRID_PAR
92 !
93 LOGICAL :: GFOUND
94 REAL(KIND=JPRB) :: ZHOOK_HANDLE
95 !
96 NAMELIST/nam_cartesian/xlat0, xlon0, nimax, njmax, xdx, xdy
97 !
98 !------------------------------------------------------------------------------
99 !
100 !* 1. opening of namelist
101 !
102 IF (lhook) CALL dr_hook('READ_NAM_GRID_CARTESIAN',0,zhook_handle)
103  CALL get_luout(hprogram,iluout)
104 !
105 IF (hdir/='H') THEN
106  !
107  CALL open_namelist(hprogram,ilunam)
108  !
109  !---------------------------------------------------------------------------
110  !
111  !* 2. Reading of projection parameters
112  ! --------------------------------
113  !
114  CALL posnam(ilunam,'NAM_CARTESIAN',gfound,iluout)
115  IF (gfound) READ(unit=ilunam,nml=nam_cartesian)
116  !
117  !---------------------------------------------------------------------------
118  CALL close_namelist(hprogram,ilunam)
119  !---------------------------------------------------------------------------
120  !
121  !* 3. Number of points
122  ! ----------------
123  !
124  kl = nimax * njmax
125  !
126  !---------------------------------------------------------------------------
127  !
128  !* 3. Array of X and Y coordinates
129  ! ----------------------------
130  !
131  !
132  ALLOCATE(zx(kl))
133  ALLOCATE(zy(kl))
134  DO jj=1,njmax
135  DO ji=1,nimax
136  jl = ji + (jj-1) * nimax
137  zx(jl) = float(ji) * xdx
138  zy(jl) = float(jj) * xdy
139  END DO
140  END DO
141  !
142  !---------------------------------------------------------------------------
143  !
144  !* 4. Array of X and Y increments
145  ! ---------------------------
146  !
147  ALLOCATE(zdx(kl))
148  ALLOCATE(zdy(kl))
149  zdx(:) = xdx
150  zdy(:) = xdy
151  !
152 ELSE
153  !
154  ALLOCATE(zx0(kdim_full),zy0(kdim_full),zdx0(kdim_full),zdy0(kdim_full))
155  !
156  CALL get_gridtype_cartesian(pgrid_full_par,plat0=xlat0,plon0=xlon0,&
157  kimax=nimax,kjmax=njmax,&
158  px=zx0,py=zy0,pdx=zdx0,pdy=zdy0)
159  !
160  kl = nsize_task(nrank)
161  ALLOCATE(zx(kl),zy(kl),zdx(kl),zdy(kl))
162  !
163  CALL read_and_send_mpi(zx0,zx)
164  CALL read_and_send_mpi(zy0,zy)
165  CALL read_and_send_mpi(zdx0,zdx)
166  CALL read_and_send_mpi(zdy0,zdy)
167  !
168  DEALLOCATE(zx0,zy0,zdx0,zdy0)
169  !
170 ENDIF
171 !---------------------------------------------------------------------------
172 !
173 !* 8. All this information stored into pointer PGRID_PAR
174 ! --------------------------------------------------
175 !
176  CALL put_gridtype_cartesian(zgrid_par,xlat0,xlon0, &
177  nimax,njmax, &
178  zx,zy,zdx,zdy )
179 !
180 !---------------------------------------------------------------------------
181 DEALLOCATE(zx)
182 DEALLOCATE(zy)
183 DEALLOCATE(zdx)
184 DEALLOCATE(zdy)
185 !---------------------------------------------------------------------------
186 !
187 !* 1st call : initializes dimension
188 !
189 IF (kgrid_par==0) THEN
190  kgrid_par = SIZE(zgrid_par)
191 !
192 ELSE
193 !
194 !* 2nd call : initializes grid array
195 !
196  pgrid_par(:) = 0.
197  pgrid_par(:) = zgrid_par
198 END IF
199 !
200 DEALLOCATE(zgrid_par)
201 IF (lhook) CALL dr_hook('READ_NAM_GRID_CARTESIAN',1,zhook_handle)
202 !
203 !---------------------------------------------------------------------------
204 !
205 END SUBROUTINE read_nam_grid_cartesian
subroutine posnam(KULNAM, HDNAML, OFOUND, KLUOUT)
subroutine put_gridtype_cartesian(PGRID_PAR, PLAT0, PLON0, KIMAX, KJMAX, PX, PY, PDX, PDY
subroutine read_nam_grid_cartesian(PGRID_FULL_PAR, KDIM_FULL, HPROGR
integer, parameter jprb
Definition: parkind1.F90:32
subroutine close_namelist(HPROGRAM, KLUNAM)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
integer, dimension(:), allocatable nsize_task
logical lhook
Definition: yomhook.F90:15
subroutine get_gridtype_cartesian(PGRID_PAR, PLAT0, PLON0,
subroutine open_namelist(HPROGRAM, KLUNAM, HFILE)