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

Last change on this file since 5105 was 5105, checked in by abarral, 8 weeks ago

Replace 1DUTILS.h by module lmdz_1dutils.f90
Replace 1DConv.h by module lmdz_old_1dconv.f90 (it's only used by old_* files)
Convert *.F to *.f90
Fix gradsdef.h formatting
Remove unnecessary "RETURN" at the end of functions/subroutines

File size: 6.3 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  IMPLICIT none
10
11  ! Lire les conditions aux limites du modele pour la chimie.
12  ! --------------------------------------------------------
13
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)
22
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)
36
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 = nf90_open ("carbon_emissions.nc", nf90_nowrite, nid1)
60    if (ierr/=nf90_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 = nf90_inq_varid (nid1, "BCFF", nvarid)
69    ierr = nf90_get_var (nid1, nvarid, lmt_bcff_glo, debut, epais)
70    IF (ierr /= nf90_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 = nf90_inq_varid (nid1, "BCNFF", nvarid)
80    ierr = nf90_get_var (nid1, nvarid, lmt_bcnff_glo, debut, epais)
81    IF (ierr /= nf90_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 = nf90_inq_varid (nid1, "BCBBL", nvarid)
89    ierr = nf90_get_var (nid1, nvarid, lmt_bcbbl_glo, debut, epais)
90    IF (ierr /= nf90_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 = nf90_inq_varid (nid1, "BCBBH", nvarid)
98    ierr = nf90_get_var (nid1, nvarid, lmt_bcbbh_glo, debut, epais)
99    IF (ierr /= nf90_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 = nf90_inq_varid (nid1, "BCBA", nvarid)
107    ierr = nf90_get_var (nid1, nvarid, lmt_bcba_glo, debut, epais)
108    IF (ierr /= nf90_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    ! OM emissions from fossil fuel combustion
118
119    ierr = nf90_inq_varid (nid1, "OMFF", nvarid)
120    ierr = nf90_get_var (nid1, nvarid, lmt_omff_glo, debut, epais)
121    IF (ierr /= nf90_noerr) THEN
122      PRINT*, 'Pb de lecture pour les sources OM'
123      CALL exit(1)
124    ENDIF
125
126    ! OM emissions from non fossil fuel combustion
127
128    ierr = nf90_inq_varid (nid1, "OMNFF", nvarid)
129    ierr = nf90_get_var (nid1, nvarid, lmt_omnff_glo, debut, epais)
130    IF (ierr /= nf90_noerr) THEN
131      PRINT*, 'Pb de lecture pour les sources OM'
132      CALL exit(1)
133    ENDIF
134
135    ! Low OM emissions from biomass burning - low
136
137    ierr = nf90_inq_varid (nid1, "OMBBL", nvarid)
138    ierr = nf90_get_var (nid1, nvarid, lmt_ombbl_glo, debut, epais)
139    IF (ierr /= nf90_noerr) THEN
140      PRINT*, 'Pb de lecture pour les sources OM low'
141      CALL exit(1)
142    ENDIF
143
144    ! High OM emissions from biomass burning - high
145
146    ierr = nf90_inq_varid (nid1, "OMBBH", nvarid)
147    ierr = nf90_get_var (nid1, nvarid, lmt_ombbh_glo, debut, epais)
148    IF (ierr /= nf90_noerr) THEN
149      PRINT*, 'Pb de lecture pour les sources OM high'
150      CALL exit(1)
151    ENDIF
152
153    ! High OM emissions from ship
154
155    ierr = nf90_inq_varid (nid1, "OMBA", nvarid)
156    ierr = nf90_get_var (nid1, nvarid, lmt_omba_glo, debut, epais)
157    IF (ierr /= nf90_noerr) THEN
158      PRINT*, 'Pb de lecture pour les sources OM ship'
159      CALL exit(1)
160    ENDIF
161
162    ! Natural Terpene emissions => Natural OM emissions
163
164    ierr = nf90_inq_varid (nid1, "TERP", nvarid)
165    ierr = nf90_get_var (nid1, nvarid, lmt_terp_glo, debut, epais)
166    IF (ierr /= nf90_noerr) THEN
167      PRINT*, 'Pb de lecture pour les sources Terpene'
168      CALL exit(1)
169    ENDIF
170
171    DO i = 1, klon_glo
172      lmt_omnat_glo(i) = lmt_terp_glo(i) * 0.11 * 1.4 !-- 11% Terpene is OC
173    ENDDO
174
175    ierr = nf90_close(nid1)
176
177    PRINT*, 'Carbon sources lues pour jour: ', jour
178    ! lmt_bcff(klon)=0.0
179    ! lmt_bcnff(klon)=0.0
180    ! lmt_omff(klon)=0.0
181    ! lmt_omnff(klon)=0.0
182    ! lmt_ombb(klon)=0.0
183    ! lmt_bcbbl(klon)=0.0
184    ! lmt_bcbbh(klon)=0.0
185    ! lmt_ombbl(klon)=0.0
186    ! lmt_ombbh(klon)=0.0
187    ! lmt_omnat(klon)=0.0
188    ! lmt_omba(klon)=0.0
189    ! lmt_terp(klon)=0.0
190
191  ENDIF
192  !$OMP END MASTER
193  !$OMP BARRIER
194  CALL scatter(lmt_bcff_glo, lmt_bcff)
195  CALL scatter(lmt_bcnff_glo, lmt_bcnff)
196  CALL scatter(lmt_bcbbl_glo, lmt_bcbbl)
197  CALL scatter(lmt_bcbbh_glo, lmt_bcbbh)
198  CALL scatter(lmt_bcba_glo, lmt_bcba)
199  CALL scatter(lmt_omff_glo, lmt_omff)
200  CALL scatter(lmt_omnff_glo, lmt_omnff)
201  CALL scatter(lmt_ombbl_glo, lmt_ombbl)
202  CALL scatter(lmt_ombbh_glo, lmt_ombbh)
203  CALL scatter(lmt_omba_glo, lmt_omba)
204  CALL scatter(lmt_terp_glo, lmt_terp)
205  CALL scatter(lmt_omnat_glo, lmt_omnat)
206
207
208END SUBROUTINE condsurfc_new
Note: See TracBrowser for help on using the repository browser.