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

Last change on this file since 3448 was 3435, checked in by Laurent Fairhead, 6 years ago

"Historic" :-) commit merging the physics branch used for DYNAMICO with the LMDZ trunk.
The same physics branch can now be used seamlessly with the traditional lon-lat LMDZ
dynamical core and DYNAMICO.
Testing consisted in running a lon-lat LMDZ bucket simulation with the NPv6.1 physics package
with the original trunk sources and the merged sources. Tests were succesful in the sense that
numeric continuity was preserved in the restart files from both simulation. Further tests
included running both versions of the physics codes for one year in a LMDZOR setting in which
the restart files also came out identical.

Caution:

  • as the physics package now manages unstructured grids, grid information needs to be transmitted

to the surface scheme ORCHIDEE. This means that the interface defined in surf_land_orchidee_mod.F90
is only compatible with ORCHIDEE version orchidee2.1 and later versions. If previous versions of
ORCHIDEE need to be used, the CPP key ORCHIDEE_NOUNSTRUCT needs to be set at compilation time.
This is done automatically if makelmdz/makelmdz_fcm are called with the veget orchidee2.0 switch

  • due to a limitation in XIOS, the time at which limit conditions will be read in by DYNAMICO will be

delayed by one physic timestep with respect to the time it is read in by the lon-lat model. This is caused
by the line

IF (MOD(itime-1, lmt_pas) == 0 .OR. (jour_lu /= jour .AND. grid_type /= unstructured)) THEN ! time to read

in limit_read_mod.F90

Work still needed on COSP integration and XML files for DYNAMICO

EM, YM, LF

