source: branches/ORCHIDEE_EXT/ORCHIDEE/src_sechiba/watchout.f90 @ 116

Last change on this file since 116 was 64, checked in by didier.solyga, 13 years ago

Import first version of ORCHIDEE_EXT

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