source: tags/ORCHIDEE_1_9_5_1/ORCHIDEE/src_sechiba/watchout.f90 @ 55

Last change on this file since 55 was 42, checked in by mmaipsl, 14 years ago

MM: Replace all 0.0 by 'zero' and 1.0 by 'un',

and all 86400. by 'one_day' in the code to reduce explicit constants.

File size: 92.4 KB
Line 
1MODULE watchout
2
3  USE defprec
4  USE parallel
5  USE constantes
6  USE netcdf
7
8  PRIVATE
9  PUBLIC :: watchout_init, watchout_write_p, watchout_close
10!watchout_write ??
11
12  LOGICAL,SAVE,PUBLIC             :: ok_watchout = .FALSE.
13  REAL, SAVE,PUBLIC               :: dt_watch = zero
14  INTEGER, SAVE,PUBLIC            :: last_action_watch = 0, &
15       & last_check_watch = 0
16  CHARACTER(LEN=80),SAVE, PUBLIC   :: watchout_file
17
18  ! At module level we need the ids of the variables for the ORCHIDEE_WATCH. They will be
19  ! shared by the watchout_init and watchout_write routines.
20  ! The flag which will control all this is watchout
21  !
22  INTEGER(i_std),SAVE      :: time_id, timestp_id
23  INTEGER(i_std),SAVE      :: watchfid, zlevid, soldownid, rainfid, snowfid, lwradid, &
24       & psolid, tairid, eairid, qairid, uid, vid, &
25       & solnetid, petAcoefid, peqAcoefid, petBcoefid, peqBcoefid, cdragid, ccanopyid
26  INTEGER(i_std),SAVE      :: watchoffset
27  REAL(r_std), ALLOCATABLE, DIMENSION(:), SAVE, PUBLIC  :: sum_zlev
28  REAL(r_std), ALLOCATABLE, DIMENSION(:), SAVE, PUBLIC  :: sum_u, sum_v
29  REAL(r_std), ALLOCATABLE, DIMENSION(:), SAVE, PUBLIC  :: sum_qair
30  REAL(r_std), ALLOCATABLE, DIMENSION(:), SAVE, PUBLIC  :: sum_temp_air
31  REAL(r_std), ALLOCATABLE, DIMENSION(:), SAVE, PUBLIC  :: sum_epot_air
32  REAL(r_std), ALLOCATABLE, DIMENSION(:), SAVE, PUBLIC  :: sum_ccanopy
33  REAL(r_std), ALLOCATABLE, DIMENSION(:), SAVE, PUBLIC  :: sum_cdrag
34  REAL(r_std), ALLOCATABLE, DIMENSION(:), SAVE, PUBLIC  :: sum_petAcoef, sum_peqAcoef, sum_petBcoef, sum_peqBcoef
35  REAL(r_std), ALLOCATABLE, DIMENSION(:), SAVE, PUBLIC  :: sum_rain, sum_snow
36  REAL(r_std), ALLOCATABLE, DIMENSION(:), SAVE, PUBLIC  :: sum_lwdown
37  REAL(r_std), ALLOCATABLE, DIMENSION(:), SAVE, PUBLIC  :: sum_swnet
38  REAL(r_std), ALLOCATABLE, DIMENSION(:), SAVE, PUBLIC  :: sum_swdown
39  REAL(r_std), ALLOCATABLE, DIMENSION(:), SAVE, PUBLIC  :: sum_pb
40  !! Short wave mean : compute with solar angle, as in readdim2
41!!$  REAL(r_std), ALLOCATABLE, DIMENSION(:,:), SAVE, PUBLIC  :: sinang, mean_sinang
42!!$  INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:), SAVE, PUBLIC :: isinang
43
44  REAL(r_std), PUBLIC :: dt_split_watch
45  !! mean julian time for each time step
46  REAL(r_std), PUBLIC :: julian_watch
47
48CONTAINS
49SUBROUTINE watchout_init(iim, jjm, kjpindex, igmax, date0, itau, dt, kindex, lon, lat, lev0)
50  !
51  IMPLICIT NONE
52  !
53  ! This routine will allow to set up forcing files for ORCHIDEE. The idea is that
54  ! during a coupled simulation one write's out all the forcing so that ORCHIDEE can
55  ! can be re-run (to equilibrium or for sensitivity) afterwards.
56  !
57  ! INPUT
58  INTEGER(i_std), INTENT(in)   :: iim, jjm, igmax, kjpindex
59  REAL(r_std), INTENT(in)      :: date0, dt
60  INTEGER(i_std), INTENT(in)   :: itau, kindex(igmax)
61  REAL(r_std), INTENT(in)      :: lon(iim,jjm), lat(iim,jjm), lev0
62  !
63  ! OUTPUT
64  !
65  !
66  ! LOCAL
67  !
68  INTEGER(i_std)   :: iret, nlonid1, nlatid1, nlevid1, fid, nlandid1, tdimid1
69  INTEGER(i_std)   :: dims(3)
70  INTEGER(i_std)   :: nlonid, nlatid, nlevid, nlandid, varid, contid, resolxid, resolyid
71  INTEGER(i_std), DIMENSION(8)  ::  neighid
72  REAL(r_std)      :: lon_min, lon_max, lat_min, lat_max, lev_min, lev_max
73  INTEGER(i_std)   :: yy, mm, dd, hh, mn, i, j, ig, direction
74  REAL(r_std)      :: ss
75  REAL(r_std),ALLOCATABLE :: tmpdata(:,:)
76  CHARACTER(LEN=3)  :: cal(12)
77  CHARACTER(LEN=10) :: today, att, axx
78  CHARACTER(LEN=30) :: str30
79  CHARACTER(LEN=70) :: str70, var, unit, titre, assoc
80  CHARACTER(LEN=80) :: stamp, lon_name, lat_name, land_name,time_name
81  !   
82  INTEGER,PARAMETER :: kind_r_watch=nf90_real8
83  !
84  ! Only root proc write watchout file
85  IF (is_root_prc) THEN
86
87     cal(1) = 'JAN'
88     cal(2) = 'FEB'
89     cal(3) = 'MAR'
90     cal(4) = 'APR'
91     cal(5) = 'MAY'
92     cal(6) = 'JUN'
93     cal(7) = 'JUL'
94     cal(8) = 'AUG'
95     cal(9) = 'SEP'
96     cal(10) = 'OCT'
97     cal(11) = 'NOV'
98     cal(12) = 'DEC'
99     !
100     iret = NF90_CREATE (TRIM(watchout_file), NF90_CLOBBER, fid)
101     IF (iret /= NF90_NOERR) THEN
102        CALL ipslerr (3,'watchout_init', &
103             &          'Could not create file :',TRIM(watchout_file), &
104             &          '(Problem with disk place or filename ?)')
105     ENDIF
106     !
107     !   Dimensions
108     !
109     iret = NF90_DEF_DIM(fid, 'x', iim, nlonid1)
110     IF (iret /= NF90_NOERR) THEN
111        CALL ipslerr (3,'watchout_init', &
112             &         'Dimension "x" can not be defined for the file : ', &
113             &         TRIM(watchout_file),'(Solution ?)')
114     ENDIF
115     iret = NF90_DEF_DIM(fid, 'y', jjm, nlatid1)
116     IF (iret /= NF90_NOERR) THEN
117        CALL ipslerr (3,'watchout_init', &
118             &         'Dimension "y" can not be defined for the file : ', &
119             &         TRIM(watchout_file),'(Solution ?)')
120     ENDIF
121     iret = NF90_DEF_DIM(fid, 'z', 1, nlevid1)
122     IF (iret /= NF90_NOERR) THEN
123        CALL ipslerr (3,'watchout_init', &
124             &         'Dimension "z" can not be defined for the file : ', &
125             &         TRIM(watchout_file),'(Solution ?)')
126     ENDIF
127     !
128     iret = NF90_DEF_DIM(fid, 'land', igmax, nlandid1)
129     IF (iret /= NF90_NOERR) THEN
130        CALL ipslerr (3,'watchout_init', &
131             &         'Dimension "land" can not be defined for the file : ', &
132             &         TRIM(watchout_file),'(Solution ?)')
133     ENDIF
134     iret = NF90_DEF_DIM(fid, 'tstep', NF90_UNLIMITED, tdimid1)
135     IF (iret /= NF90_NOERR) THEN
136        CALL ipslerr (3,'watchout_init', &
137             &         'Dimension "tstep" can not be defined for the file : ', &
138             &         TRIM(watchout_file),'(Solution ?)')
139     ENDIF
140     !
141     !   Coordinate  VARIABLES
142     !
143     dims(1) = nlonid1
144     dims(2) = nlatid1
145     !
146     lon_name = 'nav_lon'
147     iret = NF90_DEF_VAR(fid, lon_name, kind_r_watch, dims(1:2), nlonid)
148     IF (iret /= NF90_NOERR) THEN
149        CALL ipslerr (3,'watchout_init', &
150             &         'Variable '//lon_name//' can not be defined for the file : ', &
151             &         TRIM(watchout_file),'(Solution ?)')
152     ENDIF
153     iret = NF90_PUT_ATT(fid, nlonid, 'units', "degrees_east") 
154     IF (iret /= NF90_NOERR) THEN
155        CALL ipslerr (3,'watchout_init', &
156             &          'Could not add attribut to variable '//lon_name//' for the file :', &
157             &          TRIM(watchout_file),'(Solution ?)')
158     ENDIF
159     !
160     lon_min = -180.
161     lon_max = 180.
162     !
163     iret = NF90_PUT_ATT(fid, nlonid, 'valid_min', lon_min)
164     IF (iret /= NF90_NOERR) THEN
165        CALL ipslerr (3,'watchout_init', &
166             &          'Could not add attribut to variable '//lon_name//' for the file :', &
167             &          TRIM(watchout_file),'(Solution ?)')
168     ENDIF
169     iret = NF90_PUT_ATT(fid, nlonid, 'valid_max', lon_max)
170     IF (iret /= NF90_NOERR) THEN
171        CALL ipslerr (3,'watchout_init', &
172             &          'Could not add attribut to variable '//lon_name//' for the file :', &
173             &          TRIM(watchout_file),'(Solution ?)')
174     ENDIF
175     !
176     iret = NF90_PUT_ATT(fid, nlonid, 'long_name', "Longitude")
177     IF (iret /= NF90_NOERR) THEN
178        CALL ipslerr (3,'watchout_init', &
179             &          'Could not add attribut to variable '//lon_name//' for the file :', &
180             &          TRIM(watchout_file),'(Solution ?)')
181     ENDIF
182     !
183     lat_name = 'nav_lat'
184     iret = NF90_DEF_VAR(fid, lat_name, kind_r_watch, dims(1:2), nlatid)
185     IF (iret /= NF90_NOERR) THEN
186        CALL ipslerr (3,'watchout_init', &
187             &         'Variable '//lat_name//' can not be defined for the file : ', &
188             &         TRIM(watchout_file),'(Solution ?)')
189     ENDIF
190     iret = NF90_PUT_ATT(fid, nlatid, 'units', "degrees_north")
191     IF (iret /= NF90_NOERR) THEN
192        CALL ipslerr (3,'watchout_init', &
193             &          'Could not add attribut to variable '//lat_name//' for the file :', &
194             &          TRIM(watchout_file),'(Solution ?)')
195     ENDIF
196     !
197     lat_max = 90.
198     lat_min = -90.
199     !
200     iret = NF90_PUT_ATT(fid, nlatid, 'valid_min', lat_min)
201     IF (iret /= NF90_NOERR) THEN
202        CALL ipslerr (3,'watchout_init', &
203             &          'Could not add attribut to variable '//lat_name//' for the file :', &
204             &          TRIM(watchout_file),'(Solution ?)')
205     ENDIF
206     iret = NF90_PUT_ATT(fid, nlatid, 'valid_max', lat_max)
207     IF (iret /= NF90_NOERR) THEN
208        CALL ipslerr (3,'watchout_init', &
209             &          'Could not add attribut to variable '//lat_name//' for the file :', &
210             &          TRIM(watchout_file),'(Solution ?)')
211     ENDIF
212     iret = NF90_PUT_ATT(fid, nlatid, 'long_name', "Latitude")
213     IF (iret /= NF90_NOERR) THEN
214        CALL ipslerr (3,'watchout_init', &
215             &          'Could not add attribut to variable '//lat_name//' for the file :', &
216             &          TRIM(watchout_file),'(Solution ?)')
217     ENDIF
218     !
219     lat_name = 'level'
220     iret = NF90_DEF_VAR(fid, lat_name, kind_r_watch,(/ nlevid1 /), nlevid)
221     IF (iret /= NF90_NOERR) THEN
222        CALL ipslerr (3,'watchout_init', &
223             &         'Variable '//lat_name//' can not be defined for the file : ', &
224             &         TRIM(watchout_file),'(Solution ?)')
225     ENDIF
226     iret = NF90_PUT_ATT(fid, nlevid, 'units', "m")
227     IF (iret /= NF90_NOERR) THEN
228        CALL ipslerr (3,'watchout_init', &
229             &          'Could not add attribut to variable '//lat_name//' for the file :', &
230             &          TRIM(watchout_file),'(Solution ?)')
231     ENDIF
232     !
233     lev_max = lev0
234     lev_min = lev0
235     !
236     iret = NF90_PUT_ATT(fid, nlevid, 'valid_min', lev_min)
237     IF (iret /= NF90_NOERR) THEN
238        CALL ipslerr (3,'watchout_init', &
239             &          'Could not add attribut to variable '//lat_name//' for the file :', &
240             &          TRIM(watchout_file),'(Solution ?)')
241     ENDIF
242     iret = NF90_PUT_ATT(fid, nlevid, 'valid_max', lev_max)
243     IF (iret /= NF90_NOERR) THEN
244        CALL ipslerr (3,'watchout_init', &
245             &          'Could not add attribut to variable '//lat_name//' for the file :', &
246             &          TRIM(watchout_file),'(Solution ?)')
247     ENDIF
248     iret = NF90_PUT_ATT(fid, nlevid, 'long_name', "Vertical levels")
249     IF (iret /= NF90_NOERR) THEN
250        CALL ipslerr (3,'watchout_init', &
251             &          'Could not add attribut to variable '//lat_name//' for the file :', &
252             &          TRIM(watchout_file),'(Solution ?)')
253     ENDIF
254     !
255     !
256     land_name = 'land'
257     iret = NF90_DEF_VAR(fid, land_name, NF90_INT, (/ nlandid1 /), nlandid)
258     IF (iret /= NF90_NOERR) THEN
259        CALL ipslerr (3,'watchout_init', &
260             &         'Variable '//land_name//' can not be defined for the file : ', &
261             &         TRIM(watchout_file),'(Solution ?)')
262     ENDIF
263     iret = NF90_PUT_ATT(fid, nlandid, 'compress', "y x") 
264     IF (iret /= NF90_NOERR) THEN
265        CALL ipslerr (3,'watchout_init', &
266             &          'Could not add attribut to variable '//land_name//' for the file :', &
267             &          TRIM(watchout_file),'(Solution ?)')
268     ENDIF
269     !
270     !   Time in real days !
271     !
272     time_name = 'time'
273     iret = NF90_DEF_VAR(fid, time_name, kind_r_watch, (/ tdimid1 /), time_id)
274     IF (iret /= NF90_NOERR) THEN
275        CALL ipslerr (3,'watchout_init', &
276             &         'Variable '//time_name//' can not be defined for the file : ', &
277             &         TRIM(watchout_file),'(Solution ?)')
278     ENDIF
279     !
280     ! Compute an itau offset so that we can relate the itau of the model
281     ! to the position in the file
282     !
283     watchoffset = itau
284     !
285    CALL ju2ymds(date0, yy, mm, dd, ss)
286    hh = INT(ss/3600.)
287    ss = ss - hh*3600.
288     mn = INT(ss/60.) 
289     ss = ss - mn*60.
290    WRITE(str70,7000) yy, mm, dd, hh, mn, INT(ss)
291!!MM : Time axis by month :
292!$     hh = INT(sec/3600.)
293!$     ss = sec - hh*3600.
294!$     mn = INT(ss/60.)
295!$     ss = ss - mn*60.
296!$     WRITE(str70,7000) year, month, day, hh, mn, INT(ss)
297     !
298     iret = NF90_PUT_ATT(fid, time_id, 'units', TRIM(str70))
299     IF (iret /= NF90_NOERR) THEN
300        CALL ipslerr (3,'watchout_init', &
301             &          'Could not add attribut to variable '//time_name//' for the file :', &
302             &          TRIM(watchout_file),'(Solution ?)')
303     ENDIF
304     !
305     CALL ioget_calendar(str30)
306     iret = NF90_PUT_ATT(fid, time_id, 'calendar', TRIM(str30))
307     IF (iret /= NF90_NOERR) THEN
308        CALL ipslerr (3,'watchout_init', &
309             &          'Could not add attribut to variable '//time_name//' for the file :', &
310             &          TRIM(watchout_file),'(Solution ?)')
311     ENDIF
312     !
313     iret = NF90_PUT_ATT(fid, time_id, 'title', 'Time')
314     IF (iret /= NF90_NOERR) THEN
315        CALL ipslerr (3,'watchout_init', &
316             &          'Could not add attribut to variable '//time_name//' for the file :', &
317             &          TRIM(watchout_file),'(Solution ?)')
318     ENDIF
319     !
320     iret = NF90_PUT_ATT(fid, time_id, 'long_name', 'Time axis')
321     IF (iret /= NF90_NOERR) THEN
322        CALL ipslerr (3,'watchout_init', &
323             &          'Could not add attribut to variable '//time_name//' for the file :', &
324             &          TRIM(watchout_file),'(Solution ?)')
325     ENDIF
326     !
327    WRITE(str70,7001) yy, cal(mm), dd, hh, mn, INT(ss)
328!!MM : Time axis by month :
329!$     WRITE(str70,7001) year, CAL(month), day, hh, mn, INT(ss)
330     iret = NF90_PUT_ATT(fid, time_id, 'time_origin', TRIM(str70))
331     IF (iret /= NF90_NOERR) THEN
332        CALL ipslerr (3,'watchout_init', &
333             &          'Could not add attribut to variable '//time_name//' for the file :', &
334             &          TRIM(watchout_file),'(Solution ?)')
335     ENDIF
336     !
337     !   Time steps
338     !
339     time_name = 'timestp'
340     iret = NF90_DEF_VAR(fid, time_name, NF90_INT, (/ tdimid1 /), timestp_id)
341     IF (iret /= NF90_NOERR) THEN
342        CALL ipslerr (3,'watchout_init', &
343             &         'Variable '//time_name//' can not be defined for the file : ', &
344             &         TRIM(watchout_file),'(Solution ?)')
345     ENDIF
346     !
347    WRITE(str70,7002) yy, mm, dd, hh, mn, INT(ss)
348!!MM : Time axis by month :
349!$     WRITE(str70,7002) year, month, day, hh, mn, INT(ss)
350     iret = NF90_PUT_ATT(fid, timestp_id, 'units', TRIM(str70))
351     IF (iret /= NF90_NOERR) THEN
352        CALL ipslerr (3,'watchout_init', &
353             &          'Could not add attribut to variable '//time_name//' for the file :', &
354             &          TRIM(watchout_file),'(Solution ?)')
355     ENDIF
356     !
357     iret = NF90_PUT_ATT(fid, timestp_id, 'title', 'Time steps')
358     IF (iret /= NF90_NOERR) THEN
359        CALL ipslerr (3,'watchout_init', &
360             &          'Could not add attribut to variable '//time_name//' for the file :', &
361             &          TRIM(watchout_file),'(Solution ?)')
362     ENDIF
363     !
364     iret = NF90_PUT_ATT(fid, timestp_id, 'tstep_sec', dt)
365     IF (iret /= NF90_NOERR) THEN
366        CALL ipslerr (3,'watchout_init', &
367             &          'Could not add attribut to variable '//time_name//' for the file :', &
368             &          TRIM(watchout_file),'(Solution ?)')
369     ENDIF
370     !
371     iret = NF90_PUT_ATT(fid, timestp_id, 'long_name', 'Time step axis')
372     IF (iret /= NF90_NOERR) THEN
373        CALL ipslerr (3,'watchout_init', &
374             &          'Could not add attribut to variable '//time_name//' for the file :', &
375             &          TRIM(watchout_file),'(Solution ?)')
376     ENDIF
377     !
378    WRITE(str70,7001) yy, cal(mm), dd, hh, mn, INT(ss)
379!!MM : Time axis by month :
380!$     WRITE(str70,7001) year, CAL(month), day, hh, mn, INT(ss)
381     iret = NF90_PUT_ATT(fid, timestp_id, 'time_origin', TRIM(str70))
382     IF (iret /= NF90_NOERR) THEN
383        CALL ipslerr (3,'watchout_init', &
384             &          'Could not add attribut to variable '//time_name//' for the file :', &
385             &          TRIM(watchout_file),'(Solution ?)')
386     ENDIF
387     !
3887000 FORMAT('seconds since ', I4.4,'-',I2.2,'-',I2.2,' ',I2.2,':',I2.2,':',I2.2)
3897001 FORMAT(' ', I4.4,'-',A3,'-',I2.2,' ',I2.2,':',I2.2,':',I2.2)
3907002 FORMAT('timesteps since ', I4.4,'-',I2.2,'-',I2.2,' ',I2.2,':',I2.2,':',I2.2)
391     !
392
393     dims(1) = nlandid1
394     dims(2) = tdimid1
395
396     assoc = 'time (nav_lat nav_lon)'
397     axx='TYX'
398     !
399     var = 'SWdown'
400     unit = 'W/m^2'
401     titre = 'Surface incident shortwave radiation'
402     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:2), varid)
403     IF (iret /= NF90_NOERR) THEN
404        CALL ipslerr (3,'watchout_init', &
405             &         'Variable '//var//' can not be defined for the file : ', &
406             &         TRIM(watchout_file),'(Solution ?)')
407     ENDIF
408     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
409     IF (iret /= NF90_NOERR) THEN
410        CALL ipslerr (3,'watchout_init', &
411             &          'Could not add attribut to variable '//var//' for the file :', &
412             &          TRIM(watchout_file),'(Solution ?)')
413     ENDIF
414     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
415     IF (iret /= NF90_NOERR) THEN
416        CALL ipslerr (3,'watchout_init', &
417             &          'Could not add attribut to variable '//var//' for the file :', &
418             &          TRIM(watchout_file),'(Solution ?)')
419     ENDIF
420     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
421     IF (iret /= NF90_NOERR) THEN
422        CALL ipslerr (3,'watchout_init', &
423             &          'Could not add attribut to variable '//var//' for the file :', &
424             &          TRIM(watchout_file),'(Solution ?)')
425     ENDIF
426     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
427     IF (iret /= NF90_NOERR) THEN
428        CALL ipslerr (3,'watchout_init', &
429             &          'Could not add attribut to variable '//var//' for the file :', &
430             &          TRIM(watchout_file),'(Solution ?)')
431     ENDIF
432     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
433     IF (iret /= NF90_NOERR) THEN
434        CALL ipslerr (3,'watchout_init', &
435             &          'Could not add attribut to variable '//var//' for the file :', &
436             &          TRIM(watchout_file),'(Solution ?)')
437     ENDIF
438     soldownid = varid
439     !
440     var = 'SWnet'
441     unit = 'W/m^2'
442     titre = 'Net surface short-wave flux'
443     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:2), varid)
444     IF (iret /= NF90_NOERR) THEN
445        CALL ipslerr (3,'watchout_init', &
446             &         'Variable '//var//' can not be defined for the file : ', &
447             &         TRIM(watchout_file),'(Solution ?)')
448     ENDIF
449     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
450     IF (iret /= NF90_NOERR) THEN
451        CALL ipslerr (3,'watchout_init', &
452             &          'Could not add attribut to variable '//var//' for the file :', &
453             &          TRIM(watchout_file),'(Solution ?)')
454     ENDIF
455     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
456     IF (iret /= NF90_NOERR) THEN
457        CALL ipslerr (3,'watchout_init', &
458             &          'Could not add attribut to variable '//var//' for the file :', &
459             &          TRIM(watchout_file),'(Solution ?)')
460     ENDIF
461     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
462     IF (iret /= NF90_NOERR) THEN
463        CALL ipslerr (3,'watchout_init', &
464             &          'Could not add attribut to variable '//var//' for the file :', &
465             &          TRIM(watchout_file),'(Solution ?)')
466     ENDIF
467     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
468     IF (iret /= NF90_NOERR) THEN
469        CALL ipslerr (3,'watchout_init', &
470             &          'Could not add attribut to variable '//var//' for the file :', &
471             &          TRIM(watchout_file),'(Solution ?)')
472     ENDIF
473     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
474     IF (iret /= NF90_NOERR) THEN
475        CALL ipslerr (3,'watchout_init', &
476             &          'Could not add attribut to variable '//var//' for the file :', &
477             &          TRIM(watchout_file),'(Solution ?)')
478     ENDIF
479     solnetid = varid
480     !
481     var = 'Rainf'
482     unit = 'Kg/m^2s'
483     titre = 'Rainfall rate'
484     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:2), varid)
485     IF (iret /= NF90_NOERR) THEN
486        CALL ipslerr (3,'watchout_init', &
487             &         'Variable '//var//' can not be defined for the file : ', &
488             &         TRIM(watchout_file),'(Solution ?)')
489     ENDIF
490     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
491     IF (iret /= NF90_NOERR) THEN
492        CALL ipslerr (3,'watchout_init', &
493             &          'Could not add attribut to variable '//var//' for the file :', &
494             &          TRIM(watchout_file),'(Solution ?)')
495     ENDIF
496     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
497     IF (iret /= NF90_NOERR) THEN
498        CALL ipslerr (3,'watchout_init', &
499             &          'Could not add attribut to variable '//var//' for the file :', &
500             &          TRIM(watchout_file),'(Solution ?)')
501     ENDIF
502     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
503     IF (iret /= NF90_NOERR) THEN
504        CALL ipslerr (3,'watchout_init', &
505             &          'Could not add attribut to variable '//var//' for the file :', &
506             &          TRIM(watchout_file),'(Solution ?)')
507     ENDIF
508     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
509     IF (iret /= NF90_NOERR) THEN
510        CALL ipslerr (3,'watchout_init', &
511             &          'Could not add attribut to variable '//var//' for the file :', &
512             &          TRIM(watchout_file),'(Solution ?)')
513     ENDIF
514     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
515     IF (iret /= NF90_NOERR) THEN
516        CALL ipslerr (3,'watchout_init', &
517             &          'Could not add attribut to variable '//var//' for the file :', &
518             &          TRIM(watchout_file),'(Solution ?)')
519     ENDIF
520     rainfid = varid
521     !
522     var = 'Snowf'
523     unit = 'Kg/m^2s'
524     titre = 'Snowfall rate'
525     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:2), varid)
526     IF (iret /= NF90_NOERR) THEN
527        CALL ipslerr (3,'watchout_init', &
528             &         'Variable '//var//' can not be defined for the file : ', &
529             &         TRIM(watchout_file),'(Solution ?)')
530     ENDIF
531     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
532     IF (iret /= NF90_NOERR) THEN
533        CALL ipslerr (3,'watchout_init', &
534             &          'Could not add attribut to variable '//var//' for the file :', &
535             &          TRIM(watchout_file),'(Solution ?)')
536     ENDIF
537     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
538     IF (iret /= NF90_NOERR) THEN
539        CALL ipslerr (3,'watchout_init', &
540             &          'Could not add attribut to variable '//var//' for the file :', &
541             &          TRIM(watchout_file),'(Solution ?)')
542     ENDIF
543     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
544     IF (iret /= NF90_NOERR) THEN
545        CALL ipslerr (3,'watchout_init', &
546             &          'Could not add attribut to variable '//var//' for the file :', &
547             &          TRIM(watchout_file),'(Solution ?)')
548     ENDIF
549     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
550     IF (iret /= NF90_NOERR) THEN
551        CALL ipslerr (3,'watchout_init', &
552             &          'Could not add attribut to variable '//var//' for the file :', &
553             &          TRIM(watchout_file),'(Solution ?)')
554     ENDIF
555     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
556     IF (iret /= NF90_NOERR) THEN
557        CALL ipslerr (3,'watchout_init', &
558             &          'Could not add attribut to variable '//var//' for the file :', &
559             &          TRIM(watchout_file),'(Solution ?)')
560     ENDIF
561     snowfid = varid
562     !
563     var = 'LWdown'
564     unit = 'W/m^2'
565     titre = 'Surface incident longwave radiation'
566     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:2), varid)
567     IF (iret /= NF90_NOERR) THEN
568        CALL ipslerr (3,'watchout_init', &
569             &         'Variable '//var//' can not be defined for the file : ', &
570             &         TRIM(watchout_file),'(Solution ?)')
571     ENDIF
572     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
573     IF (iret /= NF90_NOERR) THEN
574        CALL ipslerr (3,'watchout_init', &
575             &          'Could not add attribut to variable '//var//' for the file :', &
576             &          TRIM(watchout_file),'(Solution ?)')
577     ENDIF
578     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
579     IF (iret /= NF90_NOERR) THEN
580        CALL ipslerr (3,'watchout_init', &
581             &          'Could not add attribut to variable '//var//' for the file :', &
582             &          TRIM(watchout_file),'(Solution ?)')
583     ENDIF
584     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
585     IF (iret /= NF90_NOERR) THEN
586        CALL ipslerr (3,'watchout_init', &
587             &          'Could not add attribut to variable '//var//' for the file :', &
588             &          TRIM(watchout_file),'(Solution ?)')
589     ENDIF
590     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
591     IF (iret /= NF90_NOERR) THEN
592        CALL ipslerr (3,'watchout_init', &
593             &          'Could not add attribut to variable '//var//' for the file :', &
594             &          TRIM(watchout_file),'(Solution ?)')
595     ENDIF
596     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
597     IF (iret /= NF90_NOERR) THEN
598        CALL ipslerr (3,'watchout_init', &
599             &          'Could not add attribut to variable '//var//' for the file :', &
600             &          TRIM(watchout_file),'(Solution ?)')
601     ENDIF
602     lwradid = varid
603     !
604     var = 'PSurf'
605     unit = 'Pa'
606     titre = 'Surface pressure'
607     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:2), varid)
608     IF (iret /= NF90_NOERR) THEN
609        CALL ipslerr (3,'watchout_init', &
610             &         'Variable '//var//' can not be defined for the file : ', &
611             &         TRIM(watchout_file),'(Solution ?)')
612     ENDIF
613     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
614     IF (iret /= NF90_NOERR) THEN
615        CALL ipslerr (3,'watchout_init', &
616             &          'Could not add attribut to variable '//var//' for the file :', &
617             &          TRIM(watchout_file),'(Solution ?)')
618     ENDIF
619     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
620     IF (iret /= NF90_NOERR) THEN
621        CALL ipslerr (3,'watchout_init', &
622             &          'Could not add attribut to variable '//var//' for the file :', &
623             &          TRIM(watchout_file),'(Solution ?)')
624     ENDIF
625     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
626     IF (iret /= NF90_NOERR) THEN
627        CALL ipslerr (3,'watchout_init', &
628             &          'Could not add attribut to variable '//var//' for the file :', &
629             &          TRIM(watchout_file),'(Solution ?)')
630     ENDIF
631     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
632     IF (iret /= NF90_NOERR) THEN
633        CALL ipslerr (3,'watchout_init', &
634             &          'Could not add attribut to variable '//var//' for the file :', &
635             &          TRIM(watchout_file),'(Solution ?)')
636     ENDIF
637     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
638     IF (iret /= NF90_NOERR) THEN
639        CALL ipslerr (3,'watchout_init', &
640             &          'Could not add attribut to variable '//var//' for the file :', &
641             &          TRIM(watchout_file),'(Solution ?)')
642     ENDIF
643     psolid = varid
644     !
645     !
646     !  3D Variables to be written
647     !
648     dims(1) = nlandid1
649     dims(2) = nlevid1
650     dims(3) = tdimid1
651     !
652     assoc = 'time level (nav_lat nav_lon)'
653     axx='TZYX'
654     !
655     lat_name = 'levels'
656     iret = NF90_DEF_VAR(fid, lat_name, kind_r_watch, dims(1:3), varid)
657     IF (iret /= NF90_NOERR) THEN
658        CALL ipslerr (3,'watchout_init', &
659             &         'Variable '//var//' can not be defined for the file : ', &
660             &         TRIM(watchout_file),'(Solution ?)')
661     ENDIF
662     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
663     IF (iret /= NF90_NOERR) THEN
664        CALL ipslerr (3,'watchout_init', &
665             &          'Could not add attribut to variable '//var//' for the file :', &
666             &          TRIM(watchout_file),'(Solution ?)')
667     ENDIF
668     iret = NF90_PUT_ATT(fid, varid, 'units', "m")
669     IF (iret /= NF90_NOERR) THEN
670        CALL ipslerr (3,'watchout_init', &
671             &          'Could not add attribut to variable '//var//' for the file :', &
672             &          TRIM(watchout_file),'(Solution ?)')
673     ENDIF
674     iret = NF90_PUT_ATT(fid, varid, 'long_name', "Vertical levels")
675     IF (iret /= NF90_NOERR) THEN
676        CALL ipslerr (3,'watchout_init', &
677             &          'Could not add attribut to variable '//var//' for the file :', &
678             &          TRIM(watchout_file),'(Solution ?)')
679     ENDIF
680     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
681     IF (iret /= NF90_NOERR) THEN
682        CALL ipslerr (3,'watchout_init', &
683             &          'Could not add attribut to variable '//var//' for the file :', &
684             &          TRIM(watchout_file),'(Solution ?)')
685     ENDIF
686     lev_min = 2.
687     lev_max = 100.
688     iret = NF90_PUT_ATT(fid, varid, 'valid_min', lev_min)
689     IF (iret /= NF90_NOERR) THEN
690        CALL ipslerr (3,'watchout_init', &
691             &          'Could not add attribut to variable '//var//' for the file :', &
692             &          TRIM(watchout_file),'(Solution ?)')
693     ENDIF
694     iret = NF90_PUT_ATT(fid, varid, 'valid_max', lev_max)
695     IF (iret /= NF90_NOERR) THEN
696        CALL ipslerr (3,'watchout_init', &
697             &          'Could not add attribut to variable '//var//' for the file :', &
698             &          TRIM(watchout_file),'(Solution ?)')
699     ENDIF
700     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
701     IF (iret /= NF90_NOERR) THEN
702        CALL ipslerr (3,'watchout_init', &
703             &          'Could not add attribut to variable '//var//' for the file :', &
704             &          TRIM(watchout_file),'(Solution ?)')
705     ENDIF
706     zlevid = varid
707     !
708     !
709     var = 'Tair'
710     unit = 'K'
711     titre = 'Near surface air temperature'
712     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:3), varid)
713     IF (iret /= NF90_NOERR) THEN
714        CALL ipslerr (3,'watchout_init', &
715             &         'Variable '//var//' can not be defined for the file : ', &
716             &         TRIM(watchout_file),'(Solution ?)')
717     ENDIF
718     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
719     IF (iret /= NF90_NOERR) THEN
720        CALL ipslerr (3,'watchout_init', &
721             &          'Could not add attribut to variable '//var//' for the file :', &
722             &          TRIM(watchout_file),'(Solution ?)')
723     ENDIF
724     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
725     IF (iret /= NF90_NOERR) THEN
726        CALL ipslerr (3,'watchout_init', &
727             &          'Could not add attribut to variable '//var//' for the file :', &
728             &          TRIM(watchout_file),'(Solution ?)')
729     ENDIF
730     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
731     IF (iret /= NF90_NOERR) THEN
732        CALL ipslerr (3,'watchout_init', &
733             &          'Could not add attribut to variable '//var//' for the file :', &
734             &          TRIM(watchout_file),'(Solution ?)')
735     ENDIF
736     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
737     IF (iret /= NF90_NOERR) THEN
738        CALL ipslerr (3,'watchout_init', &
739             &          'Could not add attribut to variable '//var//' for the file :', &
740             &          TRIM(watchout_file),'(Solution ?)')
741     ENDIF
742     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
743     IF (iret /= NF90_NOERR) THEN
744        CALL ipslerr (3,'watchout_init', &
745             &          'Could not add attribut to variable '//var//' for the file :', &
746             &          TRIM(watchout_file),'(Solution ?)')
747     ENDIF
748     tairid = varid
749     !
750     var = 'Eair'
751     unit = 'J/m^2'
752     titre = 'Air potential energy'
753     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:3), varid)
754     IF (iret /= NF90_NOERR) THEN
755        CALL ipslerr (3,'watchout_init', &
756             &         'Variable '//var//' can not be defined for the file : ', &
757             &         TRIM(watchout_file),'(Solution ?)')
758     ENDIF
759     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
760     IF (iret /= NF90_NOERR) THEN
761        CALL ipslerr (3,'watchout_init', &
762             &          'Could not add attribut to variable '//var//' for the file :', &
763             &          TRIM(watchout_file),'(Solution ?)')
764     ENDIF
765     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
766     IF (iret /= NF90_NOERR) THEN
767        CALL ipslerr (3,'watchout_init', &
768             &          'Could not add attribut to variable '//var//' for the file :', &
769             &          TRIM(watchout_file),'(Solution ?)')
770     ENDIF
771     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
772     IF (iret /= NF90_NOERR) THEN
773        CALL ipslerr (3,'watchout_init', &
774             &          'Could not add attribut to variable '//var//' for the file :', &
775             &          TRIM(watchout_file),'(Solution ?)')
776     ENDIF
777     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
778     IF (iret /= NF90_NOERR) THEN
779        CALL ipslerr (3,'watchout_init', &
780             &          'Could not add attribut to variable '//var//' for the file :', &
781             &          TRIM(watchout_file),'(Solution ?)')
782     ENDIF
783     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
784     IF (iret /= NF90_NOERR) THEN
785        CALL ipslerr (3,'watchout_init', &
786             &          'Could not add attribut to variable '//var//' for the file :', &
787             &          TRIM(watchout_file),'(Solution ?)')
788     ENDIF
789     eairid = varid
790     !
791     var = 'Qair'
792     unit = 'Kg/Kg'
793     titre = 'Near surface specific humidity'
794     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:3), varid)
795     IF (iret /= NF90_NOERR) THEN
796        CALL ipslerr (3,'watchout_init', &
797             &         'Variable '//var//' can not be defined for the file : ', &
798             &         TRIM(watchout_file),'(Solution ?)')
799     ENDIF
800     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
801     IF (iret /= NF90_NOERR) THEN
802        CALL ipslerr (3,'watchout_init', &
803             &          'Could not add attribut to variable '//var//' for the file :', &
804             &          TRIM(watchout_file),'(Solution ?)')
805     ENDIF
806     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
807     IF (iret /= NF90_NOERR) THEN
808        CALL ipslerr (3,'watchout_init', &
809             &          'Could not add attribut to variable '//var//' for the file :', &
810             &          TRIM(watchout_file),'(Solution ?)')
811     ENDIF
812     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
813     IF (iret /= NF90_NOERR) THEN
814        CALL ipslerr (3,'watchout_init', &
815             &          'Could not add attribut to variable '//var//' for the file :', &
816             &          TRIM(watchout_file),'(Solution ?)')
817     ENDIF
818     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
819     IF (iret /= NF90_NOERR) THEN
820        CALL ipslerr (3,'watchout_init', &
821             &          'Could not add attribut to variable '//var//' for the file :', &
822             &          TRIM(watchout_file),'(Solution ?)')
823     ENDIF
824     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
825     IF (iret /= NF90_NOERR) THEN
826        CALL ipslerr (3,'watchout_init', &
827             &          'Could not add attribut to variable '//var//' for the file :', &
828             &          TRIM(watchout_file),'(Solution ?)')
829     ENDIF
830     qairid = varid
831     !
832     var = 'Wind_N'
833     unit = 'm/s'
834     titre = 'Near surface northward wind component'
835     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:3), varid)
836     IF (iret /= NF90_NOERR) THEN
837        CALL ipslerr (3,'watchout_init', &
838             &         'Variable '//var//' can not be defined for the file : ', &
839             &         TRIM(watchout_file),'(Solution ?)')
840     ENDIF
841     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
842     IF (iret /= NF90_NOERR) THEN
843        CALL ipslerr (3,'watchout_init', &
844             &          'Could not add attribut to variable '//var//' for the file :', &
845             &          TRIM(watchout_file),'(Solution ?)')
846     ENDIF
847     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
848     IF (iret /= NF90_NOERR) THEN
849        CALL ipslerr (3,'watchout_init', &
850             &          'Could not add attribut to variable '//var//' for the file :', &
851             &          TRIM(watchout_file),'(Solution ?)')
852     ENDIF
853     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
854     IF (iret /= NF90_NOERR) THEN
855        CALL ipslerr (3,'watchout_init', &
856             &          'Could not add attribut to variable '//var//' for the file :', &
857             &          TRIM(watchout_file),'(Solution ?)')
858     ENDIF
859     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
860     IF (iret /= NF90_NOERR) THEN
861        CALL ipslerr (3,'watchout_init', &
862             &          'Could not add attribut to variable '//var//' for the file :', &
863             &          TRIM(watchout_file),'(Solution ?)')
864     ENDIF
865     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
866     IF (iret /= NF90_NOERR) THEN
867        CALL ipslerr (3,'watchout_init', &
868             &          'Could not add attribut to variable '//var//' for the file :', &
869             &          TRIM(watchout_file),'(Solution ?)')
870     ENDIF
871     uid = varid
872     !
873     var = 'Wind_E'
874     unit = 'm/s'
875     titre = 'Near surface eastward wind component'
876     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:3), varid)
877     IF (iret /= NF90_NOERR) THEN
878        CALL ipslerr (3,'watchout_init', &
879             &         'Variable '//var//' can not be defined for the file : ', &
880             &         TRIM(watchout_file),'(Solution ?)')
881     ENDIF
882     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
883     IF (iret /= NF90_NOERR) THEN
884        CALL ipslerr (3,'watchout_init', &
885             &          'Could not add attribut to variable '//var//' for the file :', &
886             &          TRIM(watchout_file),'(Solution ?)')
887     ENDIF
888     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
889     IF (iret /= NF90_NOERR) THEN
890        CALL ipslerr (3,'watchout_init', &
891             &          'Could not add attribut to variable '//var//' for the file :', &
892             &          TRIM(watchout_file),'(Solution ?)')
893     ENDIF
894     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
895     IF (iret /= NF90_NOERR) THEN
896        CALL ipslerr (3,'watchout_init', &
897             &          'Could not add attribut to variable '//var//' for the file :', &
898             &          TRIM(watchout_file),'(Solution ?)')
899     ENDIF
900     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
901     IF (iret /= NF90_NOERR) THEN
902        CALL ipslerr (3,'watchout_init', &
903             &          'Could not add attribut to variable '//var//' for the file :', &
904             &          TRIM(watchout_file),'(Solution ?)')
905     ENDIF
906     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba) 
907     IF (iret /= NF90_NOERR) THEN
908        CALL ipslerr (3,'watchout_init', &
909             &          'Could not add attribut to variable '//var//' for the file :', &
910             &          TRIM(watchout_file),'(Solution ?)')
911     ENDIF
912     vid = varid
913     !
914     var = 'petAcoef'
915     unit = '-'
916     titre = 'Coeficients A from the PBL resolution for T'
917     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:3), varid)
918     IF (iret /= NF90_NOERR) THEN
919        CALL ipslerr (3,'watchout_init', &
920             &         'Variable '//var//' can not be defined for the file : ', &
921             &         TRIM(watchout_file),'(Solution ?)')
922     ENDIF
923     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
924     IF (iret /= NF90_NOERR) THEN
925        CALL ipslerr (3,'watchout_init', &
926             &          'Could not add attribut to variable '//var//' for the file :', &
927             &          TRIM(watchout_file),'(Solution ?)')
928     ENDIF
929     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
930     IF (iret /= NF90_NOERR) THEN
931        CALL ipslerr (3,'watchout_init', &
932             &          'Could not add attribut to variable '//var//' for the file :', &
933             &          TRIM(watchout_file),'(Solution ?)')
934     ENDIF
935     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
936     IF (iret /= NF90_NOERR) THEN
937        CALL ipslerr (3,'watchout_init', &
938             &          'Could not add attribut to variable '//var//' for the file :', &
939             &          TRIM(watchout_file),'(Solution ?)')
940     ENDIF
941     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
942     IF (iret /= NF90_NOERR) THEN
943        CALL ipslerr (3,'watchout_init', &
944             &          'Could not add attribut to variable '//var//' for the file :', &
945             &          TRIM(watchout_file),'(Solution ?)')
946     ENDIF
947     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba) 
948     IF (iret /= NF90_NOERR) THEN
949        CALL ipslerr (3,'watchout_init', &
950             &          'Could not add attribut to variable '//var//' for the file :', &
951             &          TRIM(watchout_file),'(Solution ?)')
952     ENDIF
953     petAcoefid = varid
954     !
955     var = 'peqAcoef'
956     unit = '-'
957     titre = 'Coeficients A from the PBL resolution for q'
958     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:3), varid)
959     IF (iret /= NF90_NOERR) THEN
960        CALL ipslerr (3,'watchout_init', &
961             &         'Variable '//var//' can not be defined for the file : ', &
962             &         TRIM(watchout_file),'(Solution ?)')
963     ENDIF
964     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
965     IF (iret /= NF90_NOERR) THEN
966        CALL ipslerr (3,'watchout_init', &
967             &          'Could not add attribut to variable '//var//' for the file :', &
968             &          TRIM(watchout_file),'(Solution ?)')
969     ENDIF
970     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
971     IF (iret /= NF90_NOERR) THEN
972        CALL ipslerr (3,'watchout_init', &
973             &          'Could not add attribut to variable '//var//' for the file :', &
974             &          TRIM(watchout_file),'(Solution ?)')
975     ENDIF
976     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
977     IF (iret /= NF90_NOERR) THEN
978        CALL ipslerr (3,'watchout_init', &
979             &          'Could not add attribut to variable '//var//' for the file :', &
980             &          TRIM(watchout_file),'(Solution ?)')
981     ENDIF
982     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
983     IF (iret /= NF90_NOERR) THEN
984        CALL ipslerr (3,'watchout_init', &
985             &          'Could not add attribut to variable '//var//' for the file :', &
986             &          TRIM(watchout_file),'(Solution ?)')
987     ENDIF
988     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba) 
989     IF (iret /= NF90_NOERR) THEN
990        CALL ipslerr (3,'watchout_init', &
991             &          'Could not add attribut to variable '//var//' for the file :', &
992             &          TRIM(watchout_file),'(Solution ?)')
993     ENDIF
994     peqAcoefid = varid
995     !
996     var = 'petBcoef'
997     unit = '-'
998     titre = 'Coeficients B from the PBL resolution for T'
999     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:3), varid)
1000     IF (iret /= NF90_NOERR) THEN
1001        CALL ipslerr (3,'watchout_init', &
1002             &         'Variable '//var//' can not be defined for the file : ', &
1003             &         TRIM(watchout_file),'(Solution ?)')
1004     ENDIF
1005     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
1006     IF (iret /= NF90_NOERR) THEN
1007        CALL ipslerr (3,'watchout_init', &
1008             &          'Could not add attribut to variable '//var//' for the file :', &
1009             &          TRIM(watchout_file),'(Solution ?)')
1010     ENDIF
1011     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
1012     IF (iret /= NF90_NOERR) THEN
1013        CALL ipslerr (3,'watchout_init', &
1014             &          'Could not add attribut to variable '//var//' for the file :', &
1015             &          TRIM(watchout_file),'(Solution ?)')
1016     ENDIF
1017     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
1018     IF (iret /= NF90_NOERR) THEN
1019        CALL ipslerr (3,'watchout_init', &
1020             &          'Could not add attribut to variable '//var//' for the file :', &
1021             &          TRIM(watchout_file),'(Solution ?)')
1022     ENDIF
1023     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
1024     IF (iret /= NF90_NOERR) THEN
1025        CALL ipslerr (3,'watchout_init', &
1026             &          'Could not add attribut to variable '//var//' for the file :', &
1027             &          TRIM(watchout_file),'(Solution ?)')
1028     ENDIF
1029     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba) 
1030     IF (iret /= NF90_NOERR) THEN
1031        CALL ipslerr (3,'watchout_init', &
1032             &          'Could not add attribut to variable '//var//' for the file :', &
1033             &          TRIM(watchout_file),'(Solution ?)')
1034     ENDIF
1035     petBcoefid = varid
1036     !
1037     var = 'peqBcoef'
1038     unit = '-'
1039     titre = 'Coeficients B from the PBL resolution for q'
1040     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:3), varid)
1041     IF (iret /= NF90_NOERR) THEN
1042        CALL ipslerr (3,'watchout_init', &
1043             &         'Variable '//var//' can not be defined for the file : ', &
1044             &         TRIM(watchout_file),'(Solution ?)')
1045     ENDIF
1046     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
1047     IF (iret /= NF90_NOERR) THEN
1048        CALL ipslerr (3,'watchout_init', &
1049             &          'Could not add attribut to variable '//var//' for the file :', &
1050             &          TRIM(watchout_file),'(Solution ?)')
1051     ENDIF
1052     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
1053     IF (iret /= NF90_NOERR) THEN
1054        CALL ipslerr (3,'watchout_init', &
1055             &          'Could not add attribut to variable '//var//' for the file :', &
1056             &          TRIM(watchout_file),'(Solution ?)')
1057     ENDIF
1058     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
1059     IF (iret /= NF90_NOERR) THEN
1060        CALL ipslerr (3,'watchout_init', &
1061             &          'Could not add attribut to variable '//var//' for the file :', &
1062             &          TRIM(watchout_file),'(Solution ?)')
1063     ENDIF
1064     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
1065     IF (iret /= NF90_NOERR) THEN
1066        CALL ipslerr (3,'watchout_init', &
1067             &          'Could not add attribut to variable '//var//' for the file :', &
1068             &          TRIM(watchout_file),'(Solution ?)')
1069     ENDIF
1070     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba) 
1071     IF (iret /= NF90_NOERR) THEN
1072        CALL ipslerr (3,'watchout_init', &
1073             &          'Could not add attribut to variable '//var//' for the file :', &
1074             &          TRIM(watchout_file),'(Solution ?)')
1075     ENDIF
1076     peqBcoefid = varid
1077     !
1078     var = 'cdrag'
1079     unit = '-'
1080     titre = 'Surface drag'
1081     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:3), varid)
1082     IF (iret /= NF90_NOERR) THEN
1083        CALL ipslerr (3,'watchout_init', &
1084             &         'Variable '//var//' can not be defined for the file : ', &
1085             &         TRIM(watchout_file),'(Solution ?)')
1086     ENDIF
1087     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
1088     IF (iret /= NF90_NOERR) THEN
1089        CALL ipslerr (3,'watchout_init', &
1090             &          'Could not add attribut to variable '//var//' for the file :', &
1091             &          TRIM(watchout_file),'(Solution ?)')
1092     ENDIF
1093     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
1094     IF (iret /= NF90_NOERR) THEN
1095        CALL ipslerr (3,'watchout_init', &
1096             &          'Could not add attribut to variable '//var//' for the file :', &
1097             &          TRIM(watchout_file),'(Solution ?)')
1098     ENDIF
1099     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
1100     IF (iret /= NF90_NOERR) THEN
1101        CALL ipslerr (3,'watchout_init', &
1102             &          'Could not add attribut to variable '//var//' for the file :', &
1103             &          TRIM(watchout_file),'(Solution ?)')
1104     ENDIF
1105     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
1106     IF (iret /= NF90_NOERR) THEN
1107        CALL ipslerr (3,'watchout_init', &
1108             &          'Could not add attribut to variable '//var//' for the file :', &
1109             &          TRIM(watchout_file),'(Solution ?)')
1110     ENDIF
1111     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba) 
1112     IF (iret /= NF90_NOERR) THEN
1113        CALL ipslerr (3,'watchout_init', &
1114             &          'Could not add attribut to variable '//var//' for the file :', &
1115             &          TRIM(watchout_file),'(Solution ?)')
1116     ENDIF
1117     cdragid = varid
1118     !
1119     !
1120     var = 'ccanopy'
1121     unit = '-'
1122     titre = 'CO2 concentration in the canopy'
1123     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:3), varid)
1124     IF (iret /= NF90_NOERR) THEN
1125        CALL ipslerr (3,'watchout_init', &
1126             &         'Variable '//var//' can not be defined for the file : ', &
1127             &         TRIM(watchout_file),'(Solution ?)')
1128     ENDIF
1129     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
1130     IF (iret /= NF90_NOERR) THEN
1131        CALL ipslerr (3,'watchout_init', &
1132             &          'Could not add attribut to variable '//var//' for the file :', &
1133             &          TRIM(watchout_file),'(Solution ?)')
1134     ENDIF
1135     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
1136     IF (iret /= NF90_NOERR) THEN
1137        CALL ipslerr (3,'watchout_init', &
1138             &          'Could not add attribut to variable '//var//' for the file :', &
1139             &          TRIM(watchout_file),'(Solution ?)')
1140     ENDIF
1141     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
1142     IF (iret /= NF90_NOERR) THEN
1143        CALL ipslerr (3,'watchout_init', &
1144             &          'Could not add attribut to variable '//var//' for the file :', &
1145             &          TRIM(watchout_file),'(Solution ?)')
1146     ENDIF
1147     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
1148     IF (iret /= NF90_NOERR) THEN
1149        CALL ipslerr (3,'watchout_init', &
1150             &          'Could not add attribut to variable '//var//' for the file :', &
1151             &          TRIM(watchout_file),'(Solution ?)')
1152     ENDIF
1153     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba) 
1154     IF (iret /= NF90_NOERR) THEN
1155        CALL ipslerr (3,'watchout_init', &
1156             &          'Could not add attribut to variable '//var//' for the file :', &
1157             &          TRIM(watchout_file),'(Solution ?)')
1158     ENDIF
1159     ccanopyid = varid
1160     !
1161     !
1162     ! Time fixed variable
1163     !
1164     dims(1) = nlonid1
1165     dims(2) = nlatid1
1166     !
1167     var = 'contfrac'
1168     unit = '-'
1169     titre = 'Fraction of continent'
1170     assoc = 'nav_lat nav_lon'
1171     axx='YX'
1172     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:2), varid)
1173     IF (iret /= NF90_NOERR) THEN
1174        CALL ipslerr (3,'watchout_init', &
1175             &         'Variable '//var//' can not be defined for the file : ', &
1176             &         TRIM(watchout_file),'(Solution ?)')
1177     ENDIF
1178     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
1179     IF (iret /= NF90_NOERR) THEN
1180        CALL ipslerr (3,'watchout_init', &
1181             &          'Could not add attribut to variable '//var//' for the file :', &
1182             &          TRIM(watchout_file),'(Solution ?)')
1183     ENDIF
1184     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
1185     IF (iret /= NF90_NOERR) THEN
1186        CALL ipslerr (3,'watchout_init', &
1187             &          'Could not add attribut to variable '//var//' for the file :', &
1188             &          TRIM(watchout_file),'(Solution ?)')
1189     ENDIF
1190     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
1191     IF (iret /= NF90_NOERR) THEN
1192        CALL ipslerr (3,'watchout_init', &
1193             &          'Could not add attribut to variable '//var//' for the file :', &
1194             &          TRIM(watchout_file),'(Solution ?)')
1195     ENDIF
1196     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
1197     IF (iret /= NF90_NOERR) THEN
1198        CALL ipslerr (3,'watchout_init', &
1199             &          'Could not add attribut to variable '//var//' for the file :', &
1200             &          TRIM(watchout_file),'(Solution ?)')
1201     ENDIF
1202     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
1203     IF (iret /= NF90_NOERR) THEN
1204        CALL ipslerr (3,'watchout_init', &
1205             &          'Could not add attribut to variable '//var//' for the file :', &
1206             &          TRIM(watchout_file),'(Solution ?)')
1207     ENDIF
1208     contid=varid
1209     !
1210     !
1211     var = 'neighboursNN'
1212     unit = '-'
1213     titre = 'indices of North neighbours of each grid point'
1214     assoc = 'nav_lat nav_lon'
1215     axx='YX'
1216     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:2), varid)
1217     IF (iret /= NF90_NOERR) THEN
1218        CALL ipslerr (3,'watchout_init', &
1219             &         'Variable '//var//' can not be defined for the file : ', &
1220             &         TRIM(watchout_file),'(Solution ?)')
1221     ENDIF
1222     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
1223     IF (iret /= NF90_NOERR) THEN
1224        CALL ipslerr (3,'watchout_init', &
1225             &          'Could not add attribut to variable '//var//' for the file :', &
1226             &          TRIM(watchout_file),'(Solution ?)')
1227     ENDIF
1228     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
1229     IF (iret /= NF90_NOERR) THEN
1230        CALL ipslerr (3,'watchout_init', &
1231             &          'Could not add attribut to variable '//var//' for the file :', &
1232             &          TRIM(watchout_file),'(Solution ?)')
1233     ENDIF
1234     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
1235     IF (iret /= NF90_NOERR) THEN
1236        CALL ipslerr (3,'watchout_init', &
1237             &          'Could not add attribut to variable '//var//' for the file :', &
1238             &          TRIM(watchout_file),'(Solution ?)')
1239     ENDIF
1240     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
1241     IF (iret /= NF90_NOERR) THEN
1242        CALL ipslerr (3,'watchout_init', &
1243             &          'Could not add attribut to variable '//var//' for the file :', &
1244             &          TRIM(watchout_file),'(Solution ?)')
1245     ENDIF
1246     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
1247     IF (iret /= NF90_NOERR) THEN
1248        CALL ipslerr (3,'watchout_init', &
1249             &          'Could not add attribut to variable '//var//' for the file :', &
1250             &          TRIM(watchout_file),'(Solution ?)')
1251     ENDIF
1252     neighid(1)=varid
1253     !
1254     var = 'neighboursNE'
1255     unit = '-'
1256     titre = 'indices of North-East neighbours of each grid point'
1257     assoc = 'nav_lat nav_lon'
1258     axx='YX'
1259     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:2), varid)
1260     IF (iret /= NF90_NOERR) THEN
1261        CALL ipslerr (3,'watchout_init', &
1262             &         'Variable '//var//' can not be defined for the file : ', &
1263             &         TRIM(watchout_file),'(Solution ?)')
1264     ENDIF
1265     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
1266     IF (iret /= NF90_NOERR) THEN
1267        CALL ipslerr (3,'watchout_init', &
1268             &          'Could not add attribut to variable '//var//' for the file :', &
1269             &          TRIM(watchout_file),'(Solution ?)')
1270     ENDIF
1271     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
1272     IF (iret /= NF90_NOERR) THEN
1273        CALL ipslerr (3,'watchout_init', &
1274             &          'Could not add attribut to variable '//var//' for the file :', &
1275             &          TRIM(watchout_file),'(Solution ?)')
1276     ENDIF
1277     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
1278     IF (iret /= NF90_NOERR) THEN
1279        CALL ipslerr (3,'watchout_init', &
1280             &          'Could not add attribut to variable '//var//' for the file :', &
1281             &          TRIM(watchout_file),'(Solution ?)')
1282     ENDIF
1283     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
1284     IF (iret /= NF90_NOERR) THEN
1285        CALL ipslerr (3,'watchout_init', &
1286             &          'Could not add attribut to variable '//var//' for the file :', &
1287             &          TRIM(watchout_file),'(Solution ?)')
1288     ENDIF
1289     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
1290     IF (iret /= NF90_NOERR) THEN
1291        CALL ipslerr (3,'watchout_init', &
1292             &          'Could not add attribut to variable '//var//' for the file :', &
1293             &          TRIM(watchout_file),'(Solution ?)')
1294     ENDIF
1295     neighid(2)=varid
1296     !
1297     var = 'neighboursEE'
1298     unit = '-'
1299     titre = 'indices of East neighbours of each grid point'
1300     assoc = 'nav_lat nav_lon'
1301     axx='YX'
1302     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:2), varid)
1303     IF (iret /= NF90_NOERR) THEN
1304        CALL ipslerr (3,'watchout_init', &
1305             &         'Variable '//var//' can not be defined for the file : ', &
1306             &         TRIM(watchout_file),'(Solution ?)')
1307     ENDIF
1308     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
1309     IF (iret /= NF90_NOERR) THEN
1310        CALL ipslerr (3,'watchout_init', &
1311             &          'Could not add attribut to variable '//var//' for the file :', &
1312             &          TRIM(watchout_file),'(Solution ?)')
1313     ENDIF
1314     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
1315     IF (iret /= NF90_NOERR) THEN
1316        CALL ipslerr (3,'watchout_init', &
1317             &          'Could not add attribut to variable '//var//' for the file :', &
1318             &          TRIM(watchout_file),'(Solution ?)')
1319     ENDIF
1320     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
1321     IF (iret /= NF90_NOERR) THEN
1322        CALL ipslerr (3,'watchout_init', &
1323             &          'Could not add attribut to variable '//var//' for the file :', &
1324             &          TRIM(watchout_file),'(Solution ?)')
1325     ENDIF
1326     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
1327     IF (iret /= NF90_NOERR) THEN
1328        CALL ipslerr (3,'watchout_init', &
1329             &          'Could not add attribut to variable '//var//' for the file :', &
1330             &          TRIM(watchout_file),'(Solution ?)')
1331     ENDIF
1332     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
1333     IF (iret /= NF90_NOERR) THEN
1334        CALL ipslerr (3,'watchout_init', &
1335             &          'Could not add attribut to variable '//var//' for the file :', &
1336             &          TRIM(watchout_file),'(Solution ?)')
1337     ENDIF
1338     neighid(3)=varid
1339     !
1340     var = 'neighboursSE'
1341     unit = '-'
1342     titre = 'indices of South-East neighbours of each grid point'
1343     assoc = 'nav_lat nav_lon'
1344     axx='YX'
1345     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:2), varid)
1346     IF (iret /= NF90_NOERR) THEN
1347        CALL ipslerr (3,'watchout_init', &
1348             &         'Variable '//var//' can not be defined for the file : ', &
1349             &         TRIM(watchout_file),'(Solution ?)')
1350     ENDIF
1351     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
1352     IF (iret /= NF90_NOERR) THEN
1353        CALL ipslerr (3,'watchout_init', &
1354             &          'Could not add attribut to variable '//var//' for the file :', &
1355             &          TRIM(watchout_file),'(Solution ?)')
1356     ENDIF
1357     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
1358     IF (iret /= NF90_NOERR) THEN
1359        CALL ipslerr (3,'watchout_init', &
1360             &          'Could not add attribut to variable '//var//' for the file :', &
1361             &          TRIM(watchout_file),'(Solution ?)')
1362     ENDIF
1363     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
1364     IF (iret /= NF90_NOERR) THEN
1365        CALL ipslerr (3,'watchout_init', &
1366             &          'Could not add attribut to variable '//var//' for the file :', &
1367             &          TRIM(watchout_file),'(Solution ?)')
1368     ENDIF
1369     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
1370     IF (iret /= NF90_NOERR) THEN
1371        CALL ipslerr (3,'watchout_init', &
1372             &          'Could not add attribut to variable '//var//' for the file :', &
1373             &          TRIM(watchout_file),'(Solution ?)')
1374     ENDIF
1375     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
1376     IF (iret /= NF90_NOERR) THEN
1377        CALL ipslerr (3,'watchout_init', &
1378             &          'Could not add attribut to variable '//var//' for the file :', &
1379             &          TRIM(watchout_file),'(Solution ?)')
1380     ENDIF
1381     neighid(4)=varid
1382     !
1383     var = 'neighboursSS'
1384     unit = '-'
1385     titre = 'indices of South neighbours of each grid point'
1386     assoc = 'nav_lat nav_lon'
1387     axx='YX'
1388     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:2), varid)
1389     IF (iret /= NF90_NOERR) THEN
1390        CALL ipslerr (3,'watchout_init', &
1391             &         'Variable '//var//' can not be defined for the file : ', &
1392             &         TRIM(watchout_file),'(Solution ?)')
1393     ENDIF
1394     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
1395     IF (iret /= NF90_NOERR) THEN
1396        CALL ipslerr (3,'watchout_init', &
1397             &          'Could not add attribut to variable '//var//' for the file :', &
1398             &          TRIM(watchout_file),'(Solution ?)')
1399     ENDIF
1400     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
1401     IF (iret /= NF90_NOERR) THEN
1402        CALL ipslerr (3,'watchout_init', &
1403             &          'Could not add attribut to variable '//var//' for the file :', &
1404             &          TRIM(watchout_file),'(Solution ?)')
1405     ENDIF
1406     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
1407     IF (iret /= NF90_NOERR) THEN
1408        CALL ipslerr (3,'watchout_init', &
1409             &          'Could not add attribut to variable '//var//' for the file :', &
1410             &          TRIM(watchout_file),'(Solution ?)')
1411     ENDIF
1412     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
1413     IF (iret /= NF90_NOERR) THEN
1414        CALL ipslerr (3,'watchout_init', &
1415             &          'Could not add attribut to variable '//var//' for the file :', &
1416             &          TRIM(watchout_file),'(Solution ?)')
1417     ENDIF
1418     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
1419     IF (iret /= NF90_NOERR) THEN
1420        CALL ipslerr (3,'watchout_init', &
1421             &          'Could not add attribut to variable '//var//' for the file :', &
1422             &          TRIM(watchout_file),'(Solution ?)')
1423     ENDIF
1424     neighid(5)=varid
1425     !
1426     var = 'neighboursSW'
1427     unit = '-'
1428     titre = 'indices of South-West neighbours of each grid point'
1429     assoc = 'nav_lat nav_lon'
1430     axx='YX'
1431     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:2), varid)
1432     IF (iret /= NF90_NOERR) THEN
1433        CALL ipslerr (3,'watchout_init', &
1434             &         'Variable '//var//' can not be defined for the file : ', &
1435             &         TRIM(watchout_file),'(Solution ?)')
1436     ENDIF
1437     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
1438     IF (iret /= NF90_NOERR) THEN
1439        CALL ipslerr (3,'watchout_init', &
1440             &          'Could not add attribut to variable '//var//' for the file :', &
1441             &          TRIM(watchout_file),'(Solution ?)')
1442     ENDIF
1443     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
1444     IF (iret /= NF90_NOERR) THEN
1445        CALL ipslerr (3,'watchout_init', &
1446             &          'Could not add attribut to variable '//var//' for the file :', &
1447             &          TRIM(watchout_file),'(Solution ?)')
1448     ENDIF
1449     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
1450     IF (iret /= NF90_NOERR) THEN
1451        CALL ipslerr (3,'watchout_init', &
1452             &          'Could not add attribut to variable '//var//' for the file :', &
1453             &          TRIM(watchout_file),'(Solution ?)')
1454     ENDIF
1455     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
1456     IF (iret /= NF90_NOERR) THEN
1457        CALL ipslerr (3,'watchout_init', &
1458             &          'Could not add attribut to variable '//var//' for the file :', &
1459             &          TRIM(watchout_file),'(Solution ?)')
1460     ENDIF
1461     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
1462     IF (iret /= NF90_NOERR) THEN
1463        CALL ipslerr (3,'watchout_init', &
1464             &          'Could not add attribut to variable '//var//' for the file :', &
1465             &          TRIM(watchout_file),'(Solution ?)')
1466     ENDIF
1467     neighid(6)=varid
1468     !
1469     var = 'neighboursWW'
1470     unit = '-'
1471     titre = 'indices of West neighbours of each grid point'
1472     assoc = 'nav_lat nav_lon'
1473     axx='YX'
1474     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:2), varid)
1475     IF (iret /= NF90_NOERR) THEN
1476        CALL ipslerr (3,'watchout_init', &
1477             &         'Variable '//var//' can not be defined for the file : ', &
1478             &         TRIM(watchout_file),'(Solution ?)')
1479     ENDIF
1480     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
1481     IF (iret /= NF90_NOERR) THEN
1482        CALL ipslerr (3,'watchout_init', &
1483             &          'Could not add attribut to variable '//var//' for the file :', &
1484             &          TRIM(watchout_file),'(Solution ?)')
1485     ENDIF
1486     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
1487     IF (iret /= NF90_NOERR) THEN
1488        CALL ipslerr (3,'watchout_init', &
1489             &          'Could not add attribut to variable '//var//' for the file :', &
1490             &          TRIM(watchout_file),'(Solution ?)')
1491     ENDIF
1492     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
1493     IF (iret /= NF90_NOERR) THEN
1494        CALL ipslerr (3,'watchout_init', &
1495             &          'Could not add attribut to variable '//var//' for the file :', &
1496             &          TRIM(watchout_file),'(Solution ?)')
1497     ENDIF
1498     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
1499     IF (iret /= NF90_NOERR) THEN
1500        CALL ipslerr (3,'watchout_init', &
1501             &          'Could not add attribut to variable '//var//' for the file :', &
1502             &          TRIM(watchout_file),'(Solution ?)')
1503     ENDIF
1504     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
1505     IF (iret /= NF90_NOERR) THEN
1506        CALL ipslerr (3,'watchout_init', &
1507             &          'Could not add attribut to variable '//var//' for the file :', &
1508             &          TRIM(watchout_file),'(Solution ?)')
1509     ENDIF
1510     neighid(7)=varid
1511     !
1512     var = 'neighboursNW'
1513     unit = '-'
1514     titre = 'indices of North-West neighbours of each grid point'
1515     assoc = 'nav_lat nav_lon'
1516     axx='YX'
1517     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:2), varid)
1518     IF (iret /= NF90_NOERR) THEN
1519        CALL ipslerr (3,'watchout_init', &
1520             &         'Variable '//var//' can not be defined for the file : ', &
1521             &         TRIM(watchout_file),'(Solution ?)')
1522     ENDIF
1523     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
1524     IF (iret /= NF90_NOERR) THEN
1525        CALL ipslerr (3,'watchout_init', &
1526             &          'Could not add attribut to variable '//var//' for the file :', &
1527             &          TRIM(watchout_file),'(Solution ?)')
1528     ENDIF
1529     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
1530     IF (iret /= NF90_NOERR) THEN
1531        CALL ipslerr (3,'watchout_init', &
1532             &          'Could not add attribut to variable '//var//' for the file :', &
1533             &          TRIM(watchout_file),'(Solution ?)')
1534     ENDIF
1535     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
1536     IF (iret /= NF90_NOERR) THEN
1537        CALL ipslerr (3,'watchout_init', &
1538             &          'Could not add attribut to variable '//var//' for the file :', &
1539             &          TRIM(watchout_file),'(Solution ?)')
1540     ENDIF
1541     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
1542     IF (iret /= NF90_NOERR) THEN
1543        CALL ipslerr (3,'watchout_init', &
1544             &          'Could not add attribut to variable '//var//' for the file :', &
1545             &          TRIM(watchout_file),'(Solution ?)')
1546     ENDIF
1547     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
1548     IF (iret /= NF90_NOERR) THEN
1549        CALL ipslerr (3,'watchout_init', &
1550             &          'Could not add attribut to variable '//var//' for the file :', &
1551             &          TRIM(watchout_file),'(Solution ?)')
1552     ENDIF
1553     neighid(8)=varid
1554     !
1555     !
1556     var = 'resolutionX'
1557     unit = 'm'
1558     titre = 'resolution in x at each grid point'
1559     assoc = 'nav_lat nav_lon'
1560     axx='YX'
1561     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:2), varid)
1562     IF (iret /= NF90_NOERR) THEN
1563        CALL ipslerr (3,'watchout_init', &
1564             &         'Variable '//var//' can not be defined for the file : ', &
1565             &         TRIM(watchout_file),'(Solution ?)')
1566     ENDIF
1567     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
1568     IF (iret /= NF90_NOERR) THEN
1569        CALL ipslerr (3,'watchout_init', &
1570             &          'Could not add attribut to variable '//var//' for the file :', &
1571             &          TRIM(watchout_file),'(Solution ?)')
1572     ENDIF
1573     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
1574     IF (iret /= NF90_NOERR) THEN
1575        CALL ipslerr (3,'watchout_init', &
1576             &          'Could not add attribut to variable '//var//' for the file :', &
1577             &          TRIM(watchout_file),'(Solution ?)')
1578     ENDIF
1579     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
1580     IF (iret /= NF90_NOERR) THEN
1581        CALL ipslerr (3,'watchout_init', &
1582             &          'Could not add attribut to variable '//var//' for the file :', &
1583             &          TRIM(watchout_file),'(Solution ?)')
1584     ENDIF
1585     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
1586     IF (iret /= NF90_NOERR) THEN
1587        CALL ipslerr (3,'watchout_init', &
1588             &          'Could not add attribut to variable '//var//' for the file :', &
1589             &          TRIM(watchout_file),'(Solution ?)')
1590     ENDIF
1591     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
1592     IF (iret /= NF90_NOERR) THEN
1593        CALL ipslerr (3,'watchout_init', &
1594             &          'Could not add attribut to variable '//var//' for the file :', &
1595             &          TRIM(watchout_file),'(Solution ?)')
1596     ENDIF
1597     resolxid=varid
1598     !
1599     var = 'resolutionY'
1600     unit = 'm'
1601     titre = 'resolution in y at each grid point'
1602     assoc = 'nav_lat nav_lon'
1603     axx='YX'
1604     iret = NF90_DEF_VAR(fid,var, kind_r_watch, dims(1:2), varid)
1605     IF (iret /= NF90_NOERR) THEN
1606        CALL ipslerr (3,'watchout_init', &
1607             &         'Variable '//var//' can not be defined for the file : ', &
1608             &         TRIM(watchout_file),'(Solution ?)')
1609     ENDIF
1610     iret = NF90_PUT_ATT(fid, varid, 'axis',  TRIM(axx) )
1611     IF (iret /= NF90_NOERR) THEN
1612        CALL ipslerr (3,'watchout_init', &
1613             &          'Could not add attribut to variable '//var//' for the file :', &
1614             &          TRIM(watchout_file),'(Solution ?)')
1615     ENDIF
1616     iret = NF90_PUT_ATT(fid, varid, 'units', TRIM(unit)) 
1617     IF (iret /= NF90_NOERR) THEN
1618        CALL ipslerr (3,'watchout_init', &
1619             &          'Could not add attribut to variable '//var//' for the file :', &
1620             &          TRIM(watchout_file),'(Solution ?)')
1621     ENDIF
1622     iret = NF90_PUT_ATT(fid, varid, 'long_name', TRIM(titre))
1623     IF (iret /= NF90_NOERR) THEN
1624        CALL ipslerr (3,'watchout_init', &
1625             &          'Could not add attribut to variable '//var//' for the file :', &
1626             &          TRIM(watchout_file),'(Solution ?)')
1627     ENDIF
1628     iret = NF90_PUT_ATT(fid, varid, 'associate', TRIM(assoc))
1629     IF (iret /= NF90_NOERR) THEN
1630        CALL ipslerr (3,'watchout_init', &
1631             &          'Could not add attribut to variable '//var//' for the file :', &
1632             &          TRIM(watchout_file),'(Solution ?)')
1633     ENDIF
1634     iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
1635     IF (iret /= NF90_NOERR) THEN
1636        CALL ipslerr (3,'watchout_init', &
1637             &          'Could not add attribut to variable '//var//' for the file :', &
1638             &          TRIM(watchout_file),'(Solution ?)')
1639     ENDIF
1640     resolyid=varid
1641     !
1642     !
1643     !  Global attributes
1644     !
1645     CALL DATE_AND_TIME(today, att)
1646     stamp = "Forcing generated by intersurf in a previous run "//today(1:LEN_TRIM(today))//" at "//att(1:LEN_TRIM(att))
1647     iret = NF90_PUT_ATT(fid, NF90_GLOBAL, 'Conventions', "GDT 1.2")
1648     IF (iret /= NF90_NOERR) THEN
1649        CALL ipslerr (3,'watchout_init', &
1650             &          'Could not add global attribut to the file : ', &
1651             &          TRIM(watchout_file),'(Solution ?)')
1652     ENDIF
1653     iret = NF90_PUT_ATT(fid, NF90_GLOBAL, 'file_name', TRIM(watchout_file))
1654     IF (iret /= NF90_NOERR) THEN
1655        CALL ipslerr (3,'watchout_init', &
1656             &          'Could not add global attribut to the file : ', &
1657             &          TRIM(watchout_file),'(Solution ?)')
1658     ENDIF
1659     iret = NF90_PUT_ATT(fid, NF90_GLOBAL, 'production', TRIM(stamp))
1660     IF (iret /= NF90_NOERR) THEN
1661        CALL ipslerr (3,'watchout_init', &
1662             &          'Could not add global attribut to the file : ', &
1663             &          TRIM(watchout_file),'(Solution ?)')
1664     ENDIF
1665     !
1666     iret = NF90_ENDDEF(fid)
1667     IF (iret /= NF90_NOERR) THEN
1668        CALL ipslerr (3,'watchout_init', &
1669             &          'Could not end definitions in the file : ', &
1670             &          TRIM(watchout_file),'(Solution ?)')
1671     ENDIF
1672     !
1673     !    Write coordinates
1674     !
1675     iret = NF90_PUT_VAR(fid, nlonid, lon)
1676     IF (iret /= NF90_NOERR) THEN
1677        CALL ipslerr (3,'watchout_init', &
1678             &          'Could not put variable nav_lon  in the file : ', &
1679             &          TRIM(watchout_file),'(Solution ?)')
1680     ENDIF
1681     !
1682     iret = NF90_PUT_VAR(fid, nlatid, lat)
1683     IF (iret /= NF90_NOERR) THEN
1684        CALL ipslerr (3,'watchout_init', &
1685             &          'Could not put variable nav_lat  in the file : ', &
1686             &          TRIM(watchout_file),'(Solution ?)')
1687     ENDIF
1688     !
1689     iret = NF90_PUT_VAR(fid, nlevid, lev0)
1690     IF (iret /= NF90_NOERR) THEN
1691        CALL ipslerr (3,'watchout_init', &
1692             &          'Could not put variable level  in the file : ', &
1693             &          TRIM(watchout_file),'(Solution ?)')
1694     ENDIF
1695     !
1696     iret = NF90_PUT_VAR(fid, nlandid, kindex)
1697     IF (iret /= NF90_NOERR) THEN
1698        CALL ipslerr (3,'watchout_init', &
1699             &          'Could not put variable land  in the file : ', &
1700             &          TRIM(watchout_file),'(Solution ?)')
1701     ENDIF
1702     !
1703     IF ( .NOT. ALLOCATED(tmpdata)) THEN
1704        ALLOCATE(tmpdata(iim,jjm))
1705     ENDIF
1706     !
1707     tmpdata(:,:) = undef_sechiba
1708     DO ig=1,igmax
1709
1710        j = ((kindex(ig)-1)/iim) + 1
1711        i = (kindex(ig) - (j-1)*iim)
1712
1713        tmpdata(i,j) = contfrac_g(ig)
1714
1715     ENDDO
1716     iret = NF90_PUT_VAR(fid, contid, tmpdata)
1717     IF (iret /= NF90_NOERR) THEN
1718        CALL ipslerr (3,'watchout_init', &
1719             &          'Could not put variable contfrac  in the file : ', &
1720             &          TRIM(watchout_file),'(Solution ?)')
1721     ENDIF
1722     !   
1723     DO direction=1,8
1724        tmpdata(:,:) = undef_sechiba
1725        DO ig=1,igmax
1726
1727           j = ((kindex(ig)-1)/iim) + 1
1728           i = (kindex(ig) - (j-1)*iim)
1729
1730           tmpdata(i,j) = REAL( neighbours_g(ig,direction) )
1731
1732        ENDDO
1733        iret = NF90_PUT_VAR(fid, neighid(direction), tmpdata)
1734        IF (iret /= NF90_NOERR) THEN
1735           CALL ipslerr (3,'watchout_init', &
1736                &             'Could not put variable neighbours  in the file : ', &
1737                &             TRIM(watchout_file),'(Solution ?)')
1738        ENDIF
1739     ENDDO
1740     !
1741     tmpdata(:,:) = undef_sechiba
1742     DO ig=1,igmax
1743
1744        j = ((kindex(ig)-1)/iim) + 1
1745        i = (kindex(ig) - (j-1)*iim)
1746
1747        tmpdata(i,j) = resolution_g(ig,1)
1748
1749     ENDDO
1750     iret = NF90_PUT_VAR(fid, resolxid, tmpdata)
1751     IF (iret /= NF90_NOERR) THEN
1752        CALL ipslerr (3,'watchout_init', &
1753             &          'Could not put variable resolutionx  in the file : ', &
1754             &          TRIM(watchout_file),'(Solution ?)')
1755     ENDIF
1756     !
1757     tmpdata(:,:) = undef_sechiba
1758     DO ig=1,igmax
1759
1760        j = ((kindex(ig)-1)/iim) + 1
1761        i = (kindex(ig) - (j-1)*iim)
1762
1763        tmpdata(i,j) = resolution_g(ig,2)
1764
1765     ENDDO
1766     iret = NF90_PUT_VAR(fid, resolyid, tmpdata)
1767     IF (iret /= NF90_NOERR) THEN
1768        CALL ipslerr (3,'watchout_init', &
1769             &          'Could not put variable resolutiony  in the file : ', &
1770             &          TRIM(watchout_file),'(Solution ?)')
1771     ENDIF
1772     !
1773     DEALLOCATE(tmpdata)
1774     !
1775     watchfid = fid
1776     !
1777  ENDIF
1778  !
1779  ALLOCATE(sum_zlev(kjpindex))
1780  ALLOCATE(sum_u(kjpindex), sum_v(kjpindex))
1781  ALLOCATE(sum_qair(kjpindex))
1782  ALLOCATE(sum_temp_air(kjpindex))
1783  ALLOCATE(sum_epot_air(kjpindex))
1784  ALLOCATE(sum_ccanopy(kjpindex))
1785  ALLOCATE(sum_cdrag(kjpindex))
1786  ALLOCATE(sum_petAcoef(kjpindex), sum_peqAcoef(kjpindex), sum_petBcoef(kjpindex), sum_peqBcoef(kjpindex))
1787  ALLOCATE(sum_rain(kjpindex), sum_snow(kjpindex))
1788  ALLOCATE(sum_lwdown(kjpindex))
1789  ALLOCATE(sum_swnet(kjpindex))
1790  ALLOCATE(sum_swdown(kjpindex))
1791  ALLOCATE(sum_pb(kjpindex))
1792!!$  ALLOCATE(mean_sinang(iim,jjm))
1793!!$  ALLOCATE(sinang(iim,jjm))
1794!!$  ALLOCATE(isinang(iim,jjm))
1795
1796  sum_zlev(:) = zero
1797  sum_u(:) = zero
1798  sum_v(:) = zero
1799  sum_qair(:) = zero
1800  sum_temp_air(:) = zero
1801  sum_epot_air(:) = zero
1802  sum_ccanopy(:) = zero
1803  sum_cdrag(:) = zero
1804  sum_petAcoef(:) = zero
1805  sum_peqAcoef(:) = zero
1806  sum_petBcoef(:) = zero
1807  sum_peqBcoef(:) = zero
1808  sum_rain(:) = zero
1809  sum_snow(:) = zero
1810  sum_lwdown(:) = zero
1811  sum_swnet(:) = zero
1812  sum_swdown(:) = zero
1813  sum_pb(:) = zero
1814
1815!!$  mean_sinang(:,:) = zero
1816!!$  sinang(:,:) = zero
1817!!$  isinang(:,:) = dt_split_watch
1818
1819END SUBROUTINE watchout_init
1820  !
1821!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1822  !
1823  SUBROUTINE watchout_write_p(igmax, itau, dt, levels, &
1824       &                        soldown, rain, snow, lwdown, psurf, temp, eair, qair, u, v, &
1825       &                        solnet, petAcoef, peqAcoef, petBcoef, peqBcoef, cdrag, ccanopy )
1826    !
1827    !
1828    IMPLICIT NONE
1829    !
1830    ! INPUT
1831    !
1832    INTEGER(i_std), INTENT(in) :: igmax, itau
1833    REAL(r_std), INTENT(inout) :: levels(igmax)
1834    REAL(r_std), DIMENSION(igmax), INTENT(inout) :: soldown, rain, snow, lwdown, psurf, &
1835         &                                      solnet, petAcoef, peqAcoef, petBcoef, peqBcoef, &
1836         &                                      cdrag, ccanopy
1837    REAL(r_std), INTENT(inout) :: temp(igmax), eair(igmax), qair(igmax), u(igmax), v(igmax)
1838    REAL(r_std), INTENT(in) :: dt
1839    !
1840    ! LOCAL
1841    !
1842    REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:) :: levels_g
1843    REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:) :: soldown_g, rain_g, snow_g, lwdown_g, psurf_g, &
1844         &                             solnet_g, petAcoef_g, peqAcoef_g, petBcoef_g, peqBcoef_g, cdrag_g, &
1845         &                             temp_g, eair_g, qair_g, u_g, v_g, ccanopy_g
1846    !
1847    LOGICAL, SAVE                          :: is_first_time=.TRUE.
1848    INTEGER(i_std)                         :: ier
1849
1850    IF (is_first_time .AND. is_root_prc) THEN
1851       ALLOCATE(levels_g(nbp_glo),stat=ier)
1852       IF (ier .NE. 0) THEN
1853          WRITE (numout,*) ' error in levels_g allocation. We stop. We need iim words = ',nbp_glo
1854          STOP 'watchout_write_p'
1855       ENDIF
1856
1857       ALLOCATE(soldown_g(nbp_glo),stat=ier)
1858       IF (ier .NE. 0) THEN
1859          WRITE (numout,*) ' error in soldown_g allocation. We stop. We need iim words = ',nbp_glo
1860          STOP 'watchout_write_p'
1861       ENDIF
1862
1863       ALLOCATE(rain_g(nbp_glo),stat=ier)
1864       IF (ier .NE. 0) THEN
1865          WRITE (numout,*) ' error in rain_g allocation. We stop. We need iim words = ',nbp_glo
1866          STOP 'watchout_write_p'
1867       ENDIF
1868
1869       ALLOCATE(snow_g(nbp_glo),stat=ier)
1870       IF (ier .NE. 0) THEN
1871          WRITE (numout,*) ' error in snow_g allocation. We stop. We need iim words = ',nbp_glo
1872          STOP 'watchout_write_p'
1873       ENDIF
1874
1875       ALLOCATE(lwdown_g(nbp_glo),stat=ier)
1876       IF (ier .NE. 0) THEN
1877          WRITE (numout,*) ' error in lwdown_g allocation. We stop. We need iim words = ',nbp_glo
1878          STOP 'watchout_write_p'
1879       ENDIF
1880
1881       ALLOCATE(psurf_g(nbp_glo),stat=ier)
1882       IF (ier .NE. 0) THEN
1883          WRITE (numout,*) ' error in psurf_g allocation. We stop. We need iim words = ',nbp_glo
1884          STOP 'watchout_write_p'
1885       ENDIF
1886
1887       ALLOCATE(solnet_g(nbp_glo),stat=ier)
1888       IF (ier .NE. 0) THEN
1889          WRITE (numout,*) ' error in solnet_g allocation. We stop. We need iim words = ',nbp_glo
1890          STOP 'watchout_write_p'
1891       ENDIF
1892
1893       ALLOCATE(petAcoef_g(nbp_glo),stat=ier)
1894       IF (ier .NE. 0) THEN
1895          WRITE (numout,*) ' error in petAcoef_g allocation. We stop. We need iim words = ',nbp_glo
1896          STOP 'watchout_write_p'
1897       ENDIF
1898
1899       ALLOCATE(peqAcoef_g(nbp_glo),stat=ier)
1900       IF (ier .NE. 0) THEN
1901          WRITE (numout,*) ' error in peqAcoef_g allocation. We stop. We need iim words = ',nbp_glo
1902          STOP 'watchout_write_p'
1903       ENDIF
1904
1905       ALLOCATE(petBcoef_g(nbp_glo),stat=ier)
1906       IF (ier .NE. 0) THEN
1907          WRITE (numout,*) ' error in petBcoef_g allocation. We stop. We need iim words = ',nbp_glo
1908          STOP 'watchout_write_p'
1909       ENDIF
1910
1911       ALLOCATE(peqBcoef_g(nbp_glo),stat=ier)
1912       IF (ier .NE. 0) THEN
1913          WRITE (numout,*) ' error in peqBcoef_g allocation. We stop. We need iim words = ',nbp_glo
1914          STOP 'watchout_write_p'
1915       ENDIF
1916
1917       ALLOCATE(cdrag_g(nbp_glo),stat=ier)
1918       IF (ier .NE. 0) THEN
1919          WRITE (numout,*) ' error in cdrag_g allocation. We stop. We need iim words = ',nbp_glo
1920          STOP 'watchout_write_p'
1921       ENDIF
1922
1923       ALLOCATE(temp_g(nbp_glo),stat=ier)
1924       IF (ier .NE. 0) THEN
1925          WRITE (numout,*) ' error in temp_g allocation. We stop. We need iim words = ',nbp_glo
1926          STOP 'watchout_write_p'
1927       ENDIF
1928
1929       ALLOCATE(eair_g(nbp_glo),stat=ier)
1930       IF (ier .NE. 0) THEN
1931          WRITE (numout,*) ' error in eair_g allocation. We stop. We need iim words = ',nbp_glo
1932          STOP 'watchout_write_p'
1933       ENDIF
1934
1935       ALLOCATE(qair_g(nbp_glo),stat=ier)
1936       IF (ier .NE. 0) THEN
1937          WRITE (numout,*) ' error in qair_g allocation. We stop. We need iim words = ',nbp_glo
1938          STOP 'watchout_write_p'
1939       ENDIF
1940
1941       ALLOCATE(u_g(nbp_glo),stat=ier)
1942       IF (ier .NE. 0) THEN
1943          WRITE (numout,*) ' error in u_g allocation. We stop. We need iim words = ',nbp_glo
1944          STOP 'watchout_write_p'
1945       ENDIF
1946
1947       ALLOCATE(v_g(nbp_glo),stat=ier)
1948       IF (ier .NE. 0) THEN
1949          WRITE (numout,*) ' error in v_g allocation. We stop. We need iim words = ',nbp_glo
1950          STOP 'watchout_write_p'
1951       ENDIF
1952
1953       ALLOCATE(ccanopy_g(nbp_glo),stat=ier)
1954       IF (ier .NE. 0) THEN
1955          WRITE (numout,*) ' error in ccanopy_g allocation. We stop. We need iim words = ',nbp_glo
1956          STOP 'watchout_write_p'
1957       ENDIF
1958    ENDIF
1959    is_first_time=.FALSE.
1960
1961    CALL gather(levels,levels_g)
1962    CALL gather(soldown,soldown_g)
1963    CALL gather(rain,rain_g)
1964    CALL gather(snow,snow_g)
1965    CALL gather(lwdown,lwdown_g)
1966    CALL gather(psurf,psurf_g)
1967    CALL gather(solnet,solnet_g)
1968    CALL gather(petAcoef,petAcoef_g)
1969    CALL gather(peqAcoef,peqAcoef_g)
1970    CALL gather(petBcoef,petBcoef_g)
1971    CALL gather(peqBcoef,peqBcoef_g)
1972    CALL gather(cdrag,cdrag_g)
1973    CALL gather(temp,temp_g)
1974    CALL gather(eair,eair_g)
1975    CALL gather(qair,qair_g)
1976    CALL gather(u,u_g)
1977    CALL gather(v,v_g)
1978    CALL gather(ccanopy,ccanopy_g)
1979
1980    IF (is_root_prc) THEN
1981      CALL watchout_write(nbp_glo, itau, dt, levels_g, &
1982       &                      soldown_g, rain_g, snow_g, lwdown_g, psurf_g, temp_g, eair_g, qair_g, u_g, v_g, &
1983       &                      solnet_g, petAcoef_g, peqAcoef_g, petBcoef_g, peqBcoef_g, cdrag_g, ccanopy_g )
1984    ENDIF
1985
1986    levels(:) = zero
1987    soldown(:) = zero
1988    rain(:) = zero
1989    snow(:) = zero
1990    lwdown(:) = zero
1991    psurf(:) = zero
1992    solnet(:) = zero
1993    petAcoef(:) = zero
1994    peqAcoef(:) = zero
1995    petBcoef(:) = zero
1996    peqBcoef(:) = zero
1997    cdrag(:) = zero
1998    temp(:) = zero
1999    eair(:) = zero
2000    qair(:) = zero
2001    u(:) = zero
2002    v(:) = zero
2003    ccanopy(:) = zero
2004
2005!!$    mean_sinang(:,:) = zero
2006!!$    isinang(:,:) = dt_split_watch
2007
2008  END SUBROUTINE watchout_write_p
2009
2010  SUBROUTINE watchout_write(igmax, itau, dt, levels, &
2011       &                        soldown, rain, snow, lwdown, psurf, temp, eair, qair, u, v, &
2012       &                        solnet, petAcoef, peqAcoef, petBcoef, peqBcoef, cdrag, ccanopy )
2013    !
2014    !
2015    IMPLICIT NONE
2016    !
2017    ! This subroutine will write to the file the current fields which force the
2018    ! land-surface scheme. It will be in exactly the same format as the other forcing
2019    ! files, i.e. ALMA convention !
2020    !
2021    !
2022    ! INPUT
2023    !
2024    INTEGER(i_std) :: igmax, itau
2025    REAL(r_std) :: levels(igmax)
2026    REAL(r_std), DIMENSION(igmax), INTENT(in) :: soldown, rain, snow, lwdown, psurf, &
2027         &                                      solnet, petAcoef, peqAcoef, petBcoef, peqBcoef, &
2028         &                                      cdrag, ccanopy
2029    REAL(r_std) :: temp(igmax), eair(igmax), qair(igmax), u(igmax), v(igmax)
2030    REAL(r_std) :: dt
2031    !
2032    ! LOCAL
2033    !
2034    INTEGER(i_std) :: iret
2035    INTEGER(i_std) :: corner(3), edges(3)
2036    REAL(r_std) :: timestp
2037    LOGICAL    :: check=.FALSE.
2038    REAL(r_std),ALLOCATABLE :: tmpdata(:)
2039    INTEGER(i_std) :: corner_tstp
2040    !
2041    ! For dt_watch non equal to dt :
2042    !
2043    corner_tstp = NINT((itau - watchoffset)/dt_split_watch)
2044    !
2045    corner(1) = corner_tstp
2046    edges(1) = 1
2047    IF ( check ) &
2048         WRITE(numout,*) 'watchout_write corners, edges : ', corner(1), edges(1)
2049    !
2050    timestp = itau/dt_split_watch
2051!!MM : Time axis by month :
2052!$    timestp = (itau - watchoffset)/dt_split_watch
2053    IF ( check ) &
2054         WRITE(numout,*) "watchout_write : timestp = ",timestp
2055    iret = NF90_PUT_VAR(watchfid, timestp_id, (/ timestp /), &
2056         &              start=(/ corner(1) /), count=(/ edges(1) /))
2057    IF (iret /= NF90_NOERR) THEN
2058       CALL ipslerr (3,'watchout_write', &
2059 &          'Could not put variable timestp  in the file : ', &
2060 &          TRIM(watchout_file),'(Solution ?)')
2061    ENDIF
2062    !
2063    timestp=timestp*dt_watch
2064    IF ( check ) &
2065         WRITE(numout,*) "watchout_write : time = ",timestp
2066    iret = NF90_PUT_VAR(watchfid, time_id, (/ timestp /), &
2067         &              start=(/ corner(1) /), count=(/ edges(1) /))
2068    IF (iret /= NF90_NOERR) THEN
2069       CALL ipslerr (3,'watchout_write', &
2070 &          'Could not put variable time  in the file : ', &
2071 &          TRIM(watchout_file),'(Solution ?)')
2072    ENDIF
2073    !
2074    corner(1) = 1
2075    edges(1) = igmax
2076    corner(2) = corner_tstp
2077    edges(2) = 1
2078    !
2079    IF ( .NOT. ALLOCATED(tmpdata)) THEN
2080       ALLOCATE(tmpdata(igmax))
2081    ENDIF
2082    !
2083    ! 2D
2084    IF ( check ) THEN
2085       WRITE(numout,*) '--',itau, ' SOLDOWN : ', MINVAL(soldown), MAXVAL(soldown)
2086    ENDIF
2087    iret = NF90_PUT_VAR(watchfid, soldownid, soldown, start=corner(1:2), count=edges(1:2))
2088    IF (iret /= NF90_NOERR) THEN
2089       CALL ipslerr (3,'watchout_write', &
2090 &          'Could not put variable SWdown  in the file : ', &
2091 &          TRIM(watchout_file),'(Solution ?)')
2092    ENDIF
2093    !
2094    iret = NF90_PUT_VAR(watchfid, solnetid, solnet, start=corner(1:2), count=edges(1:2))
2095    IF (iret /= NF90_NOERR) THEN
2096       CALL ipslerr (3,'watchout_write', &
2097 &          'Could not put variable SWnet  in the file : ', &
2098 &          TRIM(watchout_file),'(Solution ?)')
2099    ENDIF
2100    !
2101    ! Bring back to kg/m^2/s
2102    !
2103    tmpdata = rain/dt
2104    IF ( check ) THEN
2105       WRITE(numout,*) '--',itau, ' RAIN : ', MINVAL(tmpdata), MAXVAL(tmpdata)
2106    ENDIF
2107    iret = NF90_PUT_VAR(watchfid, rainfid, tmpdata, start=corner(1:2), count=edges(1:2))
2108    IF (iret /= NF90_NOERR) THEN
2109       CALL ipslerr (3,'watchout_write', &
2110 &          'Could not put variable Rainf  in the file : ', &
2111 &          TRIM(watchout_file),'(Solution ?)')
2112    ENDIF
2113    tmpdata = snow/dt
2114    iret = NF90_PUT_VAR(watchfid, snowfid, tmpdata, start=corner(1:2), count=edges(1:2))
2115    IF (iret /= NF90_NOERR) THEN
2116       CALL ipslerr (3,'watchout_write', &
2117 &          'Could not put variable Snowf  in the file : ', &
2118 &          TRIM(watchout_file),'(Solution ?)')
2119    ENDIF
2120    !
2121    iret = NF90_PUT_VAR(watchfid, lwradid, lwdown, start=corner(1:2), count=edges(1:2)) 
2122    IF (iret /= NF90_NOERR) THEN
2123       CALL ipslerr (3,'watchout_write', &
2124 &          'Could not put variable LWdown  in the file : ', &
2125 &          TRIM(watchout_file),'(Solution ?)')
2126    ENDIF
2127    !
2128    !  Bring back to Pa
2129    !
2130    tmpdata = psurf*100.
2131    iret = NF90_PUT_VAR(watchfid, psolid, tmpdata, start=corner(1:2), count=edges(1:2))
2132    IF (iret /= NF90_NOERR) THEN
2133       CALL ipslerr (3,'watchout_write', &
2134 &          'Could not put variable PSurf  in the file : ', &
2135 &          TRIM(watchout_file),'(Solution ?)')
2136    ENDIF
2137    !
2138    ! 3D
2139    corner(2) = 1
2140    edges(2) = 1
2141    corner(3) = corner_tstp
2142    edges(3) = 1
2143    !
2144    iret = NF90_PUT_VAR(watchfid, zlevid, levels, start=corner(1:3), count=edges(1:3))
2145    IF (iret /= NF90_NOERR) THEN
2146       CALL ipslerr (3,'watchout_write', &
2147 &          'Could not put variable levels  in the file : ', &
2148 &          TRIM(watchout_file),'(Solution ?)')
2149    ENDIF
2150    !
2151    iret = NF90_PUT_VAR(watchfid, tairid, temp, start=corner(1:3), count=edges(1:3))
2152    IF (iret /= NF90_NOERR) THEN
2153       CALL ipslerr (3,'watchout_write', &
2154 &          'Could not put variable Tair  in the file : ', &
2155 &          TRIM(watchout_file),'(Solution ?)')
2156    ENDIF
2157
2158    iret = NF90_PUT_VAR(watchfid, eairid, eair, start=corner(1:3), count=edges(1:3))
2159    IF (iret /= NF90_NOERR) THEN
2160       CALL ipslerr (3,'watchout_write', &
2161 &          'Could not put variable Eair  in the file : ', &
2162 &          TRIM(watchout_file),'(Solution ?)')
2163    ENDIF
2164
2165    iret = NF90_PUT_VAR(watchfid, qairid, qair, start=corner(1:3), count=edges(1:3))
2166    IF (iret /= NF90_NOERR) THEN
2167       CALL ipslerr (3,'watchout_write', &
2168 &          'Could not put variable Qair  in the file : ', &
2169 &          TRIM(watchout_file),'(Solution ?)')
2170    ENDIF
2171
2172    iret = NF90_PUT_VAR(watchfid, uid, u, start=corner(1:3), count=edges(1:3))
2173    IF (iret /= NF90_NOERR) THEN
2174       CALL ipslerr (3,'watchout_write', &
2175 &          'Could not put variable Wind_N  in the file : ', &
2176 &          TRIM(watchout_file),'(Solution ?)')
2177    ENDIF
2178
2179    iret = NF90_PUT_VAR(watchfid, vid, v, start=corner(1:3), count=edges(1:3))
2180    IF (iret /= NF90_NOERR) THEN
2181       CALL ipslerr (3,'watchout_write', &
2182 &          'Could not put variable Wind_E  in the file : ', &
2183 &          TRIM(watchout_file),'(Solution ?)')
2184    ENDIF
2185    !
2186    iret = NF90_PUT_VAR(watchfid, petAcoefid, petAcoef, start=corner(1:3), count=edges(1:3))
2187    IF (iret /= NF90_NOERR) THEN
2188       CALL ipslerr (3,'watchout_write', &
2189 &          'Could not put variable petAcoef  in the file : ', &
2190 &          TRIM(watchout_file),'(Solution ?)')
2191    ENDIF
2192
2193    iret = NF90_PUT_VAR(watchfid, peqAcoefid, peqAcoef, start=corner(1:3), count=edges(1:3))
2194    IF (iret /= NF90_NOERR) THEN
2195       CALL ipslerr (3,'watchout_write', &
2196 &          'Could not put variable peqAcoef  in the file : ', &
2197 &          TRIM(watchout_file),'(Solution ?)')
2198    ENDIF
2199
2200    iret = NF90_PUT_VAR(watchfid, petBcoefid, petBcoef, start=corner(1:3), count=edges(1:3))
2201    IF (iret /= NF90_NOERR) THEN
2202       CALL ipslerr (3,'watchout_write', &
2203 &          'Could not put variable petBcoef  in the file : ', &
2204 &          TRIM(watchout_file),'(Solution ?)')
2205    ENDIF
2206
2207    iret = NF90_PUT_VAR(watchfid, peqBcoefid, peqBcoef, start=corner(1:3), count=edges(1:3))
2208    IF (iret /= NF90_NOERR) THEN
2209       CALL ipslerr (3,'watchout_write', &
2210 &          'Could not put variable peqBcoef  in the file : ', &
2211 &          TRIM(watchout_file),'(Solution ?)')
2212    ENDIF
2213
2214    iret = NF90_PUT_VAR(watchfid, cdragid, cdrag, start=corner(1:3), count=edges(1:3))
2215    IF (iret /= NF90_NOERR) THEN
2216       CALL ipslerr (3,'watchout_write', &
2217 &          'Could not put variable cdrag  in the file : ', &
2218 &          TRIM(watchout_file),'(Solution ?)')
2219    ENDIF
2220
2221    iret = NF90_PUT_VAR(watchfid, ccanopyid, ccanopy, start=corner(1:3), count=edges(1:3))
2222    IF (iret /= NF90_NOERR) THEN
2223       CALL ipslerr (3,'watchout_write', &
2224 &          'Could not put variable ccanopy  in the file : ', &
2225 &          TRIM(watchout_file),'(Solution ?)')
2226    ENDIF
2227
2228    DEALLOCATE(tmpdata)
2229    !
2230  END SUBROUTINE watchout_write
2231  !
2232  !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2233  !
2234  SUBROUTINE watchout_close()
2235    !
2236    !  Close the watch files
2237    !
2238    IMPLICIT NONE
2239    !
2240    ! LOCAL
2241    !
2242    INTEGER(i_std) :: iret
2243    LOGICAL       :: check = .FALSE.
2244    !
2245    !
2246    IF ( check )  THEN
2247       WRITE(numout,*) 'watchout_close : closing file : ', watchfid
2248    ENDIF
2249    iret = NF90_CLOSE(watchfid)
2250    IF (iret /= NF90_NOERR) THEN
2251       CALL ipslerr (3,'watchout_close','Could not close the file : ', &
2252 &          TRIM(watchout_file),'(Solution ?)')
2253    ENDIF
2254    !
2255  END SUBROUTINE watchout_close
2256
2257END MODULE watchout
Note: See TracBrowser for help on using the repository browser.