source: LMDZ6/trunk/libf/phylmd/Dust/condsurfs_new.F @ 5075

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

[continued & end] replace netcdf by lmdz_netcdf.F90 wrapper
"use netcdf" is now only used in lmdz_netcdf.F90 (except ecrad and obsolete/)
<include "netcdf.inc"> is now likewise only used in lmdz_netcdf.F90.

systematically specify explicitely <USE lmdz_netcdf, ONLY:> (probably left some missing, to correct later on)

Further replacement of nf_put_* by nf90_put_* (same for _get_)

[minor] replace deprecated boolean operators along the way

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