source: LMDZ6/branches/Amaury_dev/libf/phylmd/Dust/condsurfc_new.f90 @ 5160

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

Put .h into modules

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 lmdz_grid_phy
6  USE lmdz_phys_para
7  USE dimphy
8  USE netcdf, ONLY: nf90_get_var, nf90_close, nf90_noerr, nf90_inq_varid, nf90_open, nf90_nowrite
9  USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
10  IMPLICIT 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<0 .OR. jour>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/=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, lmt_bcff_glo, debut, epais)
71    IF (ierr /= nf90_noerr) THEN
72      PRINT*, 'Pb de lecture pour les sources BC'
73      CALL exit(1)
74    ENDIF
75    !PRINT *,'lmt_bcff = ',lmt_bcff
76    !stop
77
78    ! BC emissions from non fossil fuel combustion
79
80    ierr = nf90_inq_varid (nid1, "BCNFF", nvarid)
81    ierr = nf90_get_var (nid1, nvarid, lmt_bcnff_glo, debut, epais)
82    IF (ierr /= nf90_noerr) THEN
83      PRINT*, 'Pb de lecture pour les sources BC'
84      CALL exit(1)
85    ENDIF
86
87    ! Low BC emissions from biomass burning
88
89    ierr = nf90_inq_varid (nid1, "BCBBL", nvarid)
90    ierr = nf90_get_var (nid1, nvarid, lmt_bcbbl_glo, debut, epais)
91    IF (ierr /= nf90_noerr) THEN
92      PRINT*, 'Pb de lecture pour les sources BC low'
93      CALL exit(1)
94    ENDIF
95
96    ! High BC emissions from biomass burning
97
98    ierr = nf90_inq_varid (nid1, "BCBBH", nvarid)
99    ierr = nf90_get_var (nid1, nvarid, lmt_bcbbh_glo, debut, epais)
100    IF (ierr /= nf90_noerr) THEN
101      PRINT*, 'Pb de lecture pour les sources BC high'
102      CALL exit(1)
103    ENDIF
104
105    ! BC emissions from ship transport
106
107    ierr = nf90_inq_varid (nid1, "BCBA", nvarid)
108    ierr = nf90_get_var (nid1, nvarid, lmt_bcba_glo, debut, epais)
109    IF (ierr /= nf90_noerr) THEN
110      PRINT*, 'Pb de lecture pour les sources BC'
111      CALL exit(1)
112    ENDIF
113
114    !=======================================================================
115    ! OM EMISSIONS
116    !=======================================================================
117
118    ! OM emissions from fossil fuel combustion
119
120    ierr = nf90_inq_varid (nid1, "OMFF", nvarid)
121    ierr = nf90_get_var (nid1, nvarid, lmt_omff_glo, debut, epais)
122    IF (ierr /= nf90_noerr) THEN
123      PRINT*, 'Pb de lecture pour les sources OM'
124      CALL exit(1)
125    ENDIF
126
127    ! OM emissions from non fossil fuel combustion
128
129    ierr = nf90_inq_varid (nid1, "OMNFF", nvarid)
130    ierr = nf90_get_var (nid1, nvarid, lmt_omnff_glo, debut, epais)
131    IF (ierr /= nf90_noerr) THEN
132      PRINT*, 'Pb de lecture pour les sources OM'
133      CALL exit(1)
134    ENDIF
135
136    ! Low OM emissions from biomass burning - low
137
138    ierr = nf90_inq_varid (nid1, "OMBBL", nvarid)
139    ierr = nf90_get_var (nid1, nvarid, lmt_ombbl_glo, debut, epais)
140    IF (ierr /= nf90_noerr) THEN
141      PRINT*, 'Pb de lecture pour les sources OM low'
142      CALL exit(1)
143    ENDIF
144
145    ! High OM emissions from biomass burning - high
146
147    ierr = nf90_inq_varid (nid1, "OMBBH", nvarid)
148    ierr = nf90_get_var (nid1, nvarid, lmt_ombbh_glo, debut, epais)
149    IF (ierr /= nf90_noerr) THEN
150      PRINT*, 'Pb de lecture pour les sources OM high'
151      CALL exit(1)
152    ENDIF
153
154    ! High OM emissions from ship
155
156    ierr = nf90_inq_varid (nid1, "OMBA", nvarid)
157    ierr = nf90_get_var (nid1, nvarid, lmt_omba_glo, debut, epais)
158    IF (ierr /= nf90_noerr) THEN
159      PRINT*, 'Pb de lecture pour les sources OM ship'
160      CALL exit(1)
161    ENDIF
162
163    ! Natural Terpene emissions => Natural OM emissions
164
165    ierr = nf90_inq_varid (nid1, "TERP", nvarid)
166    ierr = nf90_get_var (nid1, nvarid, lmt_terp_glo, debut, epais)
167    IF (ierr /= nf90_noerr) THEN
168      PRINT*, 'Pb de lecture pour les sources Terpene'
169      CALL exit(1)
170    ENDIF
171
172    DO i = 1, klon_glo
173      lmt_omnat_glo(i) = lmt_terp_glo(i) * 0.11 * 1.4 !-- 11% Terpene is OC
174    ENDDO
175
176    ierr = nf90_close(nid1)
177
178    PRINT*, 'Carbon sources lues pour jour: ', jour
179    ! lmt_bcff(klon)=0.0
180    ! lmt_bcnff(klon)=0.0
181    ! lmt_omff(klon)=0.0
182    ! lmt_omnff(klon)=0.0
183    ! lmt_ombb(klon)=0.0
184    ! lmt_bcbbl(klon)=0.0
185    ! lmt_bcbbh(klon)=0.0
186    ! lmt_ombbl(klon)=0.0
187    ! lmt_ombbh(klon)=0.0
188    ! lmt_omnat(klon)=0.0
189    ! lmt_omba(klon)=0.0
190    ! lmt_terp(klon)=0.0
191
192  ENDIF
193  !$OMP END MASTER
194  !$OMP BARRIER
195  CALL scatter(lmt_bcff_glo, lmt_bcff)
196  CALL scatter(lmt_bcnff_glo, lmt_bcnff)
197  CALL scatter(lmt_bcbbl_glo, lmt_bcbbl)
198  CALL scatter(lmt_bcbbh_glo, lmt_bcbbh)
199  CALL scatter(lmt_bcba_glo, lmt_bcba)
200  CALL scatter(lmt_omff_glo, lmt_omff)
201  CALL scatter(lmt_omnff_glo, lmt_omnff)
202  CALL scatter(lmt_ombbl_glo, lmt_ombbl)
203  CALL scatter(lmt_ombbh_glo, lmt_ombbh)
204  CALL scatter(lmt_omba_glo, lmt_omba)
205  CALL scatter(lmt_terp_glo, lmt_terp)
206  CALL scatter(lmt_omnat_glo, lmt_omnat)
207
208
209END SUBROUTINE condsurfc_new
Note: See TracBrowser for help on using the repository browser.