SURFEX v8.1
General documentation of Surfex
ch_init_depconst.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 ! #########
6  SUBROUTINE ch_init_depconst(HPROGRAM,HCHEM_SURF_FILE,KLUOUT,HSV)
7 !! ##################################################
8 !!
9 !!*** *CH_INIT_DEPCONST*
10 !!
11 !! PURPOSE
12 !! -------
13 ! Read Henry Specific constant, Molecular Mass and Biological reactivity
14 !! factor.
15 !!
16 !!
17 !!** METHOD
18 !! ------
19 !
20 !! Chemical constant will be read from
21 !! the general purpose input file .
22 !!
23 !! chemical molecular diffusivity MASS_MOL
24 !! molecular reactivity factor REA_FACT
25 !! molecular effective Henry constant HENRY_SP
26 !!
27 !!
28 !! REFERENCE
29 !! ---------
30 !!
31 !! AUTHOR
32 !! ------
33 !! P. Tulet *Meteo France*
34 !!
35 !! MODIFICATIONS
36 !! -------------
37 !! Original 16/02/01
38 
39 !! EXTERNAL
40 !! --------
41 !!
42 ! open the general purpose ASCII input file
43 USE modi_open_namelist
44 USE modi_close_namelist
45 !
46 USE modi_ch_open_inputb
47 USE modd_ch_surf
48 !!
49 !! IMPLICIT ARGUMENTS
50 !! ------------------
51 !-------------------------------------------------------------------------------
52 !
53 !* 0. DECLARATIONS
54 ! ------------
55 !
56 USE yomhook ,ONLY : lhook, dr_hook
57 USE parkind1 ,ONLY : jprb
58 !
59 IMPLICIT NONE
60 !
61 !* 0.1 declarations of arguments
62 !
63  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! Program name
64  CHARACTER(LEN=28), INTENT(IN) :: HCHEM_SURF_FILE ! ascii file for chemistry aggregation
65 INTEGER, INTENT(IN) :: KLUOUT ! output listing channel
66  CHARACTER(LEN=*), DIMENSION(:), INTENT(IN) :: HSV ! name of chemical species
67 !
68 !* 0.2 declarations of local variables
69 !
70  CHARACTER(LEN=40) :: YFORMAT
71  ! format for input
72  CHARACTER(LEN=40) :: YOUTFORMAT = '(A32,2E15.5)'
73  ! format for output
74 !
75 INTEGER :: IMASS ! number of molecular diffusivity to be read
76  CHARACTER(LEN=40), DIMENSION(:), ALLOCATABLE :: YMASSMOLNAME !species names
77 REAL , DIMENSION(:), ALLOCATABLE :: ZMASSMOLVAL
78  ! molecular diffusivity value
79 !
80 INTEGER :: IREACT ! number of chemical reactivity factor to be read
81  CHARACTER(LEN=40), DIMENSION(:), ALLOCATABLE :: YREACTNAME !species names
82 REAL , DIMENSION(:), ALLOCATABLE :: ZREACTVAL
83  ! chemical reactivity factor value
84 !
85 INTEGER :: IHENRY ! number of chemical Henry constant to be read
86  CHARACTER(LEN=40), DIMENSION(:), ALLOCATABLE :: YHENRYNAME !species names
87  character(len=50) :: yname
88 REAL , DIMENSION(:,:), ALLOCATABLE :: ZHENRYVAL
89  !chemical Henry constant value
90 !
91 INTEGER :: ICH ! unit of input chemical file
92 !
93 INTEGER :: JI, JN, JNREAL ! loop control variables
94 INTEGER :: INACT ! array pointer
95 REAL(KIND=JPRB) :: ZHOOK_HANDLE
96 !
97 !-------------------------------------------------------------------------------
98 !
99 !* 1. ALLOCATE FIELD
100 ! --------------
101 !
102 IF (lhook) CALL dr_hook('CH_INIT_DEPCONST',0,zhook_handle)
103 IF(.NOT. ALLOCATED(xsrealmassmolval)) ALLOCATE( xsrealmassmolval(SIZE(hsv,1)) )
104 IF(.NOT. ALLOCATED(xsrealreactval) ) ALLOCATE( xsrealreactval(SIZE(hsv,1)) )
105 IF(.NOT. ALLOCATED(xsrealhenryval) ) ALLOCATE( xsrealhenryval(SIZE(hsv,1),2) )
106 !
107  CALL open_namelist(hprogram,ich,hfile=hchem_surf_file)
108 !
109 !* 2. read chemical molecular diffusivity MASS_MOL
110 !
111 ! open input file
112  WRITE(kluout,*) &
113  "CH_INIT_CONST: reading molar mass"
114  CALL ch_open_inputb("MASS_MOL", ich, kluout)
115 !
116 ! read number of molecular diffusivity IMASS
117  READ(ich, *) imass
118  WRITE(kluout,*) "number of molecular diffusivity: ", imass
119 !
120 ! read data input format
121  READ(ich,"(A)") yformat
122  WRITE(kluout,*) "input format is: ", yformat
123 !
124 ! allocate fields
125  ALLOCATE(ymassmolname(imass))
126  ALLOCATE(zmassmolval(imass))
127 !
128 ! read molecular diffusivity
129  DO ji = 1, imass
130  READ(ich,yformat) ymassmolname(ji), zmassmolval(ji)
131  WRITE(kluout,yformat) ymassmolname(ji), zmassmolval(ji)
132  END DO
133 !
134 !
135  WRITE(kluout,'(A)') '----------------------------------------------------'
136  WRITE(kluout,'(A)') 'MASS_MOL'
137  WRITE(kluout,'(A)') 'molecular mass (in g/mol) for molecular diffusion'
138  WRITE(kluout,'(I4)') SIZE(hsv,1)
139  WRITE(kluout,'(A)') youtformat
140 !
141  xsrealmassmolval(:) = 50. ! default molecular mass
142  DO jnreal = 1, SIZE(hsv,1)
143  inact = 0
144  search_loop3 : DO jn = 1, imass
145  IF (hsv(jnreal) .EQ. ymassmolname(jn)) THEN
146  inact = jn
147  EXIT search_loop3
148  END IF
149  END DO search_loop3
150  IF (inact .NE. 0) xsrealmassmolval(jnreal) = zmassmolval(inact)
151  WRITE(kluout,youtformat) hsv(jnreal), xsrealmassmolval(jnreal)
152  END DO
153 !
154 !
155 !-----------------------------------------------------------------------------
156 !
157 !* 3. read molecular reactivity factor REA_FACT
158 !
159 ! open input file
160  WRITE(kluout,*) &
161  "CH_INIT_CONST: reading reactivity factor "
162  CALL ch_open_inputb("REA_FACT", ich, kluout)
163 !
164 ! read number of molecular diffusivity IREACT
165  READ(ich, *) ireact
166  WRITE(kluout,*) "number of reactivity factor : ", ireact
167 !
168 ! read data input format
169  READ(ich,"(A)") yformat
170  WRITE(kluout,*) "input format is: ", yformat
171 !
172 ! allocate fields
173  ALLOCATE(yreactname(ireact))
174  ALLOCATE(zreactval(ireact))
175 ! read reactivity factor
176  DO ji = 1, ireact
177  READ(ich,yformat) yreactname(ji), zreactval(ji)
178  WRITE(kluout,yformat) yreactname(ji), zreactval(ji)
179  END DO
180 !
181  WRITE(kluout,'(A)') '----------------------------------------------------'
182  WRITE(kluout,'(A)') 'REA_FACT'
183  WRITE(kluout,'(A)') 'reactivity factor'
184  WRITE(kluout,'(I4)') SIZE(hsv,1)
185  WRITE(kluout,'(A)') youtformat
186 !
187  xsrealreactval(:) = 0.0 ! default (high surface resistance)
188  DO jnreal = 1, SIZE(hsv,1)
189  inact = 0
190  search_loop4 : DO jn = 1, ireact
191  IF (hsv(jnreal) .EQ. yreactname(jn)) THEN
192  inact = jn
193  EXIT search_loop4
194  END IF
195  END DO search_loop4
196  IF (inact .NE. 0) xsrealreactval(jnreal) = zreactval(inact)
197  WRITE(kluout,youtformat) hsv(jnreal), xsrealreactval(jnreal)
198  END DO
199 !
200 !
201 !-----------------------------------------------------------------------------
202 !
203 !* 4. read molecular effective Henry constant HENRY_SP
204 !
205 ! open input file
206  WRITE(kluout,*) &
207  "CH_INIT_CONST: reading effective Henry constant", &
208  " and its temperature correction "
209  CALL ch_open_inputb("HENRY_SP", ich, kluout)
210 !
211 ! read number of molecular diffusivity IHENRY
212  READ(ich, *) ihenry
213  WRITE(kluout,*) "number of reactivity factor : ", ihenry
214 !
215 ! read data input format
216  READ(ich,"(A)") yformat
217  WRITE(kluout,*) "input format is: ", yformat
218 !
219 ! allocate fields
220  ALLOCATE(yhenryname(ihenry))
221  ALLOCATE(zhenryval(ihenry,2))
222 !
223 ! read reactivity factor
224  DO jnreal = 1, ihenry
225  READ(ich,yformat) yhenryname(jnreal), zhenryval(jnreal,1),&
226  zhenryval(jnreal,2)
227  WRITE(kluout,yformat) yhenryname(jnreal), zhenryval(jnreal,1),&
228  zhenryval(jnreal,2)
229  END DO
230 !
231  WRITE(kluout,'(A)') '----------------------------------------------------'
232  WRITE(kluout,'(A)') 'HENRY_SP'
233  WRITE(kluout,'(A)') 'Henrys law constants factor / exponent'
234  WRITE(kluout,'(I4)') SIZE(hsv,1)
235  WRITE(kluout,'(A)') youtformat
236 !
237  xsrealhenryval(:,1) = 1e-8 ! no deposition; low Henry constant
238  xsrealhenryval(:,2) = 0. !
239  DO jnreal = 1, SIZE(hsv,1)
240  inact = 0
241  search_loop5 : DO jn = 1, ihenry
242  IF (hsv(jnreal) .EQ. yhenryname(jn)) THEN
243  inact = jn
244  EXIT search_loop5
245  END IF
246  END DO search_loop5
247  IF (inact .NE. 0) xsrealhenryval(jnreal,1) = zhenryval(inact,1)
248  IF (inact .NE. 0) xsrealhenryval(jnreal,2) = zhenryval(inact,2)
249  WRITE(kluout,youtformat) hsv(jnreal), &
250  xsrealhenryval(jnreal,1),&
251  xsrealhenryval(jnreal,2)
252  END DO
253 
254  CALL close_namelist(hprogram,ich)
255 
256 IF (lhook) CALL dr_hook('CH_INIT_DEPCONST',1,zhook_handle)
257 !
258 END SUBROUTINE ch_init_depconst
real, dimension(:), allocatable, save xsrealreactval
subroutine ch_open_inputb(HKEYWORD, KCHANNEL, KLUOUT)
integer, parameter jprb
Definition: parkind1.F90:32
real, dimension(:,:), allocatable, save xsrealhenryval
subroutine close_namelist(HPROGRAM, KLUNAM)
subroutine ch_init_depconst(HPROGRAM, HCHEM_SURF_FILE, KLUOUT, HSV)
logical lhook
Definition: yomhook.F90:15
real, dimension(:), allocatable, save xsrealmassmolval
subroutine open_namelist(HPROGRAM, KLUNAM, HFILE)