source: branches/publications/ORCHIDEE_CAN_r2290/src_sechiba/watchout.f90 @ 7475

Last change on this file since 7475 was 1395, checked in by matthew.mcgrath, 11 years ago

Merging changings from trunk up to revision 1392

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