source: branches/publications/ORCHIDEE_GLUC_r6545/src_stomate/stomate_wet_ch4.f90 @ 6737

Last change on this file since 6737 was 4719, checked in by albert.jornet, 7 years ago

Merge: from revisions [4491:4695/trunk/ORCHIDEE]

Merge done in [4671:4718/perso/albert.jornet/MICT_MERGE]

File size: 45.0 KB
Line 
1! =================================================================================================================================
2! MODULE       : stomate_wet_ch4
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF       CH4_calcul main module
10!!
11!!\n DESCRIPTION : None
12!!
13!! RECENT CHANGE(S) : None
14!!
15!! REFERENCE(S) : None
16!!
17!! SVN :
18!! $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/branches/ORCHIDEE-MICT/ORCHIDEE/src_stomate/stomate.f90 $
19!! $Date: 2017-07-28 17:48:13 +0200 (Fri, 28 Jul 2017) $
20!! $Revision: 4542 $
21!! \n
22!_ ================================================================================================================================
23MODULE stomate_wet_ch4
24
25  ! modules used:
26  USE stomate_wet_ch4_constantes_var
27  USE stomate_wet_ch4_pt_ter_0
28  USE stomate_wet_ch4_pt_ter_wet
29
30  IMPLICIT NONE
31
32  ! private & public routines
33
34  PRIVATE
35  PUBLIC stomate_wet_ch4_initialize, stomate_wet_ch4_main, stomate_wet_ch4_clear, stomate_wet_ch4_finalize, &
36         stomate_wet_ch4_histdef, stomate_wet_ch4_config_parameters
37
38  ! density flux of methane calculated for entire pixel (gCH4/dt/m**2)
39  ! pour wetland avc Water Table Depth (WTD) = 0
40  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:) :: ch4_flux_density_tot_0
41  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:) :: ch4_flux_density_dif_0
42  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:) :: ch4_flux_density_bub_0
43  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:) :: ch4_flux_density_pla_0
44  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)  :: uo_0 !concentration dim = (kjpindex,nvert)
45  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)  :: uold2_0 !concentration au pas de temps precedent
46!pour wetland avc WTD = -x1
47  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:) :: ch4_flux_density_tot_wet1
48  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:) :: ch4_flux_density_dif_wet1
49  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:) :: ch4_flux_density_bub_wet1
50  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:) :: ch4_flux_density_pla_wet1
51  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)  :: uo_wet1
52  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)  :: uold2_wet1
53!pour wetland avc WTD = -x2
54  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:) :: ch4_flux_density_tot_wet2
55  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:) :: ch4_flux_density_dif_wet2
56  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:) :: ch4_flux_density_bub_wet2
57  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:) :: ch4_flux_density_pla_wet2
58  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)  :: uo_wet2
59  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)  :: uold2_wet2
60!pour wetland avc WTD = -x3
61  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:) :: ch4_flux_density_tot_wet3
62  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:) :: ch4_flux_density_dif_wet3
63  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:) :: ch4_flux_density_bub_wet3
64  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:) :: ch4_flux_density_pla_wet3
65  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)  :: uo_wet3
66  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)  :: uold2_wet3
67!pour wetland avc WTD = -x4
68  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:) :: ch4_flux_density_tot_wet4
69  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:) :: ch4_flux_density_dif_wet4
70  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:) :: ch4_flux_density_bub_wet4
71  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:) :: ch4_flux_density_pla_wet4
72  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)  :: uo_wet4
73  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)  :: uold2_wet4
74
75
76CONTAINS
77
78!! ================================================================================================================================
79!! SUBROUTINE   : stomate_wet_ch4_config_parameters
80!!
81!>\BRIEF        stomate cste WETLAND
82!!
83!! DESCRIPTION  :
84!!               
85!! \n
86!_ ================================================================================================================================
87!!
88  SUBROUTINE stomate_wet_ch4_config_parameters
89       !Config Key   = nvert
90       !Config Desc  = nb of vertical layers for CH4 diffusion
91       !Config If    = CH4_CALCUL
92       !Config Def   = 171
93       !Config Help  =
94       !Config Units = [-]   
95       CALL getin_p('NVERT',nvert)
96
97       !Config Key   = ns
98       !Config Desc  = nb of vertical layers for CH4 diffusion
99       !Config If    = CH4_CALCUL
100       !Config Def   = 151
101       !Config Help  =
102       !Config Units = [-]   
103       CALL getin_p('NS',ns)
104
105       !Config Key   = nday
106       !Config Desc  = nb of vertical layers for CH4 diffusion
107       !Config If    = CH4_CALCUL
108       !Config Def   = 24
109       !Config Help  =
110       !Config Units = [-]   
111       CALL getin_p('NDAY',nday)
112
113       !Config Key   = h
114       !Config Desc  = nb of vertical layers for CH4 diffusion
115       !Config If    = CH4_CALCUL
116       !Config Def   = 0.1
117       !Config Help  =
118       !Config Units = [-]   
119       CALL getin_p('H',h)
120
121       !Config Key   = rk
122       !Config Desc  = nb of vertical layers for CH4 diffusion
123       !Config If    = CH4_CALCUL
124       !Config Def   = 1
125       !Config Help  =
126       !Config Units = [-]   
127       CALL getin_p('RK',rk)
128
129       !Config Key   = diffair
130       !Config Desc  = nb of vertical layers for CH4 diffusion
131       !Config If    = CH4_CALCUL
132       !Config Def   = 7.2
133       !Config Help  =
134       !Config Units = [-]   
135       CALL getin_p('DIFFAIR',diffair)
136
137       !Config Key   = pox
138       !Config Desc  = nb of vertical layers for CH4 diffusion
139       !Config If    = CH4_CALCUL
140       !Config Def   = 0.5
141       !Config Help  =
142       !Config Units = [-]   
143       CALL getin_p('POX',pox)
144
145       !Config Key   = dveg
146       !Config Desc  = nb of vertical layers for CH4 diffusion
147       !Config If    = CH4_CALCUL
148       !Config Def   = 0.001
149       !Config Help  =
150       !Config Units = [-]   
151       CALL getin_p('DVEG',dveg)
152
153       !Config Key   = rkm
154       !Config Desc  = nb of vertical layers for CH4 diffusion
155       !Config If    = CH4_CALCUL
156       !Config Def   = 5.0
157       !Config Help  =
158       !Config Units = [-]   
159       CALL getin_p('RKM',rkm)
160
161       !Config Key   = xvmax
162       !Config Desc  = nb of vertical layers for CH4 diffusion
163       !Config If    = CH4_CALCUL
164       !Config Def   = 20.0
165       !Config Help  =
166       !Config Units = [-]   
167       CALL getin_p('XVMAX',xvmax)
168
169       !Config Key   = oxq10
170       !Config Desc  = nb of vertical layers for CH4 diffusion
171       !Config If    = CH4_CALCUL
172       !Config Def   = 2.0
173       !Config Help  =
174       !Config Units = [-]   
175       CALL getin_p('OXQ10',oxq10)
176
177       !Config Key   = scmax
178       !Config Desc  = nb of vertical layers for CH4 diffusion
179       !Config If    = CH4_CALCUL
180       !Config Def   = 500.
181       !Config Help  =
182       !Config Units = [-]   
183       CALL getin_p('SCMAX',scmax)
184
185       !Config Key   = sr0pl
186       !Config Desc  = nb of vertical layers for CH4 diffusion
187       !Config If    = CH4_CALCUL
188       !Config Def   = 600.
189       !Config Help  =
190       !Config Units = [-]   
191       CALL getin_p('SR0PL',sr0pl)
192
193       !Config Key   = pwater_wet1
194       !Config Desc  = depth where saturation: definition for wetland 1 
195       !Config If    = CH4_CALCUL
196       !Config Def   = -3
197       !Config Help  =
198       !Config Units = [cm]   
199       CALL getin_p('PWATER_WET1',pwater_wet1)
200
201       !Config Key   = pwater_wet2
202       !Config Desc  = depth where saturation: definition for wetland 1 
203       !Config If    = CH4_CALCUL
204       !Config Def   = -9
205       !Config Help  =
206       !Config Units = [cm]   
207       CALL getin_p('PWATER_WET2',pwater_wet2)
208
209       !Config Key   = pwater_wet3
210       !Config Desc  = depth where saturation: definition for wetland 1 
211       !Config If    = CH4_CALCUL
212       !Config Def   = -15
213       !Config Help  =
214       !Config Units = [cm]   
215       CALL getin_p('PWATER_WET3',pwater_wet3)
216
217       !Config Key   = pwater_wet4
218       !Config Desc  = depth where saturation: definition for wetland 1 
219       !Config If    = CH4_CALCUL
220       !Config Def   = -21
221       !Config Help  =
222       !Config Units = [cm]   
223       CALL getin_p('PWATER_WET4',pwater_wet4)
224
225       !Config Key   = rpv
226       !Config Desc  = nb of vertical layers for CH4 diffusion
227       !Config If    = CH4_CALCUL
228       !Config Def   = 0.5
229       !Config Help  =
230       !Config Units = [-]   
231       CALL getin_p('RPV',rpv)
232
233       !Config Key   = iother
234       !Config Desc  = nb of vertical layers for CH4 diffusion
235       !Config If    = CH4_CALCUL
236       !Config Def   = -1.0
237       !Config Help  =
238       !Config Units = [-]   
239       CALL getin_p('IOTHER',iother)
240
241       !Config Key   = rq10
242       !Config Desc  = nb of vertical layers for CH4 diffusion
243       !Config If    = CH4_CALCUL
244       !Config Def   = 3.0
245       !Config Help  =
246       !Config Units = [-]   
247       CALL getin_p('RQ10',rq10)
248
249       !Config Key   = alpha_CH4
250       !Config Desc  = nb of vertical layers for CH4 diffusion
251       !Config If    = CH4_CALCUL
252       !Config Def   = /0.009,0.004,0.021/
253       !Config Help  =
254       !Config Units = [-]   
255       CALL getin_p('ALPHA_CH4',alpha_CH4)
256
257  END SUBROUTINE stomate_wet_ch4_config_parameters
258
259!! ================================================================================================================================
260!! SUBROUTINE   : stomate_wet_ch4_readrestart
261!!
262!>\BRIEF        Read restart variables
263!!
264!! DESCRIPTION  :
265!!               
266!! \n
267!_ ================================================================================================================================
268!!
269  SUBROUTINE stomate_wet_ch4_readrestart ( rest_id, itime )
270
271    ! 0.4 Local variables
272    CHARACTER(LEN=100)                   :: var_name !! Name of permafrost forcing file
273    INTEGER(i_std), INTENT(in)           :: rest_id
274    INTEGER(i_std), INTENT(in)           :: itime
275
276    INTEGER(i_std) ::  nivo
277!_ ================================================================================================================================
278
279    uo_0(:,:) = val_exp
280    var_name = 'uo_0'
281    CALL restget_p (rest_id, var_name, nbp_glo,   nvert, 1, itime, &
282         &              .TRUE.,uo_0 , 'gather', nbp_glo, index_g)
283    IF (ALL(uo_0(:,:) == val_exp)) THEN
284       DO nivo=1,nvert
285          IF (nivo .LE. ns) THEN
286            uo_0(:,nivo) = scmax
287         ELSE
288            uo_0(:,nivo) = CH4atmo_CONC
289         ENDIF
290      ENDDO
291   ENDIF
292
293   uold2_0(:,:) = val_exp
294   var_name = 'uold2_0'
295   CALL restget_p (rest_id, var_name, nbp_glo,   nvert, 1, itime, &
296        &              .TRUE.,uold2_0 , 'gather', nbp_glo, index_g)
297   IF (ALL(uold2_0(:,:) == val_exp)) THEN
298      DO nivo=1,nvert
299         IF (nivo .LE. ns) THEN
300            uold2_0(:,nivo) = scmax
301         ELSE
302            uold2_0(:,nivo) = CH4atmo_CONC
303         ENDIF
304      ENDDO
305   ENDIF
306   
307   uo_wet1(:,:) = val_exp
308   var_name = 'uo_wet1'
309   CALL restget_p (rest_id, var_name, nbp_glo,   nvert, 1, itime, &
310       &              .TRUE.,uo_wet1 , 'gather', nbp_glo, index_g)
311   IF (ALL(uo_wet1(:,:) == val_exp)) THEN
312      DO nivo=1,nvert
313         IF (nivo .LE. ns-10) THEN
314            uo_wet1(:,nivo) = scmax
315         ELSE
316            uo_wet1(:,nivo) = CH4atmo_CONC
317         ENDIF
318      ENDDO
319   ENDIF
320   
321   uold2_wet1(:,:) = val_exp
322   var_name = 'uold2_wet1'
323   CALL restget_p (rest_id, var_name, nbp_glo,   nvert, 1, itime, &
324        &              .TRUE.,uold2_wet1 , 'gather', nbp_glo, index_g)
325   IF (ALL(uold2_wet1(:,:) == val_exp)) THEN
326      DO nivo=1,nvert
327         IF (nivo .LE. ns-10) THEN
328            uold2_wet1(:,nivo) = scmax
329         ELSE
330            uold2_wet1(:,nivo) = CH4atmo_CONC
331         ENDIF
332      ENDDO
333   ENDIF
334 
335   uo_wet2(:,:) = val_exp
336   var_name = 'uo_wet2'
337   CALL restget_p (rest_id, var_name, nbp_glo,   nvert, 1, itime, &
338        &              .TRUE.,uo_wet2 , 'gather', nbp_glo, index_g)
339   IF (ALL(uo_wet2(:,:) == val_exp)) THEN
340      DO nivo=1,nvert
341         IF (nivo .LE. ns-10) THEN
342            uo_wet2(:,nivo) = scmax
343         ELSE
344            uo_wet2(:,nivo) = CH4atmo_CONC
345         ENDIF
346      ENDDO
347   ENDIF
348
349   uold2_wet2(:,:) = val_exp
350   var_name = 'uold2_wet2'
351   CALL restget_p (rest_id, var_name, nbp_glo,   nvert, 1, itime, &
352        &              .TRUE.,uold2_wet2 , 'gather', nbp_glo, index_g)
353   IF (ALL(uold2_wet2(:,:) == val_exp)) THEN
354      DO nivo=1,nvert
355         IF (nivo .LE. ns-10) THEN
356            uold2_wet2(:,nivo) = scmax
357         ELSE
358            uold2_wet2(:,nivo) = CH4atmo_CONC
359         ENDIF
360      ENDDO
361   ENDIF
362
363   uo_wet3(:,:) = val_exp
364   var_name = 'uo_wet3'
365   CALL restget_p (rest_id, var_name, nbp_glo,   nvert, 1, itime, &
366        &              .TRUE.,uo_wet3 , 'gather', nbp_glo, index_g)
367   IF (ALL(uo_wet3(:,:) == val_exp)) THEN
368      DO nivo=1,nvert
369         IF (nivo .LE. ns-10) THEN
370            uo_wet3(:,nivo) = scmax
371         ELSE
372            uo_wet3(:,nivo) = CH4atmo_CONC
373         ENDIF
374      ENDDO
375   ENDIF
376   
377   uold2_wet3(:,:) = val_exp
378   var_name = 'uold2_wet3'
379   CALL restget_p (rest_id, var_name, nbp_glo,   nvert, 1, itime, &
380        &              .TRUE.,uold2_wet3 , 'gather', nbp_glo, index_g)
381   IF (ALL(uold2_wet3(:,:) == val_exp)) THEN
382      DO nivo=1,nvert
383         IF (nivo .LE. ns-10) THEN
384            uold2_wet3(:,nivo) = scmax
385         ELSE
386            uold2_wet3(:,nivo) = CH4atmo_CONC
387         ENDIF
388      ENDDO
389   ENDIF
390
391   uo_wet4(:,:) = val_exp
392   var_name = 'uo_wet4'
393   CALL restget_p (rest_id, var_name, nbp_glo,   nvert, 1, itime, &
394        &              .TRUE.,uo_wet4 , 'gather', nbp_glo, index_g)
395   IF (ALL(uo_wet4(:,:) == val_exp)) THEN
396      DO nivo=1,nvert
397         IF (nivo .LE. ns-10) THEN
398            uo_wet4(:,nivo) = scmax
399         ELSE
400            uo_wet4(:,nivo) = CH4atmo_CONC
401         ENDIF
402      ENDDO
403   ENDIF
404
405   uold2_wet4(:,:) = val_exp
406   var_name = 'uold2_wet4'
407   CALL restget_p (rest_id, var_name, nbp_glo,   nvert, 1, itime, &
408        &              .TRUE.,uold2_wet4 , 'gather', nbp_glo, index_g)
409   IF (ALL(uold2_wet4(:,:) == val_exp)) THEN
410      DO nivo=1,nvert
411         IF (nivo .LE. ns-10) THEN
412            uold2_wet4(:,nivo) = scmax
413         ELSE
414            uold2_wet4(:,nivo) = CH4atmo_CONC
415         ENDIF
416      ENDDO
417   ENDIF
418  END SUBROUTINE stomate_wet_ch4_readrestart
419
420!! ================================================================================================================================
421!! SUBROUTINE   : stomate_wet_ch4_writerestart
422!!
423!>\BRIEF        Module restart write variables
424!!
425!! DESCRIPTION  :
426!!               
427!! \n
428!_ ================================================================================================================================
429!!
430  SUBROUTINE stomate_wet_ch4_writerestart ( rest_id, itime )
431
432    ! 0.1 Input variables
433    INTEGER(i_std), INTENT(in) :: rest_id
434    INTEGER(i_std), INTENT(in) :: itime
435
436    ! 0.4 Local variables
437    CHARACTER(LEN=100)                   :: var_name !! Name of permafrost forcing file
438
439!_ ================================================================================================================================
440    var_name = 'uo_0'
441    CALL restput_p (rest_id, var_name, nbp_glo, nvert, 1, itime, &
442         &              uo_0, 'scatter', nbp_glo, index_g)
443   
444    var_name = 'uold2_0'
445    CALL restput_p (rest_id, var_name, nbp_glo, nvert, 1, itime, &
446         &              uold2_0, 'scatter', nbp_glo, index_g)
447   
448    var_name = 'uo_wet1'
449    CALL restput_p (rest_id, var_name, nbp_glo, nvert, 1, itime, &
450         &              uo_wet1, 'scatter', nbp_glo, index_g)
451   
452    var_name = 'uold2_wet1'
453    CALL restput_p (rest_id, var_name, nbp_glo, nvert, 1, itime, &
454         &              uold2_wet1, 'scatter', nbp_glo, index_g)
455   
456    var_name = 'uo_wet2'
457    CALL restput_p (rest_id, var_name, nbp_glo, nvert, 1, itime, &
458         &              uo_wet2, 'scatter', nbp_glo, index_g)
459 
460    var_name = 'uold2_wet2'
461    CALL restput_p (rest_id, var_name, nbp_glo, nvert, 1, itime, &
462         &              uold2_wet2, 'scatter', nbp_glo, index_g)
463
464    var_name = 'uo_wet3'
465    CALL restput_p (rest_id, var_name, nbp_glo, nvert, 1, itime, &
466       &              uo_wet3, 'scatter', nbp_glo, index_g)
467   
468    var_name = 'uold2_wet3'
469    CALL restput_p (rest_id, var_name, nbp_glo, nvert, 1, itime, &
470         &              uold2_wet3, 'scatter', nbp_glo, index_g)
471   
472    var_name = 'uo_wet4'
473    CALL restput_p (rest_id, var_name, nbp_glo, nvert, 1, itime, &
474         &              uo_wet4, 'scatter', nbp_glo, index_g)
475   
476    var_name = 'uold2_wet4'
477    CALL restput_p (rest_id, var_name, nbp_glo, nvert, 1, itime, &
478         &              uold2_wet4, 'scatter', nbp_glo, index_g)
479
480  END SUBROUTINE stomate_wet_ch4_writerestart
481
482
483!! ================================================================================================================================
484!! SUBROUTINE   : stomate_wet_ch4_initialize
485!!
486!>\BRIEF        Module initialization
487!!
488!! DESCRIPTION  :
489!!               
490!! \n
491!_ ================================================================================================================================
492!!
493  SUBROUTINE stomate_wet_ch4_initialize ( kjpindex, rest_id, itime )
494    !
495    ! 0 declarations
496    !
497
498    ! 0.1 input
499    INTEGER(i_std), INTENT(in)                     :: kjpindex ! Domain size
500    INTEGER(i_std), INTENT(in)                     :: rest_id
501    INTEGER(i_std), INTENT(in)                     :: itime
502
503    ! 0.2 modified fields
504
505    ! 0.3 output
506
507    ! 0.4 local
508!_ ================================================================================================================================
509   !1.4.10 wetland CH4
510   !pss:+
511   !appel routines pour calcul des densites de flux de CH4
512
513       
514   !Config  Key  = CH4atm_CONC
515   !Config  Desc =
516   !Config If    = CH4_CALCUL
517   !Config  Def  = 0.0017
518   !Config  Help =
519   !               
520   !Config Units = [-]
521   CH4atmo_CONC=0.0017
522   CALL getin_p('CH4atmo_CONC', CH4atmo_CONC)
523
524   CH4_WTD1  = .TRUE.
525   !Config  Key  = CH4_WTD1
526   !Config  Desc =
527   !Config If    = CH4_CALCUL
528   !Config  Def  = True
529   !Config  Help =
530   !               
531   !Config Units = Y/n
532   CALL getin_p('CH4_WTD1', CH4_WTD1)
533   !Config  Key  = CH4_WTD2
534   !Config  Desc =
535   !Config If    = CH4_CALCUL
536   !Config  Def  = True
537   !Config  Help =
538   !               
539   !Config Units = Y/n
540   CH4_WTD2  = .TRUE.
541   CALL getin_p('CH4_WDT2', CH4_WTD2)
542   !Config  Key  = CH4_WTD3
543   !Config  Desc =
544   !Config If    = CH4_CALCUL
545   !Config  Def  = True
546   !Config  Help =
547   !               
548   !Config Units = Y/n
549   CH4_WTD3  = .TRUE.
550   CALL getin_p('CH4_WTD3', CH4_WTD3)
551   !Config  Key  = CH4_WTD4
552   !Config  Desc =
553   !Config If    = CH4_CALCUL
554   !Config  Def  = True
555   !Config  Help =
556   !               
557   !Config Units = Y/n
558   CH4_WTD4  = .TRUE.
559   CALL getin_p('CH4_WTD4', CH4_WTD4)
560
561   ! allocate
562   CALL stomate_wet_ch4_init (kjpindex)
563
564   ! read data from restart files (if any)
565   CALL stomate_wet_ch4_readrestart (rest_id, itime)
566
567  END SUBROUTINE stomate_wet_ch4_initialize
568
569!! ================================================================================================================================
570!! SUBROUTINE   : stomate_wet_ch4_init
571!!
572!>\BRIEF        Module variables allocation
573!!
574!! DESCRIPTION  :
575!!               
576!! \n
577!_ ================================================================================================================================
578!!
579  SUBROUTINE stomate_wet_ch4_init ( kjpindex )
580    !
581    ! 0 declarations
582    !
583
584    ! 0.1 input
585
586    ! Domain size
587    INTEGER(i_std), INTENT(in)                                 :: kjpindex
588    ! 0.2 modified fields
589
590    ! 0.3 output
591
592    ! 0.4 local
593    INTEGER(i_std)               :: ier
594!_ ================================================================================================================================
595
596    ALLOCATE(ch4_flux_density_tot_0(kjpindex),stat=ier)
597    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'ch4_flux_density_tot_0', '')
598    ch4_flux_density_tot_0 = zero
599
600    ALLOCATE(ch4_flux_density_dif_0(kjpindex),stat=ier)
601    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'ch4_flux_density_dif_0', '')
602    ch4_flux_density_dif_0 = zero
603
604    ALLOCATE(ch4_flux_density_bub_0(kjpindex),stat=ier)
605    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'ch4_flux_density_bub_0', '')
606    ch4_flux_density_bub_0 = zero
607
608    ALLOCATE(ch4_flux_density_pla_0(kjpindex),stat=ier)
609    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'ch4_flux_density_pla_0', '')
610    ch4_flux_density_pla_0 = zero
611
612   
613    ALLOCATE(ch4_flux_density_tot_wet1(kjpindex),stat=ier)
614    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'ch4_flux_density_tot_wet1', '')
615    ch4_flux_density_tot_wet1 = zero
616
617    ALLOCATE(ch4_flux_density_dif_wet1(kjpindex),stat=ier)
618    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'ch4_flux_density_dif_wet1', '')
619    ch4_flux_density_dif_wet1 = zero
620
621    ALLOCATE(ch4_flux_density_bub_wet1(kjpindex),stat=ier)
622    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'ch4_flux_density_bub_wet1', '')
623    ch4_flux_density_bub_wet1 = zero
624
625    ALLOCATE(ch4_flux_density_pla_wet1(kjpindex),stat=ier)
626    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'ch4_flux_density_pla_wet1', '')
627    ch4_flux_density_pla_wet1 = zero
628
629
630    ALLOCATE(ch4_flux_density_tot_wet2(kjpindex),stat=ier)
631    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'ch4_flux_density_tot_wet2', '')
632    ch4_flux_density_tot_wet2 = zero
633
634    ALLOCATE(ch4_flux_density_dif_wet2(kjpindex),stat=ier)
635    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'ch4_flux_density_dif_wet2', '')
636    ch4_flux_density_dif_wet2 = zero
637
638    ALLOCATE(ch4_flux_density_bub_wet2(kjpindex),stat=ier)
639    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'ch4_flux_density_bub_wet2', '')
640    ch4_flux_density_bub_wet2 = zero
641
642    ALLOCATE(ch4_flux_density_pla_wet2(kjpindex),stat=ier)
643    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'ch4_flux_density_pla_wet2', '')
644    ch4_flux_density_pla_wet2 = zero
645
646   
647    ALLOCATE(ch4_flux_density_tot_wet3(kjpindex),stat=ier)
648    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'ch4_flux_density_tot_wet3', '')
649    ch4_flux_density_tot_wet3 = zero
650
651    ALLOCATE(ch4_flux_density_dif_wet3(kjpindex),stat=ier)
652    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'ch4_flux_density_dif_wet3', '')
653    ch4_flux_density_dif_wet3 = zero
654
655    ALLOCATE(ch4_flux_density_bub_wet3(kjpindex),stat=ier)
656    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'ch4_flux_density_bub_wet3', '')
657    ch4_flux_density_bub_wet3 = zero
658
659    ALLOCATE(ch4_flux_density_pla_wet3(kjpindex),stat=ier)
660    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'ch4_flux_density_pla_wet3', '')
661    ch4_flux_density_pla_wet3 = zero
662
663   
664    ALLOCATE(ch4_flux_density_tot_wet4(kjpindex),stat=ier)
665    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'ch4_flux_density_tot_wet4', '')
666    ch4_flux_density_tot_wet4 = zero
667   
668    ALLOCATE(ch4_flux_density_dif_wet4(kjpindex),stat=ier)
669    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'ch4_flux_density_dif_wet4', '')
670    ch4_flux_density_dif_wet4 = zero
671   
672    ALLOCATE(ch4_flux_density_bub_wet4(kjpindex),stat=ier)
673    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'ch4_flux_density_bub_wet4', '')
674    ch4_flux_density_bub_wet4 = zero
675 
676    ALLOCATE(ch4_flux_density_pla_wet4(kjpindex),stat=ier)
677    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'ch4_flux_density_pla_wet4', '')
678    ch4_flux_density_pla_wet4 = zero
679 
680
681    ALLOCATE(uo_0(kjpindex,nvert),stat=ier)
682    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'uo_0', '')
683    uo_0 = zero
684
685    ALLOCATE(uold2_0(kjpindex,nvert),stat=ier)
686    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'uold2_0', '')
687    uold2_0 = zero
688
689    ALLOCATE(uo_wet1(kjpindex,nvert),stat=ier)
690    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'uo_wet1', '')
691    uo_wet1 = zero
692
693    ALLOCATE(uold2_wet1(kjpindex,nvert),stat=ier)
694    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'uold2_wet1', '')
695    uold2_wet1 = zero
696
697    ALLOCATE(uo_wet2(kjpindex,nvert),stat=ier)
698    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'uo_wet2', '')
699    uo_wet2 = zero
700
701    ALLOCATE(uold2_wet2(kjpindex,nvert),stat=ier)
702    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'uold2_wet2', '')
703    uold2_wet2 = zero
704
705    ALLOCATE(uo_wet3(kjpindex,nvert),stat=ier)
706    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'uo_wet3', '')
707    uo_wet3 = zero
708
709    ALLOCATE(uold2_wet3(kjpindex,nvert),stat=ier)
710    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'uold2_wet3', '')
711    uold2_wet3 = zero
712
713    ALLOCATE(uo_wet4(kjpindex,nvert),stat=ier)
714    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'uo_wet4', '')
715    uo_wet4 = zero
716
717    ALLOCATE(uold2_wet4(kjpindex,nvert),stat=ier)
718    IF (ier /= 0) CALL ipslerr_p(3, 'stomate_wet_ch4_initialize', 'There is an allocation variable error: ', 'uold2_wet4', '')
719    uold2_wet4 = zero
720
721  END SUBROUTINE stomate_wet_ch4_init
722
723!! ================================================================================================================================
724!! SUBROUTINE   : stomate_wet_ch4_main
725!!
726!>\BRIEF        ch4 main body
727!!
728!! DESCRIPTION  :
729!!               
730!! \n
731!_ ================================================================================================================================
732!!
733  SUBROUTINE stomate_wet_ch4_main ( kjpindex,       stempdiag,      tsurf_daily, tsurf_year,    &
734                                    veget_cov_max,  veget,          lai, carbon,                &
735                                    carbon_surf,    itime,          hist_id_stomate, hori_index) 
736    !
737    ! 0 declarations
738    !
739
740    ! 0.1 input
741
742    ! Domain size
743    INTEGER(i_std), INTENT(in)                                 :: kjpindex 
744    REAL(r_std),DIMENSION (:,:), INTENT (in)               :: stempdiag   ! kjpindex, nslm
745    ! temperature (K) at the surface
746    REAL(r_std), DIMENSION(:), INTENT(in)                  :: tsurf_daily ! kjpindex
747
748    ! temperature (K) at the surface
749    REAL(r_std), DIMENSION(:), INTENT(in)                  :: tsurf_year ! kjpindex
750
751    ! "maximal" coverage fraction of a PFT (LAI -> infinity) on nat/agri ground
752    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: veget_cov_max    ! kjpindex, nvm
753    REAL(r_std), DIMENSION(:,:), INTENT(in)               :: veget            ! kjpindex, nvm
754    REAL(r_std), DIMENSION(:,:),INTENT(in)  :: lai               !! Leaf area inex @tex $(m^2 m^{-2})$ @endtex
755    !! Carbon pool integrated to over surface soils: active, slow, or passive ( kjpindex, ncarb, nvm )
756    REAL(r_std), DIMENSION(:,:,:), INTENT(in)        :: carbon_surf 
757    !! Soil carbon pools per ground area: active, slow, or ( kjpindex, ncarb, nvm )
758    REAL(r_std), DIMENSION(:,:,:), INTENT(in)        :: carbon 
759    INTEGER(i_std), INTENT(in)                                      :: itime
760    INTEGER(i_std), INTENT(in)                                      :: hist_id_stomate
761    INTEGER(i_std), DIMENSION(:), INTENT(in)                        :: hori_index     !! Move to Horizontal indices
762
763    ! 0.2 modified fields
764
765    ! 0.3 output
766
767    ! 0.4 local
768
769!_ ================================================================================================================================
770
771    IF (.NOT. CH4_calcul) CALL ipslerr_p(3, 'stomate_wet_ch4_main', & 
772        'CH4 module needs to be enabled to run this subroutine', 'Set CH4_CALCUL=y', &
773        'in your run.def file')
774
775
776    !routine pour densite de flux d un wetland ou WTD = 0
777    CALL ch4_wet_flux_density_0 (kjpindex,stempdiag,tsurf_daily,tsurf_year,veget_cov_max,veget,&
778         & carbon,lai,uo_0,uold2_0, ch4_flux_density_tot_0, ch4_flux_density_dif_0,&
779         & ch4_flux_density_bub_0,ch4_flux_density_pla_0, CH4atmo_CONC) 
780
781
782    IF (CH4_WTD1) THEN
783       !routine calcule densite de flux d un wetland ou WTD = pwater_wet1 (cf.stomate_cste_wetlands.f90)
784       CALL ch4_wet_flux_density_wet (kjpindex,stempdiag,tsurf_daily,tsurf_year,veget_cov_max,veget,&
785            & carbon_surf,lai,uo_wet1,uold2_wet1,ch4_flux_density_tot_wet1, ch4_flux_density_dif_wet1, &
786            & ch4_flux_density_bub_wet1,ch4_flux_density_pla_wet1, CH4atmo_CONC, pwater_wet1) 
787    ENDIF
788         
789      IF (CH4_WTD2) THEN
790         !routine calcule densite de flux d un wetland ou WTD = pwater_wet2 (cf.stomate_cste_wetlands.f90)
791         CALL ch4_wet_flux_density_wet (kjpindex,stempdiag,tsurf_daily,tsurf_year,veget_cov_max,veget,&
792              & carbon_surf,lai,uo_wet2,uold2_wet2,ch4_flux_density_tot_wet2, ch4_flux_density_dif_wet2, &
793              & ch4_flux_density_bub_wet2,ch4_flux_density_pla_wet2, CH4atmo_CONC, pwater_wet2) 
794      ENDIF
795
796      IF (CH4_WTD3) THEN
797         !routine calcule densite de flux d un wetland ou WTD = pwater_wet3 (cf.stomate_cste_wetlands.f90)
798         CALL ch4_wet_flux_density_wet (kjpindex,stempdiag,tsurf_daily,tsurf_year,veget_cov_max,veget,&
799              & carbon_surf,lai,uo_wet3,uold2_wet3,ch4_flux_density_tot_wet3, ch4_flux_density_dif_wet3, &
800              & ch4_flux_density_bub_wet3,ch4_flux_density_pla_wet3, CH4atmo_CONC, pwater_wet3) 
801      ENDIF
802
803      IF (CH4_WTD4) THEN
804         !routine calcule densite de flux d un wetland ou WTD = pwater_wet4 (cf.stomate_cste_wetlands.f90)
805         CALL ch4_wet_flux_density_wet (kjpindex,stempdiag,tsurf_daily,tsurf_year,veget_cov_max,veget,&
806            & carbon_surf,lai,uo_wet4,uold2_wet4,ch4_flux_density_tot_wet4, ch4_flux_density_dif_wet4, &
807            & ch4_flux_density_bub_wet4,ch4_flux_density_pla_wet4, CH4atmo_CONC, pwater_wet4) 
808      ENDIF
809     
810!!!! Wetland CH4 methane
811!pss:+
812    CALL histwrite_p (hist_id_stomate, 'CH4_FLUX_TOT_0', itime, &
813                    ch4_flux_density_tot_0, kjpindex, hori_index)
814    CALL histwrite_p (hist_id_stomate, 'CH4_FLUX_DIF_0', itime, &
815                    ch4_flux_density_dif_0, kjpindex, hori_index)
816    CALL histwrite_p (hist_id_stomate, 'CH4_FLUX_BUB_0', itime, &
817                    ch4_flux_density_bub_0, kjpindex, hori_index)
818    CALL histwrite_p (hist_id_stomate, 'CH4_FLUX_PLA_0', itime, &
819                    ch4_flux_density_pla_0, kjpindex, hori_index)
820    CALL histwrite_p (hist_id_stomate, 'CH4_FLUX_TOT_wet1', itime, &
821                    ch4_flux_density_tot_wet1, kjpindex, hori_index)
822    CALL histwrite_p (hist_id_stomate, 'CH4_FLUX_DIF_wet1', itime, &
823                    ch4_flux_density_dif_wet1, kjpindex, hori_index)
824    CALL histwrite_p (hist_id_stomate, 'CH4_FLUX_BUB_wet1', itime, &
825                    ch4_flux_density_bub_wet1, kjpindex, hori_index)
826    CALL histwrite_p (hist_id_stomate, 'CH4_FLUX_PLA_wet1', itime, &
827                    ch4_flux_density_pla_wet1, kjpindex, hori_index)
828    CALL histwrite_p (hist_id_stomate, 'CH4_FLUX_TOT_wet2', itime, &
829                    ch4_flux_density_tot_wet2, kjpindex, hori_index)
830    CALL histwrite_p (hist_id_stomate, 'CH4_FLUX_DIF_wet2', itime, &
831                    ch4_flux_density_dif_wet2, kjpindex, hori_index)
832    CALL histwrite_p (hist_id_stomate, 'CH4_FLUX_BUB_wet2', itime, &
833                    ch4_flux_density_bub_wet2, kjpindex, hori_index)
834    CALL histwrite_p (hist_id_stomate, 'CH4_FLUX_PLA_wet2', itime, &
835                    ch4_flux_density_pla_wet2, kjpindex, hori_index)
836    CALL histwrite_p (hist_id_stomate, 'CH4_FLUX_TOT_wet3', itime, &
837                    ch4_flux_density_tot_wet3, kjpindex, hori_index)
838    CALL histwrite_p (hist_id_stomate, 'CH4_FLUX_DIF_wet3', itime, &
839                    ch4_flux_density_dif_wet3, kjpindex, hori_index)
840    CALL histwrite_p (hist_id_stomate, 'CH4_FLUX_BUB_wet3', itime, &
841                    ch4_flux_density_bub_wet3, kjpindex, hori_index)
842    CALL histwrite_p (hist_id_stomate, 'CH4_FLUX_PLA_wet3', itime, &
843                    ch4_flux_density_pla_wet3, kjpindex, hori_index)
844    CALL histwrite_p (hist_id_stomate, 'CH4_FLUX_TOT_wet4', itime, &
845                    ch4_flux_density_tot_wet4, kjpindex, hori_index)
846    CALL histwrite_p (hist_id_stomate, 'CH4_FLUX_DIF_wet4', itime, &
847                    ch4_flux_density_dif_wet4, kjpindex, hori_index)
848    CALL histwrite_p (hist_id_stomate, 'CH4_FLUX_BUB_wet4', itime, &
849                    ch4_flux_density_bub_wet4, kjpindex, hori_index)
850    CALL histwrite_p (hist_id_stomate, 'CH4_FLUX_PLA_wet4', itime, &
851                    ch4_flux_density_pla_wet4, kjpindex, hori_index)
852
853  END SUBROUTINE stomate_wet_ch4_main
854
855!! ================================================================================================================================
856!! SUBROUTINE   : stomate_wet_ch4_clear
857!!
858!>\BRIEF        Module variables deallocation
859!!
860!! DESCRIPTION  :
861!!               
862!! \n
863!_ ================================================================================================================================
864!!
865  SUBROUTINE stomate_wet_ch4_clear ( )
866    !
867    ! 0 declarations
868    !
869
870    ! 0.1 input
871
872    ! 0.2 modified fields
873
874    ! 0.3 output
875
876    ! density flux of methane calculated for entire pixel (gCH4/dt/m**2)
877
878    ! 0.4 local
879
880
881    IF (ALLOCATED(uo_0)) DEALLOCATE(uo_0)
882    IF (ALLOCATED(uold2_0)) DEALLOCATE(uold2_0)
883    IF (ALLOCATED(uo_wet1)) DEALLOCATE(uo_wet1)
884    IF (ALLOCATED(uold2_wet1)) DEALLOCATE(uold2_wet1)
885    IF (ALLOCATED(uo_wet2)) DEALLOCATE(uo_wet2)
886    IF (ALLOCATED(uold2_wet2)) DEALLOCATE(uold2_wet2)
887    IF (ALLOCATED(uo_wet3)) DEALLOCATE(uo_wet3)
888    IF (ALLOCATED(uold2_wet3)) DEALLOCATE(uold2_wet3)
889    IF (ALLOCATED(uo_wet4)) DEALLOCATE(uo_wet4)
890    IF (ALLOCATED(uold2_wet4)) DEALLOCATE(uold2_wet4)
891
892    IF (ALLOCATED(ch4_flux_density_tot_0)) DEALLOCATE(ch4_flux_density_tot_0)
893    IF (ALLOCATED(ch4_flux_density_dif_0)) DEALLOCATE(ch4_flux_density_dif_0)
894    IF (ALLOCATED(ch4_flux_density_bub_0)) DEALLOCATE(ch4_flux_density_bub_0)
895    IF (ALLOCATED(ch4_flux_density_pla_0)) DEALLOCATE(ch4_flux_density_pla_0)
896    IF (ALLOCATED(ch4_flux_density_tot_wet1)) DEALLOCATE(ch4_flux_density_tot_wet1)
897    IF (ALLOCATED(ch4_flux_density_dif_wet1)) DEALLOCATE(ch4_flux_density_dif_wet1)
898    IF (ALLOCATED(ch4_flux_density_bub_wet1)) DEALLOCATE(ch4_flux_density_bub_wet1)
899    IF (ALLOCATED(ch4_flux_density_pla_wet1)) DEALLOCATE(ch4_flux_density_pla_wet1)
900    IF (ALLOCATED(ch4_flux_density_tot_wet2)) DEALLOCATE(ch4_flux_density_tot_wet2)
901    IF (ALLOCATED(ch4_flux_density_dif_wet2)) DEALLOCATE(ch4_flux_density_dif_wet2)
902    IF (ALLOCATED(ch4_flux_density_bub_wet2)) DEALLOCATE(ch4_flux_density_bub_wet2)
903    IF (ALLOCATED(ch4_flux_density_pla_wet2)) DEALLOCATE(ch4_flux_density_pla_wet2)
904    IF (ALLOCATED(ch4_flux_density_tot_wet3)) DEALLOCATE(ch4_flux_density_tot_wet3)
905    IF (ALLOCATED(ch4_flux_density_dif_wet3)) DEALLOCATE(ch4_flux_density_dif_wet3)
906    IF (ALLOCATED(ch4_flux_density_bub_wet3)) DEALLOCATE(ch4_flux_density_bub_wet3)
907    IF (ALLOCATED(ch4_flux_density_pla_wet3)) DEALLOCATE(ch4_flux_density_pla_wet3)
908    IF (ALLOCATED(ch4_flux_density_tot_wet4)) DEALLOCATE(ch4_flux_density_tot_wet4)
909    IF (ALLOCATED(ch4_flux_density_dif_wet4)) DEALLOCATE(ch4_flux_density_dif_wet4)
910    IF (ALLOCATED(ch4_flux_density_bub_wet4)) DEALLOCATE(ch4_flux_density_bub_wet4)
911    IF (ALLOCATED(ch4_flux_density_pla_wet4)) DEALLOCATE(ch4_flux_density_pla_wet4)
912
913    CALL ch4_wet_flux_density_clear_0
914    CALL ch4_wet_flux_density_clear_wet
915
916  END SUBROUTINE stomate_wet_ch4_clear
917
918
919!! ================================================================================================================================
920!! SUBROUTINE   : stomate_wet_ch4_finalize
921!!
922!>\BRIEF       Write data to restart file
923!!
924!! DESCRIPTION  :
925!!               
926!! \n
927!_ ================================================================================================================================
928!!
929  SUBROUTINE stomate_wet_ch4_finalize ( rest_id, itime )
930
931    ! 0.1 Input variables
932    INTEGER(i_std), INTENT(in) :: rest_id
933    INTEGER(i_std), INTENT(in) :: itime
934
935!_ =====================================================================================================================
936
937    !
938    ! 0 declarations
939    !
940
941    ! 0.1 input
942
943    ! 0.2 modified fields
944
945    ! 0.3 output
946
947    ! density flux of methane calculated for entire pixel (gCH4/dt/m**2)
948
949    ! 0.4 local
950
951    CALL stomate_wet_ch4_writerestart( rest_id, itime)
952
953  END SUBROUTINE stomate_wet_ch4_finalize
954
955
956!! ================================================================================================================================
957!! SUBROUTINE   : stomate_wet_ch4_histdef
958!!
959!>\BRIEF        Define IOIPSL history output
960!!
961!! DESCRIPTION  : 
962!!               
963!! \n
964!_ ================================================================================================================================
965!!
966  SUBROUTINE stomate_wet_ch4_histdef (iim, jjm, dt, hist_hori_id, hist_id, ave, &
967                                      hist_id_stomate )
968    !
969    ! 0 declarations
970    !
971
972    ! 0.1 input
973    INTEGER(i_std), INTENT(in)          :: iim, jjm  !! Size in x and y of the data to be handeled
974   
975    REAL(r_std),INTENT(in)              :: hist_id            !- Time step of history file (s)
976   
977    INTEGER(i_std),INTENT(in)           :: hist_hori_id !- id horizontal grid
978   
979    REAL(r_std),INTENT(in)              :: dt !- Time step of STOMATE (seconds)
980
981    CHARACTER(LEN=40), DIMENSION(:), INTENT(in) ::  ave
982
983    INTEGER(i_std),INTENT(in)           :: hist_id_stomate !- history stomate id
984    ! 0.2 modified fields
985
986    ! 0.3 output
987
988    ! 0.4 local
989!_ ================================================================================================================================
990
991    CALL histdef (hist_id_stomate, &
992         &               TRIM("CH4_FLUX_TOT_0      "), &
993         &               TRIM("flux density tot of CH4 by wetlands               "), &
994         &               TRIM("mgCH4/d/m**2        "), iim,jjm, hist_hori_id, &
995         &               1,1,1, -99,32, ave(5), dt, hist_id)
996   
997    CALL histdef (hist_id_stomate, &
998         &               TRIM("CH4_FLUX_DIF_0      "), &
999         &               TRIM("flux density dif of CH4 by wetlands               "), &
1000         &               TRIM("mgCH4/d/m**2        "), iim,jjm, hist_hori_id, &
1001         &               1,1,1, -99,32, ave(5), dt, hist_id)
1002   
1003    CALL histdef (hist_id_stomate, &
1004         &               TRIM("CH4_FLUX_BUB_0      "), &
1005         &               TRIM("flux density bub of CH4 by wetlands               "), &
1006         &               TRIM("mgCH4/d/m**2        "), iim,jjm, hist_hori_id, &
1007         &               1,1,1, -99,32, ave(5), dt, hist_id)
1008   
1009    CALL histdef (hist_id_stomate, &
1010         &               TRIM("CH4_FLUX_PLA_0      "), &
1011         &               TRIM("flux density pla of CH4 by wetlands               "), &
1012         &               TRIM("mgCH4/d/m**2        "), iim,jjm, hist_hori_id, &
1013         &               1,1,1, -99,32, ave(5), dt, hist_id)
1014   
1015    !!pour wetland avec WTD = -x1
1016    CALL histdef (hist_id_stomate, &
1017         &               TRIM("CH4_FLUX_TOT_wet1    "), &
1018         &               TRIM("flux density tot of CH4 by wetlands               "), &
1019         &               TRIM("mgCH4/d/m**2        "), iim,jjm, hist_hori_id, &
1020         &               1,1,1, -99,32, ave(5), dt, hist_id)
1021   
1022   CALL histdef (hist_id_stomate, &
1023        &               TRIM("CH4_FLUX_DIF_wet1    "), &
1024        &               TRIM("flux density dif of CH4 by wetlands               "), &
1025        &               TRIM("mgCH4/d/m**2        "), iim,jjm, hist_hori_id, &
1026        &               1,1,1, -99,32, ave(5), dt, hist_id)
1027   
1028   CALL histdef (hist_id_stomate, &
1029        &               TRIM("CH4_FLUX_BUB_wet1    "), &
1030        &               TRIM("flux density bub of CH4 by wetlands               "), &
1031        &               TRIM("mgCH4/d/m**2        "), iim,jjm, hist_hori_id, &
1032        &               1,1,1, -99,32, ave(5), dt, hist_id)
1033   
1034   CALL histdef (hist_id_stomate, &
1035        &               TRIM("CH4_FLUX_PLA_wet1    "), &
1036        &               TRIM("flux density pla of CH4 by wetlands               "), &
1037        &               TRIM("mgCH4/d/m**2        "), iim,jjm, hist_hori_id, &
1038        &               1,1,1, -99,32, ave(5), dt, hist_id)
1039   
1040   !pour wetland avc WTD = -x2
1041   CALL histdef (hist_id_stomate, &
1042        &               TRIM("CH4_FLUX_TOT_wet2    "), &
1043        &               TRIM("flux density tot of CH4 by wetlands               "), &
1044        &               TRIM("mgCH4/d/m**2        "), iim,jjm, hist_hori_id, &
1045        &               1,1,1, -99,32, ave(5), dt, hist_id)
1046   
1047   CALL histdef (hist_id_stomate, &
1048        &               TRIM("CH4_FLUX_DIF_wet2    "), &
1049        &               TRIM("flux density dif of CH4 by wetlands               "), &
1050        &               TRIM("mgCH4/d/m**2        "), iim,jjm, hist_hori_id, &
1051        &               1,1,1, -99,32, ave(5), dt, hist_id)
1052   
1053   CALL histdef (hist_id_stomate, &
1054        &               TRIM("CH4_FLUX_BUB_wet2    "), &
1055        &               TRIM("flux density bub of CH4 by wetlands               "), &
1056        &               TRIM("mgCH4/d/m**2        "), iim,jjm, hist_hori_id, &
1057        &               1,1,1, -99,32, ave(5), dt, hist_id)
1058   
1059   CALL histdef (hist_id_stomate, &
1060        &               TRIM("CH4_FLUX_PLA_wet2    "), &
1061        &               TRIM("flux density pla of CH4 by wetlands               "), &
1062        &               TRIM("mgCH4/d/m**2        "), iim,jjm, hist_hori_id, &
1063        &               1,1,1, -99,32, ave(5), dt, hist_id)
1064
1065   !pour wetland avec WTD = -x3
1066   CALL histdef (hist_id_stomate, &
1067        &               TRIM("CH4_FLUX_TOT_wet3    "), &
1068        &               TRIM("flux density tot of CH4 by wetlands               "), &
1069        &               TRIM("mgCH4/d/m**2        "), iim,jjm, hist_hori_id, &
1070        &               1,1,1, -99,32, ave(5), dt, hist_id)
1071   
1072   CALL histdef (hist_id_stomate, &
1073        &               TRIM("CH4_FLUX_DIF_wet3    "), &
1074        &               TRIM("flux density dif of CH4 by wetlands               "), &
1075        &               TRIM("mgCH4/d/m**2        "), iim,jjm, hist_hori_id, &
1076        &               1,1,1, -99,32, ave(5), dt, hist_id)
1077   
1078   CALL histdef (hist_id_stomate, &
1079        &               TRIM("CH4_FLUX_BUB_wet3    "), &
1080        &               TRIM("flux density bub of CH4 by wetlands               "), &
1081        &               TRIM("mgCH4/d/m**2        "), iim,jjm, hist_hori_id, &
1082        &               1,1,1, -99,32, ave(5), dt, hist_id)
1083   
1084   CALL histdef (hist_id_stomate, &
1085        &               TRIM("CH4_FLUX_PLA_wet3    "), &
1086        &               TRIM("flux density pla of CH4 by wetlands               "), &
1087        &               TRIM("mgCH4/d/m**2        "), iim,jjm, hist_hori_id, &
1088        &               1,1,1, -99,32, ave(5), dt, hist_id)
1089   
1090   !wetland avc WTD = -x4
1091   CALL histdef (hist_id_stomate, &
1092        &               TRIM("CH4_FLUX_TOT_wet4    "), &
1093        &               TRIM("flux density tot of CH4 by wetlands               "), &
1094        &               TRIM("mgCH4/d/m**2        "), iim,jjm, hist_hori_id, &
1095        &               1,1,1, -99,32, ave(5), dt, hist_id)
1096   
1097   CALL histdef (hist_id_stomate, &
1098        &               TRIM("CH4_FLUX_DIF_wet4    "), &
1099        &               TRIM("flux density dif of CH4 by wetlands               "), &
1100        &               TRIM("mgCH4/d/m**2        "), iim,jjm, hist_hori_id, &
1101        &               1,1,1, -99,32, ave(5), dt, hist_id)
1102   
1103   CALL histdef (hist_id_stomate, &
1104        &               TRIM("CH4_FLUX_BUB_wet4    "), &
1105        &               TRIM("flux density bub of CH4 by wetlands               "), &
1106        &               TRIM("mgCH4/d/m**2        "), iim,jjm, hist_hori_id, &
1107        &               1,1,1, -99,32, ave(5), dt, hist_id)
1108   
1109   CALL histdef (hist_id_stomate, &
1110        &               TRIM("CH4_FLUX_PLA_wet4    "), &
1111        &               TRIM("flux density pla of CH4 by wetlands               "), &
1112        &               TRIM("mgCH4/d/m**2        "), iim,jjm, hist_hori_id, &
1113        &               1,1,1, -99,32, ave(5), dt, hist_id)
1114
1115  END SUBROUTINE stomate_wet_ch4_histdef
1116 
1117
1118END MODULE stomate_wet_ch4
1119
1120
1121
1122
1123
1124
1125
1126
1127
1128
1129
1130
1131
1132
1133
1134
1135
1136
1137
1138
Note: See TracBrowser for help on using the repository browser.