source: LMDZ6/trunk/libf/phylmd/tracco2i_mod.F90 @ 3361

Last change on this file since 3361 was 3361, checked in by oboucher, 6 years ago

Embryon of changes for interactive CO2
type_trac=co2i

File size: 5.9 KB
Line 
1MODULE tracco2i_mod
2!
3! This module does the work for the interactive CO2 tracers
4!
5CONTAINS
6
7  SUBROUTINE tracco2i(pdtphys, debutphy, &
8       xlat, xlon, pphis, pphi, &
9       t_seri, pplay, paprs, tr_seri, source)
10
11    USE dimphy
12    USE infotrac
13    USE geometry_mod, ONLY : cell_area
14    USE mod_grid_phy_lmdz
15    USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
16    USE mod_phys_lmdz_para, ONLY: gather, bcast, scatter
17    USE phys_cal_mod
18
19    IMPLICIT NONE
20
21    INCLUDE "clesphys.h"
22    INCLUDE "YOMCST.h"
23
24! Input argument
25!---------------
26    REAL,INTENT(IN)    :: pdtphys    ! Pas d'integration pour la physique (seconde)
27    LOGICAL,INTENT(IN) :: debutphy   ! le flag de l'initialisation de la physique
28
29    REAL,DIMENSION(klon),INTENT(IN)        :: xlat    ! latitudes pour chaque point
30    REAL,DIMENSION(klon),INTENT(IN)        :: xlon    ! longitudes pour chaque point
31    REAL,DIMENSION(klon),INTENT(IN)        :: pphis   ! geopotentiel du sol
32    REAL,DIMENSION(klon,klev),INTENT(IN)   :: pphi    ! geopotentiel de chaque couche
33
34    REAL,DIMENSION(klon,klev),INTENT(IN)   :: t_seri  ! Temperature
35    REAL,DIMENSION(klon,klev),INTENT(IN)   :: pplay   ! pression pour le mileu de chaque couche (en Pa)
36    REAL,DIMENSION(klon,klev+1),INTENT(IN) :: paprs   ! pression pour chaque inter-couche (en Pa)
37    REAL,DIMENSION(klon,nbtr),INTENT(INOUT):: source  ! flux de traceur [U/m2/s]
38
39! Output argument
40!----------------
41    REAL,DIMENSION(klon,klev,nbtr),INTENT(INOUT)  :: tr_seri ! Concentration Traceur [U/kgA] 
42
43! Local variables
44!----------------
45
46    INTEGER, PARAMETER :: id_CO2=1                           !--temporaire OB=> PC to be changed
47    REAL, PARAMETER    :: MCO2=44.011   !--g/mol
48    INTEGER                                 :: it, k, i
49    REAL, DIMENSION(klon,klev)              :: m_air          ! mass of air in every grid box [kg]
50    REAL, DIMENSION(klon)                   :: co2ff          ! surface fossil-fuel CO2 emissions [kg CO2/m2/s]
51    REAL, DIMENSION(klon)                   :: co2bb          ! surface biomass burning CO2 emissions [kg CO2/m2/s]
52    REAL, DIMENSION(klon_glo,klev) :: co2_glo   ! variable temporaire sur la grille global
53    REAL, DIMENSION(klon_glo,klev) :: m_air_glo ! variable temporaire sur la grille global
54
55
56    INTEGER, SAVE :: mth_pre=0
57!$OMP THREADPRIVATE(mth_pre)
58    REAL, SAVE :: RCO2_glo
59!$OMP THREADPRIVATE(RCO2_glo)
60
61    IF (is_mpi_root) THEN
62      PRINT *,'in tracco2i: date from phys_cal_mod =',year_cur,'-',mth_cur,'-',day_cur,'-',hour
63    ENDIF
64
65!--initialisation of CO2 field if not in restart file
66!--dirty way of doing, do it better later
67!--convert 280 ppm into kg CO2 / kg air
68    IF (debutphy) THEN
69      IF (MAXVAL(tr_seri(:,:,id_CO2)).LT.1.e-15) THEN
70        tr_seri(:,:,id_CO2)=280.e-6/RMD*MCO2
71      ENDIF
72    ENDIF
73
74!--calculate mass of air in every grid box in kg
75    DO i=1, klon
76    DO k=1, klev
77      m_air(i,k)=(paprs(i,k)-paprs(i,k+1))/RG*cell_area(i)
78    ENDDO
79    ENDDO
80
81!--call CO2 emission routine
82!--co2bb is zero for now
83    CALL co2_emissions(debutphy,co2ff,co2bb)
84
85!--preparing the net anthropogenic flux at the surface for mixing layer
86!--unit kg CO2 / m2 / s
87    DO i=1, klon
88      source(i,id_CO2)=co2ff(i)+co2bb(i)
89    ENDDO
90
91!--computing global mean CO2 for radiation
92!    IF (debutphy.OR.mth_cur.NE.mth_pre) THEN
93      CALL gather(tr_seri(:,:,id_CO2),co2_glo)
94      CALL gather(m_air,m_air_glo)
95!$OMP MASTER
96       IF (is_mpi_root) THEN
97         RCO2_glo=SUM(co2_glo*m_air_glo)/SUM(m_air_glo)*1.e6*RMD/MCO2
98       ENDIF
99       PRINT *,'in tracco2i: global CO2 in ppm =', RCO2_glo
100!$OMP END MASTER
101       CALL bcast(RCO2_glo)
102       mth_pre=mth_cur
103!    ENDIF
104
105  END SUBROUTINE tracco2i
106
107  SUBROUTINE co2_emissions(debutphy,co2ff,co2bb)
108
109    USE dimphy
110    USE infotrac
111    USE geometry_mod, ONLY : cell_area
112    USE mod_grid_phy_lmdz
113    USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
114    USE mod_phys_lmdz_para, ONLY: gather, scatter
115    USE phys_cal_mod
116    USE YOMCST
117
118    USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_varid, nf95_open
119    USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
120
121    IMPLICIT NONE
122
123    LOGICAL,INTENT(IN) :: debutphy
124    REAL,DIMENSION(klon),INTENT(out) :: co2ff            !  fossil-fuel CO2 emissions
125    REAL,DIMENSION(klon),INTENT(out) :: co2bb            !  biomass burning CO2 emissions
126
127! For NetCDF:
128    integer ncid_in  ! IDs for input files
129    integer varid, ncerr
130
131    INTEGER :: n_glo, n_month
132    REAL, POINTER:: vector(:), time(:)
133    REAL,ALLOCATABLE       :: flx_co2_glo(:,:) !  fossil-fuel CO2
134    REAL,ALLOCATABLE, SAVE :: flx_co2(:,:)     !  fossil-fuel CO2
135!$OMP THREADPRIVATE(flx_co2)
136
137  IF (debutphy) THEN
138
139  ALLOCATE(flx_co2(klon,12))
140
141!$OMP MASTER
142  IF (is_mpi_root) THEN
143    ! ... Open the file
144    CALL nf95_open("sflx_lmdz_co2.nc", nf90_nowrite, ncid_in)
145
146    CALL nf95_inq_varid(ncid_in, "vector", varid)
147    CALL nf95_gw_var(ncid_in, varid, vector)
148    n_glo = size(vector)
149    IF (n_glo.NE.klon_glo) THEN
150       print *,'Le nombre de points n est pas egal a klon_glo'
151       STOP
152    ENDIF
153
154    CALL nf95_inq_varid(ncid_in, "time", varid)
155    CALL nf95_gw_var(ncid_in, varid, time)
156    n_month = size(time)
157    IF (n_month.NE.12) THEN
158       print *,'Le nombre de month n est pas egal a 12'
159       STOP
160    ENDIF
161
162    IF (.NOT.ALLOCATED(flx_co2_glo)) ALLOCATE(flx_co2_glo(n_glo,n_month))
163
164!--reading flx_co2
165    CALL nf95_inq_varid(ncid_in, "flx_co2", varid)
166    ncerr = nf90_get_var(ncid_in, varid, flx_co2_glo)
167
168    CALL nf95_close(ncid_in)
169  ENDIF
170!$OMP END MASTER
171
172!--scatter on all proc
173  CALL scatter(flx_co2_glo,flx_co2)
174
175!$OMP MASTER
176  IF (is_mpi_root) THEN
177     DEALLOCATE(flx_co2_glo)
178  ENDIF
179!$OMP END MASTER
180
181  ENDIF !--end debuthy
182
183!---select the correct month
184  IF (mth_cur.LT.1.OR.mth_cur.GT.12) THEN
185    print *,'probleme avec le mois dans co2_ini =', mth_cur
186  ENDIF
187  co2ff(:) = flx_co2(:,mth_cur)
188  co2bb(:) = 0.0
189
190  END SUBROUTINE co2_emissions
191
192END MODULE tracco2i_mod
Note: See TracBrowser for help on using the repository browser.