SURFEX v8.1
General documentation of Surfex
init_restart_trip.F90
Go to the documentation of this file.
1 ! #########
2  SUBROUTINE init_restart_trip (TPG, &
3  KLISTING,HFILE,KLON,KLAT,HTITLE,HTIMEUNIT,OTIME)
4 ! #######################################################################
5 !
6 !!**** *INIT_RESTART_TRIP*
7 !!
8 !! PURPOSE
9 !! -------
10 !
11 ! Define the name and unit of each trip restart variables.
12 !
13 !! REFERENCE
14 !! ---------
15 !!
16 !! AUTHOR
17 !! ------
18 !! B. Decharme
19 !!
20 !! MODIFICATIONS
21 !! -------------
22 !! Original 27/05/08
23 !-------------------------------------------------------------------------------
24 !
25 !* 0. DECLARATIONS
26 ! ------------
27 !
28 !
29 !
30 USE modd_trip_grid, ONLY : trip_grid_t
31 !
33 !
34 USE modn_trip, ONLY : cgroundw, lflood
35 USE modd_trip_par, ONLY : xundef, lncprint
36 !
37 USE yomhook ,ONLY : lhook, dr_hook
38 USE parkind1 ,ONLY : jprb
39 !
40 USE netcdf
41 !
42 USE modi_get_lonlat_trip
43 !
44 IMPLICIT NONE
45 !
46 !
47 !* 0.1 declarations of arguments
48 !
49 !
50 !
51 TYPE(trip_grid_t), INTENT(INOUT) :: TPG
52 !
53  CHARACTER(LEN=*), INTENT(IN) :: HFILE, HTITLE, HTIMEUNIT
54 !
55 INTEGER, INTENT(IN) :: KLISTING, KLON, KLAT
56 !
57 LOGICAL, INTENT(IN) :: OTIME
58 !
59 !* 0.2 declarations of restart variables
60 !
61  CHARACTER(LEN=NF90_MAX_NAME), DIMENSION(:), ALLOCATABLE :: YVNAME !Name of each restart variable
62  CHARACTER(LEN=NF90_MAX_NAME), DIMENSION(:), ALLOCATABLE :: YVLNAME !Long name of each restart variables
63  CHARACTER(LEN=NF90_MAX_NAME), DIMENSION(:), ALLOCATABLE :: YUNIT !Unit of each restart variable
64 !
65  CHARACTER(LEN=NF90_MAX_NAME) :: YFILE,YTITLE,YTIMEUNIT
66 !
67 REAL, DIMENSION(:), ALLOCATABLE :: ZLON
68 REAL, DIMENSION(:), ALLOCATABLE :: ZLAT
69 LOGICAL, DIMENSION(:), ALLOCATABLE :: LDOUBLE
70 !
71 INTEGER :: IND, INCID, INUM
72 REAL(KIND=JPRB) :: ZHOOK_HANDLE
73 !
74 !-------------------------------------------------------------------------------
75 !-------------------------------------------------------------------------------
76 !
77 ! * Number of restart variable
78 !
79 IF (lhook) CALL dr_hook('INIT_RESTART_TRIP',0,zhook_handle)
80 ind = 1
81 IF(cgroundw=='CST'.OR.cgroundw=='DIF') ind = ind + 1
82 IF(lflood)ind = ind + 3
83 !
84 ! * Allocate netcdf file attributs
85 !
86 ALLOCATE(yvname(ind))
87 ALLOCATE(yvlname(ind))
88 ALLOCATE(yunit(ind))
89 ALLOCATE(ldouble(ind))
90 ldouble(:)=.true.
91 !
92 ALLOCATE(zlon(klon))
93 ALLOCATE(zlat(klat))
94 !
95 ! * Initialyse netcdf file attributs
96 !
97 yvname(1) = 'SURF_STO '
98 yvlname(1) = 'River storage '
99 yunit(1) = 'kg '
100 !
101 inum = 1
102 !
103 IF(cgroundw=='CST')THEN
104 !
105 inum = inum + 1
106 yvname(inum) = 'GROUND_STO '
107 yvlname(inum) = 'Groundwater storage '
108 yunit(inum) = 'kg '
109 !
110 ELSEIF(cgroundw=='DIF')THEN
111 !
112 inum = inum + 1
113 yvname(inum) = 'HGROUND '
114 yvlname(inum) = 'Groundwater height '
115 yunit(inum) = 'm '
116 !
117 ENDIF
118 !
119 IF(lflood)THEN
120 !
121 inum = inum + 1
122 yvname(inum) = 'FLOOD_STO '
123 yvlname(inum) = 'Floodplain storage '
124 yunit(inum) = 'kg '
125 
126 inum = inum + 1
127 yvname(inum) = 'FFLOOD '
128 yvlname(inum) = 'TRIP flooded fraction '
129 yunit(inum) = '- '
130 !
131 inum = inum + 1
132 yvname(inum) = 'HFLOOD '
133 yvlname(inum) = 'Flood depth '
134 yunit(inum) = 'm '
135 !
136 ENDIF
137 !
138 ! * Create netcdf file
139 !
140 yfile = hfile(1:len_trim(hfile))
141 ytitle = htitle(1:len_trim(htitle))
142 ytimeunit = htimeunit(1:len_trim(htimeunit))
143 !
144  CALL get_lonlat_trip(tpg, &
145  klon,klat,zlon,zlat)
146 !
147  CALL nccreate(klisting,yfile,ytitle,ytimeunit,yvname,yvlname,yunit,zlon,zlat, &
148  xundef,lncprint,incid,otime,odouble=ldouble)
149 !
150  CALL ncclose(klisting,lncprint,yfile,incid)
151 !
152 ! * Deallocate netcdf file attributs
153 !
154 DEALLOCATE(yvname )
155 DEALLOCATE(yvlname )
156 DEALLOCATE(yunit )
157 DEALLOCATE(zlon )
158 DEALLOCATE(zlat )
159 IF (lhook) CALL dr_hook('INIT_RESTART_TRIP',1,zhook_handle)
160 !
161 !-------------------------------------------------------------------------------
162 !-------------------------------------------------------------------------------
163 END SUBROUTINE init_restart_trip
logical lflood
Definition: modn_trip.F90:62
subroutine init_restart_trip(TPG, KLISTING, HFILE, KLON, KLAT, HTITLE, HTI
integer, parameter jprb
Definition: parkind1.F90:32
logical, save lncprint
subroutine ncclose(KLISTING, OVERBOSE, HFILENAME, KNCID)
character(len=3) cgroundw
Definition: modn_trip.F90:49
logical lhook
Definition: yomhook.F90:15
subroutine nccreate(KLISTING, HFILENAME, HTITLE, HTIMEUNIT, HVNAME, HVLNAME, HUNIT, PLON, PLAT, PMISSVAL, OVERBOSE, KNCID, OTIME, KZLEN, OVARZDIM, ODOUBLE)
subroutine get_lonlat_trip(TPG, KLON, KLAT, PLON, PLAT)
real, save xundef