source: LMDZ6/branches/Amaury_dev/libf/phylmd/Dust/condsurfs_new.f90 @ 5209

Last change on this file since 5209 was 5160, checked in by abarral, 7 weeks ago

Put .h into modules

File size: 8.5 KB
Line 
1SUBROUTINE condsurfs_new(jour, edgar, flag_dms, &
2        lmt_so2b, lmt_so2h, lmt_so2nff, &
3        lmt_so2bb_l, lmt_so2bb_h, lmt_so2ba, &
4        lmt_so2volc_cont, lmt_altvolc_cont, &
5        lmt_so2volc_expl, lmt_altvolc_expl, &
6        lmt_dmsbio, lmt_h2sbio, lmt_dms, &
7        lmt_dmsconc)
8  USE lmdz_grid_phy
9  USE lmdz_phys_para
10  USE dimphy
11  USE netcdf, ONLY: nf90_get_var, nf90_inq_varid, nf90_close, nf90_noerr, nf90_open, nf90_nowrite
12  USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
13  IMPLICIT NONE
14
15  ! Lire les conditions aux limites du modele pour la chimie.
16  ! --------------------------------------------------------
17
18
19
20  REAL :: lmt_so2b(klon), lmt_so2h(klon), lmt_so2nff(klon)
21  REAL :: lmt_so2bb_l(klon), lmt_so2bb_h(klon)
22  REAL :: lmt_dmsbio(klon), lmt_h2sbio(klon), lmt_so2ba(klon)
23  REAL :: lmt_so2volc_cont(klon), lmt_altvolc_cont(klon)
24  REAL :: lmt_so2volc_expl(klon), lmt_altvolc_expl(klon)
25  REAL :: lmt_dms(klon), lmt_dmsconc(klon)
26
27  REAL :: lmt_so2b_glo(klon_glo), lmt_so2h_glo(klon_glo)
28  REAL :: lmt_so2nff_glo(klon_glo)
29  REAL :: lmt_so2bb_l_glo(klon_glo), lmt_so2bb_h_glo(klon_glo)
30  REAL :: lmt_dmsbio_glo(klon_glo), lmt_h2sbio_glo(klon_glo)
31  REAL :: lmt_so2ba_glo(klon_glo)
32  REAL :: lmt_so2volc_cont_glo(klon_glo), lmt_altvolc_cont_glo(klon_glo)
33  REAL :: lmt_so2volc_expl_glo(klon_glo), lmt_altvolc_expl_glo(klon_glo)
34  REAL :: lmt_dms_glo(klon_glo), lmt_dmsconc_glo(klon_glo)
35  LOGICAL :: edgar
36  INTEGER :: flag_dms
37
38  INTEGER :: jour, i
39  INTEGER :: ierr
40  INTEGER :: nid, nvarid
41  INTEGER :: debut(2), epais(2)
42
43  IF (jour<0 .OR. jour>(366 - 1)) THEN
44    PRINT*, 'Le jour demande n est pas correcte:', jour
45    PRINT *, 'JE: FORCED TO CONTINUE (emissions have&
46            & to be longer than 1 year!!!! )'
47    ! CALL ABORT
48  ENDIF
49
50  !$OMP MASTER
51  IF (is_mpi_root .AND. is_omp_root) THEN
52
53    ! Tranche a lire:
54    debut(1) = 1
55    debut(2) = jour
56    ! epais(1) = klon
57    epais(1) = klon_glo
58    epais(2) = 1
59    !=======================================================================
60    ! READING NEW EMISSIONS FROM RCP
61    !=======================================================================
62
63    ierr = nf90_open ("sulphur_emissions_antro.nc", nf90_nowrite, nid)
64    IF (ierr/=nf90_noerr) THEN
65      WRITE(6, *)' Pb d''ouverture du fichier sulphur_emissions_antro'
66      WRITE(6, *)' ierr = ', ierr
67      CALL exit(1)
68    endif
69
70    ! SO2 Low level emissions
71
72    ierr = nf90_inq_varid (nid, "SO2FF_LOW", nvarid)
73    ierr = nf90_get_var(nid, nvarid, lmt_so2b_glo, debut, epais)
74    IF (ierr /= nf90_noerr) THEN
75      PRINT*, 'Pb de lecture pour les sources so2 low'
76      PRINT *, 'JE klon, jour, debut ,epais ', klon_glo, jour, debut, epais
77      CALL HANDLE_ERR(ierr)
78      PRINT *, 'error ierr= ', ierr
79      CALL exit(1)
80    ENDIF
81
82    ! SO2 High level emissions
83
84    ierr = nf90_inq_varid (nid, "SO2FF_HIGH", nvarid)
85    ierr = nf90_get_var(nid, nvarid, lmt_so2h_glo, debut, epais)
86    IF (ierr /= nf90_noerr) THEN
87      PRINT*, 'Pb de lecture pour les sources so2 high'
88      CALL exit(1)
89    ENDIF
90
91    ! SO2 Biomass burning High level emissions
92
93    ierr = nf90_inq_varid (nid, "SO2BBH", nvarid)
94    ierr = nf90_get_var(nid, nvarid, lmt_so2bb_h_glo, debut, epais)
95    IF (ierr /= nf90_noerr) THEN
96      PRINT*, 'Pb de lecture pour les sources so2 BB high'
97      CALL exit(1)
98    ENDIF
99
100    ! SO2 biomass burning low level emissions
101
102    ierr = nf90_inq_varid (nid, "SO2BBL", nvarid)
103    ierr = nf90_get_var(nid, nvarid, lmt_so2bb_l_glo, debut, epais)
104    IF (ierr /= nf90_noerr) THEN
105      PRINT*, 'Pb de lecture pour les sources so2 BB low'
106      CALL exit(1)
107    ENDIF
108
109    ! SO2 ship emissions
110
111    ierr = nf90_inq_varid (nid, "SO2BA", nvarid)
112    ierr = nf90_get_var(nid, nvarid, lmt_so2ba_glo, debut, epais)
113    IF (ierr /= nf90_noerr) THEN
114      PRINT*, 'Pb de lecture pour les sources so2 ship'
115      CALL exit(1)
116    ENDIF
117
118    ! SO2 Non Fossil Fuel Emissions
119
120    ierr = nf90_inq_varid (nid, "SO2NFF", nvarid)
121    ierr = nf90_get_var(nid, nvarid, lmt_so2nff_glo, debut, epais)
122    IF (ierr /= nf90_noerr) THEN
123      PRINT*, 'Pb de lecture pour les sources so2 non FF'
124      CALL exit(1)
125    ENDIF
126
127    ierr = nf90_close(nid)
128
129    !=======================================================================
130    ! READING NATURAL EMISSIONS
131    !=======================================================================
132    ierr = nf90_open ("sulphur_emissions_nat.nc", nf90_nowrite, nid)
133    IF (ierr/=nf90_noerr) THEN
134      WRITE(6, *)' Pb d''ouverture du fichier sulphur_emissions_nat'
135      WRITE(6, *)' ierr = ', ierr
136      CALL exit(1)
137    endif
138
139    ! Biologenic source of DMS
140
141    ierr = nf90_inq_varid (nid, "DMSB", nvarid)
142    ierr = nf90_get_var(nid, nvarid, lmt_dmsbio_glo, debut, epais)
143    IF (ierr /= nf90_noerr) THEN
144      PRINT*, 'Pb de lecture pour les sources dms bio'
145      CALL exit(1)
146    ENDIF
147
148    ! Biologenic source of H2S
149
150    ierr = nf90_inq_varid (nid, "H2SB", nvarid)
151    ierr = nf90_get_var(nid, nvarid, lmt_h2sbio_glo, debut, epais)
152    IF (ierr /= nf90_noerr) THEN
153      PRINT*, 'Pb de lecture pour les sources h2s bio'
154      CALL exit(1)
155    ENDIF
156
157    ! Ocean surface concentration of dms (emissions are computed later)
158
159    IF (flag_dms==4) THEN
160
161      ierr = nf90_inq_varid (nid, "DMSC2", nvarid)
162      ierr = nf90_get_var(nid, nvarid, lmt_dmsconc_glo, debut, epais)
163      IF (ierr /= nf90_noerr) THEN
164        PRINT*, 'Pb de lecture pour les sources dms conc 2'
165        CALL exit(1)
166      ENDIF
167
168      DO i = 1, klon
169        ! lmt_dms(i)=0.0
170        lmt_dms_glo(i) = 0.0
171      ENDDO
172
173    ELSE
174
175      PRINT *, 'choix non possible pour flag_dms'
176      STOP
177
178    ENDIF
179
180    ierr = nf90_close(nid)
181
182    !=======================================================================
183    !                  READING VOLCANIC EMISSIONS
184    !=======================================================================
185    PRINT *, '   ***      READING VOLCANIC EMISSIONS   ***   '
186    PRINT *, ' Jour = ', jour
187    ierr = nf90_open ("sulphur_emissions_volc.nc", nf90_nowrite, nid)
188    IF (ierr/=nf90_noerr) THEN
189      WRITE(6, *)' Pb d''ouverture du fichier sulphur_emissions_volc'
190      WRITE(6, *)' ierr = ', ierr
191      CALL exit(1)
192    endif
193
194    ! Continuous Volcanic emissions
195
196    !  ierr = nf90_inq_varid (nid, "VOLC", nvarid)
197    ierr = nf90_inq_varid (nid, "flx_volc_cont", nvarid)
198    ierr = nf90_get_var(nid, nvarid, lmt_so2volc_cont_glo, debut, epais)
199    IF (ierr /= nf90_noerr) THEN
200      PRINT*, 'Pb de lecture pour les sources so2 volcan (cont)'
201      CALL exit(1)
202    ENDIF
203    PRINT *, 'SO2 volc cont (in read) = ', SUM(lmt_so2volc_cont_glo), &
204            MINVAL(lmt_so2volc_cont_glo), MAXVAL(lmt_so2volc_cont_glo)
205    ! lmt_so2volc(:)=0.0
206
207    ! Altitud of continuous volcanic emissions
208
209    !  ierr = nf90_inq_varid (nid, "ALTI", nvarid)
210    ierr = nf90_inq_varid (nid, "flx_volc_altcont", nvarid)
211    ierr = nf90_get_var(nid, nvarid, lmt_altvolc_cont_glo, debut, epais)
212    IF (ierr /= nf90_noerr) THEN
213      PRINT*, 'Pb de lecture pour les altitudes volcan (cont)'
214      CALL exit(1)
215    ENDIF
216
217    ! Explosive Volcanic emissions
218
219    ierr = nf90_inq_varid (nid, "flx_volc_expl", nvarid)
220    ierr = nf90_get_var(nid, nvarid, lmt_so2volc_expl_glo, debut, epais)
221    IF (ierr /= nf90_noerr) THEN
222      PRINT*, 'Pb de lecture pour les sources so2 volcan (expl)'
223      CALL exit(1)
224    ENDIF
225    ! lmt_so2volc_expl(:)=0.0
226    PRINT *, 'SO2 volc expl (in read) = ', SUM(lmt_so2volc_expl_glo), &
227            MINVAL(lmt_so2volc_expl_glo), MAXVAL(lmt_so2volc_expl_glo)
228
229    ! Altitud of explosive volcanic emissions
230
231    ierr = nf90_inq_varid (nid, "flx_volc_altexpl", nvarid)
232    ierr = nf90_get_var(nid, nvarid, lmt_altvolc_expl_glo, debut, epais)
233    IF (ierr /= nf90_noerr) THEN
234      PRINT*, 'Pb de lecture pour les altitudes volcan'
235      CALL exit(1)
236    ENDIF
237    ! lmt_altvolc_expl(:)=0.0
238
239    ierr = nf90_close(nid)
240
241    PRINT*, 'Sources SOUFRE lues pour jour: ', jour
242
243  ENDIF
244  !$OMP END MASTER
245  !$OMP BARRIER
246  CALL scatter(lmt_so2b_glo, lmt_so2b)
247  CALL scatter(lmt_so2h_glo, lmt_so2h)
248  CALL scatter(lmt_so2bb_h_glo, lmt_so2bb_h)
249  CALL scatter(lmt_so2bb_l_glo, lmt_so2bb_l)
250  CALL scatter(lmt_so2ba_glo, lmt_so2ba)
251  CALL scatter(lmt_so2nff_glo, lmt_so2nff)
252  CALL scatter(lmt_dmsbio_glo, lmt_dmsbio)
253  CALL scatter(lmt_h2sbio_glo, lmt_h2sbio)
254  CALL scatter(lmt_dmsconc_glo, lmt_dmsconc)
255  CALL scatter(lmt_dms_glo, lmt_dms)
256  CALL scatter(lmt_so2volc_cont_glo, lmt_so2volc_cont)
257  CALL scatter(lmt_altvolc_cont_glo, lmt_altvolc_cont)
258  CALL scatter(lmt_so2volc_expl_glo, lmt_so2volc_expl)
259  CALL scatter(lmt_altvolc_expl_glo, lmt_altvolc_expl)
260
261
262END SUBROUTINE condsurfs_new
Note: See TracBrowser for help on using the repository browser.