source: CONFIG/publications/ICOLMDZORINCA_CO2_Transport_GMD_2023/INCA/build/ppsrc/INCA_VEG/surf_chem_mod.f90 @ 6610

Last change on this file since 6610 was 6610, checked in by acosce, 10 months ago

INCA used for ICOLMDZORINCA_CO2_Transport_GMD_2023

File size: 7.2 KB
Line 
1
2
3
4
5
6
7
8
9
10
11
12MODULE SURF_CHEM_MOD
13
14  ! Max. fraction of vegetation type (LAI->infty) - issue de Orchidee
15  REAL,ALLOCATABLE, SAVE, DIMENSION (:,:)     :: maxvegetfrac_fromOrch       
16!$OMP THREADPRIVATE(maxvegetfrac_fromOrch)
17
18  ! repartition des types de surface = maxvegetfrac + sic + lic + oce
19  REAL,ALLOCATABLE, SAVE, DIMENSION (:,:)     :: surftype_frac       
20!$OMP THREADPRIVATE(surftype_frac)
21
22  ! Surface foliere
23  REAL, ALLOCATABLE, SAVE, DIMENSION(:,:)     :: lai_fromOrch
24!$OMP THREADPRIVATE(lai_fromOrch)
25
26  ! tableau contenant les emissions recuperees de orchidee
27  REAL, DIMENSION(:,:,:), SAVE, ALLOCATABLE :: emiflx_fromOrch 
28!$OMP THREADPRIVATE(emiflx_fromOrch)
29
30  ! tabeau contenant les emissions ponderees par le type de surface
31  REAL, DIMENSION(:,:), SAVE, ALLOCATABLE :: tot_emiflx_fromOrch
32!$OMP THREADPRIVATE(tot_emiflx_fromOrch)
33
34  ! tableau contenant les fractions de types de vegetation (unitless, 0-1)
35  REAL, DIMENSION(:,:), SAVE, ALLOCATABLE :: vegetfrac_fromOrch
36!$OMP THREADPRIVATE(vegetfrac_fromOrch)
37
38  !  Mean top dry soil height (m) version beton
39  REAL, DIMENSION(:), SAVE, ALLOCATABLE :: hdry_fromOrch
40!$OMP THREADPRIVATE(hdry_fromOrch)
41
42  ! Snow mass [Kg/m^2]
43  REAL, DIMENSION(:), SAVE, ALLOCATABLE :: snow_fromOrch
44!$OMP THREADPRIVATE(snow_fromOrch)
45
46  ! id du fichier d'output veget
47  INTEGER, SAVE :: veget_id
48!$OMP THREADPRIVATE(veget_id)
49
50  ! noms des variables pour le fichier netcdf
51  CHARACTER*(200), SAVE, ALLOCATABLE, DIMENSION(:) :: title_emi
52!$OMP THREADPRIVATE(title_emi)
53
54  ! unites pour le fichier netcdf
55  CHARACTER*(20), SAVE, ALLOCATABLE, DIMENSION(:)  :: unit_emi
56!$OMP THREADPRIVATE(unit_emi)
57
58  ! numero id des differents flux
59  INTEGER, SAVE :: id_Orch_iso, id_Orch_apin, id_Orch_orvoc, id_Orch_mbo, id_Orch_ch3oh, id_Orch_ch3coch3, id_Orch_acetal, &
60       id_Orch_formal, id_Orch_acetic, id_Orch_formic, id_Orch_no_soil, id_Orch_nox, id_Orch_fertil_no, &
61       id_Orch_flx_apinen, id_Orch_bpinen, id_Orch_limonen, id_Orch_myrcen, id_Orch_sabinen, id_Orch_camphen, &   
62       id_Orch_3caren, id_Orch_tbocimen, id_Orch_othermono, id_Orch_sesquiter 
63
64
65!$OMP THREADPRIVATE(id_Orch_iso, id_Orch_apin, id_Orch_orvoc, id_Orch_mbo, id_Orch_ch3oh, id_Orch_ch3coch3, id_Orch_acetal)
66!$OMP THREADPRIVATE(id_Orch_formal, id_Orch_acetic, id_Orch_formic, id_Orch_no_soil, id_Orch_nox, id_Orch_fertil_no)
67!$OMP THREADPRIVATE(id_Orch_flx_apinen, id_Orch_bpinen, id_Orch_limonen, id_Orch_myrcen, id_Orch_sabinen, id_Orch_camphen)
68!$OMP THREADPRIVATE(id_Orch_3caren, id_Orch_tbocimen, id_Orch_othermono, id_Orch_sesquiter) 
69
70  INTEGER, SAVE :: nbsurf   ! nombre de type de surf (nbveget  + sic + lic + oce)
71!OMP THREADPRIVATE(nbsurf)
72
73CONTAINS
74       
75  SUBROUTINE INIT_SURF_CHEM_MOD
76
77    USE INCA_DIM
78    USE IOIPSL
79    USE PRINT_INCA
80    USE PARAM_CHEM
81
82    IMPLICIT NONE
83     
84    INTEGER :: i 
85 
86    id_orch_iso        = 0
87    id_orch_apin       = 0
88    id_orch_orvoc      = 0
89    id_orch_mbo        = 0
90    id_orch_ch3oh      = 0
91    id_orch_ch3coch3   = 0
92    id_orch_acetal     = 0
93    id_orch_formal     = 0
94    id_orch_acetic     = 0
95    id_orch_formic     = 0
96    id_orch_no_soil    = 0
97    id_orch_nox        = 0
98    id_orch_fertil_no  = 0 
99    id_orch_flx_apinen = 0 
100    id_orch_bpinen     = 0
101    id_orch_limonen    = 0 
102    id_orch_myrcen     = 0 
103    id_orch_sabinen    = 0 
104    id_orch_camphen    = 0 
105    id_orch_3caren     = 0 
106    id_orch_tbocimen   = 0 
107    id_orch_othermono  = 0 
108    id_orch_sesquiter  = 0 
109
110    nbsurf = nbveget + 3 
111   
112    IF (nb_flux .NE. 0) THEN
113        ALLOCATE(emiflx_fromOrch(PLON,nbveget, nb_flux))
114        emiflx_fromOrch(:,:,:) = 0. 
115        allocate(tot_emiflx_fromOrch(PLON,nb_flux)) 
116        tot_emiflx_fromOrch(:,:) = 0. 
117        ALLOCATE(title_emi(nb_flux)) 
118        ALLOCATE(unit_emi(nb_flux))
119    ENDIF
120
121    DO i=1, nb_flux
122
123      SELECT CASE(TRIM(field_emi_names(i)))
124      CASE("flx_iso") 
125          title_emi(i)="Isoprene emissions from vegetation"
126          unit_emi(i) = "kgC/m²/s "
127          id_Orch_iso = i
128      CASE("flx_mono") 
129          title_emi(i)="Monoterpene emissions from vegetation"
130          unit_emi(i) = "kgC/m²/s "
131          id_Orch_apin = i
132
133      CASE("flx_ORVOC") 
134          title_emi(i)="Other Volatile Organic Compound emissions from vegetation"
135          unit_emi(i) = "kgC/m²/s "
136          id_Orch_orvoc = i
137
138      CASE("flx_MBO") 
139          title_emi(i)="2-methyl-3-buten-2-ol emissions from vegetation (mainly pines in America)"
140          unit_emi(i) = "kgC/m²/s "
141          id_Orch_mbo = i 
142
143      CASE("flx_methanol") 
144          title_emi(i)="Methanol emissions from vegetation"
145          unit_emi(i) = "kgC/m²/s "
146          id_Orch_ch3oh = i 
147
148      CASE("flx_acetone") 
149          title_emi(i)="Acetone emissions from vegetation"
150          unit_emi(i) = "kgC/m²/s "
151          id_Orch_ch3coch3 = i 
152
153      CASE("flx_acetal") 
154          title_emi(i)="Acetaldehyde emissions from vegetation"
155          unit_emi(i) = "kgC/m²/s "
156          id_Orch_acetal = i
157
158      CASE("flx_formal") 
159          title_emi(i)="Formaldehyde emissions from vegetation"
160          unit_emi(i) = "kgC/m²/s "
161          id_Orch_formal = i 
162
163      CASE("flx_acetic") 
164          title_emi(i)="Acetic acid emissions from vegetation"
165          unit_emi(i) = "kgC/m²/s "
166          id_Orch_acetic = i
167
168      CASE("flx_formic") 
169          title_emi(i)="Formic acid emissions from vegetation"
170          unit_emi(i) = "kgC/m²/s "
171          id_Orch_formic = i 
172
173      CASE("flx_no_soil") 
174          title_emi(i)="Nitrogen Oxide emissions from soil, before deposition on canopy"
175          unit_emi(i) = "ngN/m²/s "
176          id_Orch_no_soil = i 
177
178      CASE("flx_nox") 
179          title_emi(i)="Net nitrogen Oxide emissions from soil, after deposition on canopy"
180          unit_emi(i) = "ngN/m²/s "
181          id_Orch_nox = i 
182         
183      CASE("flx_fertil_no") 
184          title_emi(i)="Nitrogen Oxide emission related ONLY to the use of fertilisers, before deposition on canopy"
185          unit_emi(i) = "ngN/m²/s "
186          id_Orch_fertil_no = i 
187
188       CASE("flx_apinen")
189          title_emi(i)=""
190          unit_emi(i) = ""
191          id_Orch_flx_apinen = i 
192       CASE("flx_bpinen")
193          title_emi(i)=""
194          unit_emi(i) = ""
195          id_Orch_bpinen = i 
196       CASE("flx_limonen")
197          title_emi(i)=""
198          unit_emi(i) = ""
199          id_Orch_limonen = i 
200       CASE("flx_myrcen")
201          title_emi(i)=""
202          unit_emi(i) = ""
203          id_Orch_myrcen = i 
204       CASE("flx_sabinen")
205          title_emi(i)=""
206          unit_emi(i) = ""
207          id_Orch_sabinen = i 
208       CASE("flx_camphen")
209          title_emi(i)=""
210          unit_emi(i) = ""
211          id_Orch_camphen = i 
212       CASE("flx_3caren")
213          title_emi(i)=""
214          unit_emi(i) = ""
215          id_Orch_3caren = i 
216       CASE("flx_tbocimen")
217          title_emi(i)=""
218          unit_emi(i) = ""
219          id_Orch_tbocimen = i 
220       CASE("flx_othermono")
221          title_emi(i)=""
222          unit_emi(i) = ""
223          id_Orch_othermono = i 
224       CASE("flx_sesquiter")
225          title_emi(i)=""
226          unit_emi(i) = ""
227          id_Orch_sesquiter = i 
228         
229      CASE DEFAULT 
230         
231           
232      END SELECT
233     
234
235
236
237    ENDDO
238   
239  END SUBROUTINE INIT_SURF_CHEM_MOD
240
241END MODULE SURF_CHEM_MOD
Note: See TracBrowser for help on using the repository browser.