File size: 8.0 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_phy
13    USE geometry_mod, ONLY : cell_area
14    USE carbon_cycle_mod, ONLY : nbcf_in, fields_in, cfname_in, fco2_ocn_day, fco2_ff, fco2_bb
15    USE mod_grid_phy_lmdz
16    USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
17    USE mod_phys_lmdz_para, ONLY: gather, bcast, scatter
18    USE phys_cal_mod
19
20    IMPLICIT NONE
21
22    INCLUDE "clesphys.h"
23    INCLUDE "YOMCST.h"
24
25! Input argument
26!---------------
27    REAL,INTENT(IN)    :: pdtphys    ! Pas d'integration pour la physique (seconde)
28    LOGICAL,INTENT(IN) :: debutphy   ! le flag de l'initialisation de la physique
29
30    REAL,DIMENSION(klon),INTENT(IN)        :: xlat    ! latitudes pour chaque point
31    REAL,DIMENSION(klon),INTENT(IN)        :: xlon    ! longitudes pour chaque point
32    REAL,DIMENSION(klon),INTENT(IN)        :: pphis   ! geopotentiel du sol
33    REAL,DIMENSION(klon,klev),INTENT(IN)   :: pphi    ! geopotentiel de chaque couche
34
35    REAL,DIMENSION(klon,klev),INTENT(IN)   :: t_seri  ! Temperature
36    REAL,DIMENSION(klon,klev),INTENT(IN)   :: pplay   ! pression pour le mileu de chaque couche (en Pa)
37    REAL,DIMENSION(klon,klev+1),INTENT(IN) :: paprs   ! pression pour chaque inter-couche (en Pa)
38    REAL,DIMENSION(klon,nbtr),INTENT(INOUT):: source  ! flux de traceur [U/m2/s]
39
40! Output argument
41!----------------
42    REAL,DIMENSION(klon,klev,nbtr),INTENT(INOUT)  :: tr_seri ! Concentration Traceur [U/kgA] 
43
44! Local variables
45!----------------
46
47    INTEGER, PARAMETER :: id_CO2=1              !--temporaire OB -- to be changed
48    INTEGER                        :: it, k, i, nb
49    REAL, DIMENSION(klon,klev)     :: m_air     ! mass of air in every grid box [kg]
50    REAL, DIMENSION(klon)          :: co2land   ! surface land CO2 emissions [kg CO2/m2/s]
51    REAL, DIMENSION(klon)          :: co2ocean  ! surface ocean 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*RMCO2
71      ENDIF
72    ENDIF
73
74!--calculate mass of air in every grid box in kg air
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!--unit kg CO2 m-2 s-1
84    CALL co2_emissions(debutphy)
85
86!--retrieving land and ocean CO2 flux
87!--fCO2_nep comes in unit of g CO2 m-2 dt_stomate-1
88!--this needs to be changed in ORCHIDEE
89    co2land(:)=0.0
90    co2ocean(:)=0.0
91    DO nb=1, nbcf_in
92      IF (cfname_in(nb) == "fCO2_nep" )   co2land(:)=fields_in(:,nb)*RMCO2/RMC/86400./1000.
93      !!IF (cfname_in(nb) == "fCO2_fgco2" ) co2ocean(:)=fco2_ocn_day(:) !--for now
94    ENDDO
95
96!--preparing the net anthropogenic flux at the surface for mixing layer
97!--unit kg CO2 / m2 / s
98    source(:,id_CO2)=fco2_ff(:)+fco2_bb(:)+co2land(:)+co2ocean(:)
99
100!--computing global mean CO2 for radiation
101!--every timestep for now but enough every month
102!    IF (debutphy.OR.mth_cur.NE.mth_pre) THEN
103      CALL gather(tr_seri(:,:,id_CO2),co2_glo)
104      CALL gather(m_air,m_air_glo)
105!$OMP MASTER
106!--conversion from kg CO2/kg air into ppm
107       IF (is_mpi_root) THEN
108         RCO2_glo=SUM(co2_glo*m_air_glo)/SUM(m_air_glo)*1.e6*RMD/RMCO2
109       ENDIF
110       PRINT *,'toto in tracco2i: global CO2 in ppm =', RCO2_glo
111!$OMP END MASTER
112       CALL bcast(RCO2_glo)
113       mth_pre=mth_cur
114!    ENDIF
115
116  END SUBROUTINE tracco2i
117
118  SUBROUTINE co2_emissions(debutphy)
119
120    USE dimphy
121    USE infotrac_phy
122    USE geometry_mod, ONLY : cell_area
123    USE mod_grid_phy_lmdz
124    USE mod_phys_lmdz_mpi_data, ONLY: is_mpi_root
125    USE mod_phys_lmdz_para, ONLY: gather, scatter
126    USE phys_cal_mod
127
128    USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_varid, nf95_open
129    USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
130
131    USE carbon_cycle_mod, ONLY : fco2_ff, fco2_bb
132
133    IMPLICIT NONE
134
135    INCLUDE "YOMCST.h"
136    LOGICAL,INTENT(IN) :: debutphy
137
138! For NetCDF:
139    INTEGER ncid_in  ! IDs for input files
140    INTEGER varid, ncerr
141
142    INTEGER :: n_glo, n_month
143    REAL, POINTER:: vector(:), time(:)
144    REAL,ALLOCATABLE       :: flx_co2ff_glo(:,:) !  fossil-fuel CO2
145    REAL,ALLOCATABLE       :: flx_co2bb_glo(:,:) !  biomass-burning CO2
146    REAL,ALLOCATABLE, SAVE :: flx_co2ff(:,:)     !  fossil-fuel CO2
147    REAL,ALLOCATABLE, SAVE :: flx_co2bb(:,:)     !  biomass-burning CO2
148!$OMP THREADPRIVATE(flx_co2ff,flx_co2bb)
149
150!! may be controlled via the .def later on
151!! also co2bb for now comes from ORCHIDEE
152    LOGICAL, PARAMETER :: readco2ff=.TRUE., readco2bb=.FALSE.
153
154    IF (debutphy) THEN
155
156    ALLOCATE(flx_co2ff(klon,12))
157    ALLOCATE(flx_co2bb(klon,12))
158
159!$OMP MASTER
160    IF (is_mpi_root) THEN
161   
162      IF (.NOT.ALLOCATED(flx_co2ff_glo)) ALLOCATE(flx_co2ff_glo(klon_glo,12))
163      IF (.NOT.ALLOCATED(flx_co2bb_glo)) ALLOCATE(flx_co2bb_glo(klon_glo,12))
164
165!--reading CO2 fossil fuel emissions
166      IF (readco2ff) THEN
167
168        ! ... Open the COZff file
169        CALL nf95_open("sflx_lmdz_co2_ff.nc", nf90_nowrite, ncid_in)
170
171        CALL nf95_inq_varid(ncid_in, "vector", varid)
172        CALL nf95_gw_var(ncid_in, varid, vector)
173        n_glo = size(vector)
174        IF (n_glo.NE.klon_glo) THEN
175           PRINT *,'sflx_lmdz_co2_ff: le nombre de points n est pas egal a klon_glo'
176           STOP
177        ENDIF
178
179        CALL nf95_inq_varid(ncid_in, "time", varid)
180        CALL nf95_gw_var(ncid_in, varid, time)
181        n_month = size(time)
182        IF (n_month.NE.12) THEN
183           PRINT *,'sflx_lmdz_co2_ff: le nombre de month n est pas egal a 12'
184           STOP
185        ENDIF
186
187!--reading flx_co2 for fossil fuel
188        CALL nf95_inq_varid(ncid_in, "flx_co2", varid)
189        ncerr = nf90_get_var(ncid_in, varid, flx_co2ff_glo)
190
191        CALL nf95_close(ncid_in)
192   
193      ELSE  !--co2ff not to be read
194        flx_co2ff_glo(:,:)=0.0
195      ENDIF
196
197!--reading CO2 biomass burning emissions
198      IF (readco2bb) THEN
199
200      ! ... Open the CO2bb file
201      CALL nf95_open("sflx_lmdz_co2_bb.nc", nf90_nowrite, ncid_in)
202
203      CALL nf95_inq_varid(ncid_in, "vector", varid)
204      CALL nf95_gw_var(ncid_in, varid, vector)
205      n_glo = size(vector)
206      IF (n_glo.NE.klon_glo) THEN
207         PRINT *,'sflx_lmdz_co2_bb: le nombre de points n est pas egal a klon_glo'
208         STOP
209      ENDIF
210
211      CALL nf95_inq_varid(ncid_in, "time", varid)
212      CALL nf95_gw_var(ncid_in, varid, time)
213      n_month = size(time)
214      IF (n_month.NE.12) THEN
215         PRINT *,'sflx_lmdz_co2_bb: le nombre de month n est pas egal a 12'
216         STOP
217      ENDIF
218
219!--reading flx_co2 for biomass burning
220      CALL nf95_inq_varid(ncid_in, "flx_co2", varid)
221      ncerr = nf90_get_var(ncid_in, varid, flx_co2bb_glo)
222
223      CALL nf95_close(ncid_in)
224   
225      ELSE  !--co2bb not to be read
226        flx_co2bb_glo(:,:)=0.0
227      ENDIF
228
229    ENDIF
230!$OMP END MASTER
231
232!--scatter on all proc
233    CALL scatter(flx_co2ff_glo,flx_co2ff)
234    CALL scatter(flx_co2bb_glo,flx_co2bb)
235
236!$OMP MASTER
237    IF (is_mpi_root) THEN
238       DEALLOCATE(flx_co2ff_glo)
239       DEALLOCATE(flx_co2bb_glo)
240    ENDIF
241!$OMP END MASTER
242
243  ENDIF !--end debuthy
244
245!---select the correct month
246  IF (mth_cur.LT.1.OR.mth_cur.GT.12) THEN
247    PRINT *,'probleme avec le mois dans co2_ini =', mth_cur
248  ENDIF
249  IF (.NOT.ALLOCATED(fco2_ff)) ALLOCATE(fco2_ff(klon))
250  IF (.NOT.ALLOCATED(fco2_bb)) ALLOCATE(fco2_bb(klon))
251  fco2_ff(:) = flx_co2ff(:,mth_cur)
252  fco2_bb(:) = flx_co2bb(:,mth_cur)
253
254  END SUBROUTINE co2_emissions
255
256END MODULE tracco2i_mod
Note: See TracBrowser for help on using the repository browser.