SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
modd_gr_biog_greenroofn.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #####################
7 ! ######################
8 !
9 !!
10 !!!!**** *MODD_GR_BIOG_GREENROOF_n* - Declaration of variables for biogenic emissions
11 !
12 !!
13 !!** IMPLICIT ARGUMENTS
14 !! ------------------
15 !! None
16 !!
17 !! REFERENCE
18 !! ---------
19 !! AUTHOR
20 !! ------
21 !! F. Solmon *LA*
22 !!
23 !! MODIFICATIONS
24 !! -------------
25 !! P. Tulet 30/07/03 externalisation of biogenics fluxes
26 !!
27 !* 0. DECLARATIONS
28 ! ----------
29 !
30 !
31 USE yomhook ,ONLY : lhook, dr_hook
32 USE parkind1 ,ONLY : jprb
33 !
34 IMPLICIT NONE
35 
37 !
38 !
39 !
40 !* Emission potential for isoprene and monoterpenes
41  REAL, DIMENSION(:), POINTER :: XISOPOT
42  REAL, DIMENSION(:), POINTER :: XMONOPOT
43 !
44 !* Radiation at different level(cf Gauss) in the canopy
45  REAL, DIMENSION(:), POINTER :: XP_IACAN !pack radiation
46  REAL, DIMENSION(:,:,:),POINTER ::XIACAN ! PAR at 3 gauss level for each patch
47 !
48 !* XFISO = isoprene emission flux (ppp.m.s-1)
49 ! XFMONO = monoterpenes emission flux (ppp m s-1)
50  REAL, DIMENSION(:), POINTER :: XFISO, XFMONO
51 !
52 !
53 END TYPE gr_biog_greenroof_t
54 
55 
56 
57  CONTAINS
58 
59 !
60 
61 
62 
63 
64 SUBROUTINE gr_biog_greenroof_init(YGR_BIOG_GREENROOF)
65 TYPE(gr_biog_greenroof_t), INTENT(INOUT) :: ygr_biog_greenroof
66 REAL(KIND=JPRB) :: zhook_handle
67 IF (lhook) CALL dr_hook("MODD_GR_BIOG_GREENROOF_N:GR_BIOG_GREENROOF_INIT",0,zhook_handle)
68  nullify(ygr_biog_greenroof%XISOPOT)
69  nullify(ygr_biog_greenroof%XMONOPOT)
70  nullify(ygr_biog_greenroof%XP_IACAN)
71  nullify(ygr_biog_greenroof%XIACAN)
72  nullify(ygr_biog_greenroof%XFISO)
73  nullify(ygr_biog_greenroof%XFMONO)
74 IF (lhook) CALL dr_hook("MODD_GR_BIOG_GREENROOF_N:GR_BIOG_GREENROOF_INIT",1,zhook_handle)
75 END SUBROUTINE gr_biog_greenroof_init
76 
77 
78 END MODULE modd_gr_biog_greenroof_n
subroutine gr_biog_greenroof_init(YGR_BIOG_GREENROOF)