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

Last change on this file since 5075 was 5075, checked in by abarral, 3 months 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: 6.7 KB
Line 
1      SUBROUTINE condsurfc_new(jour,lmt_bcff, lmt_bcnff,
2     .                         lmt_bcbbl,lmt_bcbbh, lmt_bcba,
3     .                         lmt_omff,lmt_omnff,lmt_ombbl,lmt_ombbh,
4     .                                             lmt_omnat, lmt_omba)
5      USE mod_grid_phy_lmdz
6      USE mod_phys_lmdz_para
7      USE dimphy
8      USE lmdz_netcdf, ONLY:nf90_get_var,nf_close,nf_noerr,nf_inq_varid,nf_open,nf_nowrite
9      IMPLICIT none
10c
11c Lire les conditions aux limites du modele pour la chimie.
12c --------------------------------------------------------
13c
14      INCLUDE "dimensions.h"
15
16      REAL lmt_bcff(klon), lmt_bcnff(klon), lmt_bcba(klon)
17      REAL lmt_omff(klon), lmt_omnff(klon), lmt_ombb(klon)
18      REAL lmt_bcbbl(klon), lmt_bcbbh(klon)
19      REAL lmt_ombbl(klon), lmt_ombbh(klon)
20      REAL lmt_omnat(klon), lmt_omba(klon)
21      REAL lmt_terp(klon)
22c
23      REAL lmt_bcff_glo(klon_glo), lmt_bcnff_glo(klon_glo)
24      REAL lmt_bcba_glo(klon_glo)
25      REAL lmt_omff_glo(klon_glo), lmt_omnff_glo(klon_glo)
26      REAL lmt_ombb_glo(klon_glo)
27      REAL lmt_bcbbl_glo(klon_glo), lmt_bcbbh_glo(klon_glo)
28      REAL lmt_ombbl_glo(klon_glo), lmt_ombbh_glo(klon_glo)
29      REAL lmt_omnat_glo(klon_glo), lmt_omba_glo(klon_glo)
30      REAL lmt_terp_glo(klon_glo)
31!
32      INTEGER jour, i
33      INTEGER ierr
34      INTEGER nid1,nvarid
35      INTEGER debut(2),epais(2)
36c
37!      IF (jour.LT.0 .OR. jour.GT.(366-1)) THEN
38      IF (jour<0 .OR. jour>366) THEN
39         PRINT*,'Le jour demande n est pas correcte:', jour
40         print *,'JE: FORCED TO CONTINUE (emissions have
41     . to be longer than 1 year!!!! )'
42!JE         CALL ABORT
43      ENDIF
44
45!$OMP MASTER
46      IF (is_mpi_root .AND. is_omp_root) THEN
47!
48! Tranche a lire:
49      debut(1) = 1
50      debut(2) = jour
51      epais(1) = klon_glo
52!      epais(1) = klon
53      epais(2) = 1
54!
55!=======================================================================
56!                        BC EMISSIONS
57!=======================================================================
58!
59      ierr = NF_OPEN ("carbon_emissions.nc", NF_NOWRITE, nid1)
60      if (ierr/=NF_NOERR) then
61        write(6,*)' Pb d''ouverture du fichier limitbc.nc'
62        write(6,*)' ierr = ', ierr
63        call exit(1)
64      endif
65!
66! BC emissions from fossil fuel combustion
67!
68      ierr = NF_INQ_VARID (nid1, "BCFF", nvarid)
69      ierr = nf90_get_var (nid1, nvarid, lmt_bcff_glo, debut, epais)
70      IF (ierr /= NF_NOERR) THEN
71         PRINT*, 'Pb de lecture pour les sources BC'
72         CALL exit(1)
73      ENDIF
74      !print *,'lmt_bcff = ',lmt_bcff
75      !stop
76!
77! BC emissions from non fossil fuel combustion
78!
79      ierr = NF_INQ_VARID (nid1, "BCNFF", nvarid)
80      ierr = nf90_get_var (nid1, nvarid, lmt_bcnff_glo, debut, epais)
81      IF (ierr /= NF_NOERR) THEN
82         PRINT*, 'Pb de lecture pour les sources BC'
83         CALL exit(1)
84      ENDIF
85!
86! Low BC emissions from biomass burning
87!
88      ierr = NF_INQ_VARID (nid1, "BCBBL", nvarid)
89      ierr = nf90_get_var (nid1, nvarid, lmt_bcbbl_glo, debut, epais)
90      IF (ierr /= NF_NOERR) THEN
91         PRINT*, 'Pb de lecture pour les sources BC low'
92         CALL exit(1)
93      ENDIF
94!
95! High BC emissions from biomass burning
96!
97      ierr = NF_INQ_VARID (nid1, "BCBBH", nvarid)
98      ierr = nf90_get_var (nid1, nvarid, lmt_bcbbh_glo, debut, epais)
99      IF (ierr /= NF_NOERR) THEN
100         PRINT*, 'Pb de lecture pour les sources BC high'
101         CALL exit(1)
102      ENDIF
103!
104! BC emissions from ship transport
105!
106      ierr = NF_INQ_VARID (nid1, "BCBA", nvarid)
107      ierr = nf90_get_var (nid1, nvarid, lmt_bcba_glo, debut, epais)
108      IF (ierr /= NF_NOERR) THEN
109         PRINT*, 'Pb de lecture pour les sources BC'
110         CALL exit(1)
111      ENDIF
112!
113!=======================================================================
114!                        OM EMISSIONS
115!=======================================================================
116!
117
118!
119! OM emissions from fossil fuel combustion
120!
121      ierr = NF_INQ_VARID (nid1, "OMFF", nvarid)
122      ierr = nf90_get_var (nid1, nvarid, lmt_omff_glo, debut, epais)
123      IF (ierr /= NF_NOERR) THEN
124         PRINT*, 'Pb de lecture pour les sources OM'
125         CALL exit(1)
126      ENDIF
127!
128! OM emissions from non fossil fuel combustion
129!
130      ierr = NF_INQ_VARID (nid1, "OMNFF", nvarid)
131      ierr = nf90_get_var (nid1, nvarid, lmt_omnff_glo, debut, epais)
132      IF (ierr /= NF_NOERR) THEN
133         PRINT*, 'Pb de lecture pour les sources OM'
134         CALL exit(1)
135      ENDIF
136!
137! Low OM emissions from biomass burning - low
138!
139      ierr = NF_INQ_VARID (nid1, "OMBBL", nvarid)
140      ierr = nf90_get_var (nid1, nvarid, lmt_ombbl_glo, debut, epais)
141      IF (ierr /= NF_NOERR) THEN
142         PRINT*, 'Pb de lecture pour les sources OM low'
143         CALL exit(1)
144      ENDIF
145!
146! High OM emissions from biomass burning - high
147!
148      ierr = NF_INQ_VARID (nid1, "OMBBH", nvarid)
149      ierr = nf90_get_var (nid1, nvarid, lmt_ombbh_glo, debut, epais)
150      IF (ierr /= NF_NOERR) THEN
151         PRINT*, 'Pb de lecture pour les sources OM high'
152         CALL exit(1)
153      ENDIF
154!
155! High OM emissions from ship
156!
157      ierr = NF_INQ_VARID (nid1, "OMBA", nvarid)
158      ierr = nf90_get_var (nid1, nvarid, lmt_omba_glo, debut, epais)
159      IF (ierr /= NF_NOERR) THEN
160         PRINT*, 'Pb de lecture pour les sources OM ship'
161         CALL exit(1)
162      ENDIF
163!
164! Natural Terpene emissions => Natural OM emissions
165!
166      ierr = NF_INQ_VARID (nid1, "TERP", nvarid)
167      ierr = nf90_get_var (nid1, nvarid, lmt_terp_glo, debut, epais)
168      IF (ierr /= NF_NOERR) THEN
169         PRINT*, 'Pb de lecture pour les sources Terpene'
170         CALL exit(1)
171      ENDIF
172!
173      DO i=1,klon_glo
174        lmt_omnat_glo(i)  = lmt_terp_glo(i)*0.11*1.4 !-- 11% Terpene is OC
175      ENDDO
176
177      ierr = NF_CLOSE(nid1)
178!
179      PRINT*, 'Carbon sources lues pour jour: ', jour
180!      lmt_bcff(klon)=0.0
181!      lmt_bcnff(klon)=0.0
182!      lmt_omff(klon)=0.0
183!      lmt_omnff(klon)=0.0
184!      lmt_ombb(klon)=0.0
185!      lmt_bcbbl(klon)=0.0
186!      lmt_bcbbh(klon)=0.0
187!      lmt_ombbl(klon)=0.0
188!      lmt_ombbh(klon)=0.0
189!      lmt_omnat(klon)=0.0
190!      lmt_omba(klon)=0.0
191!      lmt_terp(klon)=0.0
192
193
194      ENDIF
195!$OMP END MASTER
196!$OMP BARRIER
197      call scatter( lmt_bcff_glo   , lmt_bcff )   
198      call scatter( lmt_bcnff_glo  , lmt_bcnff )
199      call scatter( lmt_bcbbl_glo  , lmt_bcbbl )
200      call scatter( lmt_bcbbh_glo  , lmt_bcbbh )
201      call scatter( lmt_bcba_glo   , lmt_bcba )
202      call scatter( lmt_omff_glo   , lmt_omff )
203      call scatter( lmt_omnff_glo  , lmt_omnff )
204      call scatter( lmt_ombbl_glo  , lmt_ombbl )
205      call scatter( lmt_ombbh_glo  , lmt_ombbh )
206      call scatter( lmt_omba_glo   , lmt_omba )
207      call scatter( lmt_terp_glo   , lmt_terp )
208      call scatter( lmt_omnat_glo  , lmt_omnat )
209
210
211
212
213
214      RETURN
215      END
Note: See TracBrowser for help on using the repository browser.