SURFEX v8.1
General documentation of Surfex
read_nam_grid_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 read_nam_grid_lonlat_rot(PGRID_FULL_PAR,KDIM_FULL,HPROGRAM,KGRID_PAR,KL,PGRID_PAR,HDIR)
7 ! ################################################################
8 !
9 !!**** *READ_NAM_GRID_LONLAT_ROT* - 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 !! P. Samuelsson SMHI
31 !!
32 !! MODIFICATIONS
33 !! -------------
34 !! Original 12/2012
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 !
49 !
51 !
52 USE yomhook ,ONLY : lhook, dr_hook
53 USE parkind1 ,ONLY : jprb
54 !
55 IMPLICIT NONE
56 !
57 !* 0.1 Declarations of arguments
58 ! -------------------------
59 !
60 REAL, DIMENSION(:), POINTER :: PGRID_FULL_PAR
61 INTEGER, INTENT(IN) :: KDIM_FULL
62 !
63  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! calling program
64 INTEGER, INTENT(INOUT) :: KGRID_PAR ! size of PGRID_PAR
65 INTEGER, INTENT(OUT) :: KL ! number of points
66 REAL, DIMENSION(KGRID_PAR), INTENT(OUT) :: PGRID_PAR ! parameters defining this grid
67  CHARACTER(LEN=1), INTENT(IN) :: HDIR
68 !
69 !* 0.2 Declarations of local variables
70 ! -------------------------------
71 !
72 INTEGER :: ILUOUT ! output listing logical unit
73 INTEGER :: ILUNAM ! namelist file logical unit
74 !
75 REAL, DIMENSION(:), ALLOCATABLE :: ZLAT, ZLAT0 ! latitude of all points
76 REAL, DIMENSION(:), ALLOCATABLE :: ZLON, ZLON0 ! longitude of all points
77 !
78 REAL, DIMENSION(:), POINTER :: ZGRID_PAR
79 !
80 LOGICAL :: GFOUND
81 !
82 !
83 !* 0.3 Declarations of namelist
84 ! ------------------------
85 !
86 REAL :: XWEST ! West longitude in rotated grid (degrees)
87 REAL :: XSOUTH ! South latitude in rotated grid (degrees)
88 REAL :: XDLON ! Longitudal grid spacing (degrees)
89 REAL :: XDLAT ! Latitudal grid spacing (degrees)
90 REAL :: XPOLON ! Longitude of rotated pole (degrees)
91 REAL :: XPOLAT ! Latitude of rotated pole (degrees)
92 INTEGER :: NLON ! number of points in longitude
93 INTEGER :: NLAT ! number of points in latitude
94 REAL(KIND=JPRB) :: ZHOOK_HANDLE
95 NAMELIST/nam_lonlat_rot/xwest,xsouth,xdlon,xdlat,xpolon,xpolat,nlon,nlat
96 !
97 !------------------------------------------------------------------------------
98 !
99 !* 1. opening of namelist
100 !
101 IF (lhook) CALL dr_hook('READ_NAM_GRID_LONLAT_ROT',0,zhook_handle)
102  CALL get_luout(hprogram,iluout)
103 !
104 IF (hdir/='H') THEN
105  !
106  CALL open_namelist(hprogram,ilunam)
107  !
108  !---------------------------------------------------------------------------
109  !
110  !* 2. Reading of projection parameters
111  ! --------------------------------
112  !
113  CALL posnam(ilunam,'NAM_LONLAT_ROT',gfound,iluout)
114  IF (gfound) READ(unit=ilunam,nml=nam_lonlat_rot)
115  !
116  !---------------------------------------------------------------------------
117  !
118  !* 3. Number of points
119  ! ----------------
120  !
121  kl = nlon * nlat
122  !
123  !---------------------------------------------------------------------------
124  CALL close_namelist(hprogram,ilunam)
125  !---------------------------------------------------------------------------
126  !
127  !* 4. All this information stored into pointer PGRID_PAR
128  ! --------------------------------------------------
129  !
130  ALLOCATE(zlat(kl))
131  ALLOCATE(zlon(kl))
132  !
133  CALL latlon_lonlat_rot(xwest,xsouth,xdlon,xdlat,xpolon,xpolat, &
134  nlon,nlat,zlon,zlat )
135  !
136 ELSE
137  !
138  ALLOCATE(zlon0(kdim_full),zlat0(kdim_full))
139  !
140  CALL get_gridtype_lonlat_rot(pgrid_full_par,pwest=xwest,psouth=xsouth,&
141  pdlon=xdlon,pdlat=xdlat,ppolon=xpolon,ppolat=xpolat,&
142  klon=nlon,klat=nlat,kl=kl,plon=zlon0,plat=zlat0)
143  !
144  ALLOCATE(zlon(kl),zlat(kl))
145  !
146  CALL read_and_send_mpi(zlon0,zlon)
147  CALL read_and_send_mpi(zlat0,zlat)
148  !
149  DEALLOCATE(zlon0,zlat0)
150  !
151 ENDIF
152 !
153  CALL put_gridtype_lonlat_rot(zgrid_par, &
154  xwest,xsouth,xdlon,xdlat,xpolon,xpolat, &
155  nlon,nlat,kl,zlon,zlat )
156 !
157 DEALLOCATE(zlat)
158 DEALLOCATE(zlon)
159 !
160 !---------------------------------------------------------------------------
161 !
162 !* 1st call : initializes dimension
163 !
164 IF (kgrid_par==0) THEN
165  kgrid_par = SIZE(zgrid_par)
166 !
167 ELSE
168 !
169 !* 2nd call : initializes grid array
170 !
171  pgrid_par(:) = 0.
172  pgrid_par(:) = zgrid_par
173 END IF
174 !
175 DEALLOCATE(zgrid_par)
176 IF (lhook) CALL dr_hook('READ_NAM_GRID_LONLAT_ROT',1,zhook_handle)
177 !
178 !---------------------------------------------------------------------------
179 !
180 END SUBROUTINE read_nam_grid_lonlat_rot
subroutine posnam(KULNAM, HDNAML, OFOUND, KLUOUT)
subroutine read_nam_grid_lonlat_rot(PGRID_FULL_PAR, KDIM_FULL, HPROG
integer, parameter jprb
Definition: parkind1.F90:32
subroutine get_gridtype_lonlat_rot(PGRID_PAR,
subroutine close_namelist(HPROGRAM, KLUNAM)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
subroutine latlon_lonlat_rot(PWEST, PSOUTH, PDLON, PDLAT, PPOLON, PPOL
integer, dimension(:), allocatable nsize_task
logical lhook
Definition: yomhook.F90:15
subroutine put_gridtype_lonlat_rot(PGRID_PAR,
subroutine open_namelist(HPROGRAM, KLUNAM, HFILE)