source: LMDZ6/trunk/libf/phylmd/Dust/condsurfc_new.f90 @ 5284

Last change on this file since 5284 was 5271, checked in by abarral, 4 days ago

Move dimensions.h into a module
Nb: doesn't compile yet

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