SURFEX v8.1
General documentation of Surfex
read_nam_trip_grid.F90
Go to the documentation of this file.
1 ! #########
2 SUBROUTINE read_nam_trip_grid (TPG, &
3  KLISTING)
4 !############################
5 !
6 !!**** *READ_NAM_TRIP_GRID* - routine to read in namelist the TRIP horizontal grid
7 !!
8 !! PURPOSE
9 !! -------
10 !!
11 !!** METHOD
12 !! ------
13 !!
14 !! EXTERNAL
15 !! --------
16 !!
17 !!
18 !! IMPLICIT ARGUMENTS
19 !! ------------------
20 !!
21 !! REFERENCE
22 !! ---------
23 !!
24 !!
25 !! AUTHOR
26 !! ------
27 !! B. Decharme *Meteo France*
28 !!
29 !! MODIFICATIONS
30 !! -------------
31 !! Original 05/2008
32 !-------------------------------------------------------------------------------
33 !
34 !* 0. DECLARATIONS
35 ! ------------
36 !
37 !
38 !
39 USE modd_trip_grid, ONLY : trip_grid_t
40 !
41 USE modi_trip_posnam
42 USE modi_abort_trip
43 USE modi_open_trip_namelist
44 USE modi_close_trip_namelist
45 !
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 !
57 TYPE(trip_grid_t), INTENT(INOUT) :: TPG
58 !
59 INTEGER, INTENT(IN) :: KLISTING
60 !
61 !* 0.2 Declarations of local variables
62 ! -------------------------------
63 !
64 INTEGER :: ILUNAM ! namelist file logical unit
65 INTEGER :: I
66 LOGICAL :: GFOUND
67 REAL :: ZWORK
68 !
69 !
70 !* 0.3 Declarations of namelist
71 ! ------------------------
72 !
73 REAL :: TLONMIN = 0. ! minimum longitude (degrees)
74 REAL :: TLONMAX = 0. ! maximum longitude (degrees)
75 REAL :: TLATMIN = 0. ! minimum latitude (degrees)
76 REAL :: TLATMAX = 0. ! maximum latitude (degrees)
77 REAL :: TRES = 0. ! 1deg or 0.5deg resolution
78 !
79 REAL, DIMENSION(:), ALLOCATABLE :: ZLON
80 REAL, DIMENSION(:), ALLOCATABLE :: ZLAT
81 !
82 INTEGER :: ILON,ILAT
83 REAL(KIND=JPRB) :: ZHOOK_HANDLE
84 !
85 NAMELIST/nam_trip_grid/tlonmin, tlonmax, tlatmin, tlatmax, tres
86 !
87 !------------------------------------------------------------------------------
88 !
89 !* 1. opening of namelist
90 !
91 IF (lhook) CALL dr_hook('READ_NAM_TRIP_GRID',0,zhook_handle)
92 !
93  CALL open_trip_namelist(ilunam)
94 !
95 !---------------------------------------------------------------------------
96 !
97 !* 2. Reading of projection parameters
98 ! --------------------------------
99 !
100  CALL trip_posnam(ilunam,'NAM_TRIP_GRID',gfound,klisting)
101 IF (gfound) THEN
102  READ(unit=ilunam,nml=nam_trip_grid)
103 ELSE
104  WRITE(klisting,*)'READ_NAM_TRIP_GRID: NAM_TRIP_GRID not found in namelist'
105  CALL abort_trip('READ_NAM_TRIP_GRID: NAM_TRIP_GRID not found in namelist')
106 ENDIF
107 !
108  CALL close_trip_namelist(ilunam)
109 !
110 IF(tres/=0.5.AND.tres/=1.0)THEN
111  IF(tres<0.08.OR.tres>0.09)THEN
112  WRITE(klisting,*)'Error : The resolution of the TRIP grid must be 1deg or 0.5deg '
113  WRITE(klisting,*)' or 0.083333deg over France '
114  WRITE(klisting,*)' In NAM_TRIP_GRID, TRES should be 0.083333 or 0.5 or 1. '
115  CALL abort_trip('READ_NAM_TRIP_GRID: The resolution of the TRIP grid must be 1deg or 0.5deg or 0.083333deg')
116  ELSE
117  tres=REAL(nint(tres*12.))/12.
118  ENDIF
119 ENDIF
120 !
121 !---------------------------------------------------------------------------
122 !
123 !* 3. Number of lattitude and longitude
124 !
125 ilon = int((tlonmax-tlonmin)/tres)
126 ilat = int((tlatmax-tlatmin)/tres)
127 !
128 !---------------------------------------------------------------------------
129 !
130 !* 4. lattitude and longitude values
131 !
132 ALLOCATE(zlon(ilon))
133 ALLOCATE(zlat(ilat))
134 !
135 zwork = tlonmin-(tres/2.)
136 DO i=1,ilon
137  zwork = zwork + tres
138  zlon(i) = zwork
139 ENDDO
140 !
141 zwork =tlatmin-(tres/2.)
142 DO i=1,ilat
143  zwork = zwork + tres
144  zlat(i) = zwork
145 ENDDO
146 !
147 !---------------------------------------------------------------------------
148 !
149 !* 5. All this information stored into PTRIP_GRID
150 ! -------------------------------------------
151 !
152 ALLOCATE(tpg%XTRIP_GRID(7+ilon+ilat))
153 tpg%XTRIP_GRID(:) = 0.0
154 !
155  CALL put_trip_grid(tpg%XTRIP_GRID,tlonmin,tlonmax,tlatmin,tlatmax,tres,ilon,ilat,zlon,zlat)
156 !
157 DEALLOCATE(zlon)
158 DEALLOCATE(zlat)
159 !
160 IF (lhook) CALL dr_hook('READ_NAM_TRIP_GRID',1,zhook_handle)
161 !
162 !---------------------------------------------------------------------------
163 !
164 END SUBROUTINE read_nam_trip_grid
subroutine read_nam_trip_grid(TPG, KLISTING)
integer, parameter jprb
Definition: parkind1.F90:32
subroutine put_trip_grid(PTRIP_GRID, PLONMIN, PLONMAX, PLATMIN, PLATMAX, PRES, KLON, KLAT, PLON, PLAT)
logical lhook
Definition: yomhook.F90:15
subroutine close_trip_namelist(KLUNAM)
subroutine open_trip_namelist(KLUNAM)
subroutine abort_trip(YTEXT)
Definition: abort_trip.F90:3
subroutine trip_posnam(KULNAM, HDNAML, OFOUND, KLISTING)
Definition: trip_posnam.F90:3