source: CONFIG/publications/ICOLMDZORINCA_CO2_Transport_GMD_2023/INCA/build/ppsrc/INCA_SRC/dvel_inti.f90 @ 6610

Last change on this file since 6610 was 6610, checked in by acosce, 10 months ago

INCA used for ICOLMDZORINCA_CO2_Transport_GMD_2023

File size: 4.4 KB
Line 
1
2
3
4
5
6
7
8
9
10
11
12!$Id: dvel_inti.F90 104 2008-12-23 10:28:51Z acosce $
13!! =========================================================================
14!! INCA - INteraction with Chemistry and Aerosols
15!!
16!! Copyright Laboratoire des Sciences du Climat et de l'Environnement (LSCE)
17!!           Unite mixte CEA-CNRS-UVSQ
18!!
19!! Contributors to this INCA subroutine:
20!!
21!! Didier Hauglustaine, LSCE, hauglustaine@cea.fr
22!!
23!! Anne Cozic, LSCE, anne.cozic@cea.fr
24!! Yann Meurdesoif, LSCE, yann.meurdesoif@cea.fr
25!!
26!! This software is a computer program whose purpose is to simulate the
27!! atmospheric gas phase and aerosol composition. The model is designed to be
28!! used within a transport model or a general circulation model. This version
29!! of INCA was designed to be coupled to the LMDz GCM. LMDz-INCA accounts
30!! for emissions, transport (resolved and sub-grid scale), photochemical
31!! transformations, and scavenging (dry deposition and washout) of chemical
32!! species and aerosols interactively in the GCM. Several versions of the INCA
33!! model are currently used depending on the envisaged applications with the
34!! chemistry-climate model.
35!!
36!! This software is governed by the CeCILL  license under French law and
37!! abiding by the rules of distribution of free software.  You can  use,
38!! modify and/ or redistribute the software under the terms of the CeCILL
39!! license as circulated by CEA, CNRS and INRIA at the following URL
40!! "http://www.cecill.info".
41!!
42!! As a counterpart to the access to the source code and  rights to copy,
43!! modify and redistribute granted by the license, users are provided only
44!! with a limited warranty  and the software's author,  the holder of the
45!! economic rights,  and the successive licensors  have only  limited
46!! liability.
47!!
48!! In this respect, the user's attention is drawn to the risks associated
49!! with loading,  using,  modifying and/or developing or reproducing the
50!! software by the user in light of its specific status of free software,
51!! that may mean  that it is complicated to manipulate,  and  that  also
52!! therefore means  that it is reserved for developers  and  experienced
53!! professionals having in-depth computer knowledge. Users are therefore
54!! encouraged to load and test the software's suitability as regards their
55!! requirements in conditions enabling the security of their systems and/or
56!! data to be ensured and,  more generally, to use and operate it in the
57!! same conditions as regards security.
58!!
59!! The fact that you are presently reading this means that you have had
60!! knowledge of the CeCILL license and that you accept its terms.
61!! =========================================================================
62
63
64
65SUBROUTINE XIOS_NPP_LANDUSE_INTI()
66  !-----------------------------------------------------------------------
67  !     ... Read the NPP data set
68  ! Didier Hauglustaine, IPSL, 2000.
69  !-----------------------------------------------------------------------
70 
71  USE NPP_INT
72  USE INCA_DIM
73  USE MOD_INCA_PARA
74  use MOD_INCA_MPI_DATA, ONLY : ntime_npp, ntype_landuse
75  USE XIOS_INCA
76  USE DRYDEP_PARAMETERS, ONLY : n_land_type
77  USE DRYDEP_ARRAYS, ONLY : fraction_landuse
78
79  IMPLICIT NONE
80
81  INCLUDE 'netcdf.inc'
82
83  !----------------------------------------------------------------------
84  !       ... Dummy args
85  !----------------------------------------------------------------------
86 
87  !----------------------------------------------------------------------
88  !       ... Local variables
89  !----------------------------------------------------------------------
90  INTEGER :: i
91  INTEGER :: iret
92  INTEGER :: varid
93  INTEGER :: error
94 
95  REAL, ALLOCATABLE, DIMENSION (:,:) :: wrk
96  REAL, ALLOCATABLE, DIMENSION (:,:) :: npp_glo
97 
98  !--------------------------------------------------------------------------------
99  !       ... Open the file and read NPP
100  !--------------------------------------------------------------------------------
101  CALL xios_inca_change_context("inca")
102
103
104  ALLOCATE(npp(PLON,ntime_npp), STAT=error)
105  ALLOCATE(daysnpp(ntime_npp), STAT=error) 
106  CALL xios_inca_recv_field("npp_interp", npp) 
107  CALL xios_inca_recv_field_glo("timenpp_read", daysnpp) 
108 
109
110  ALLOCATE(fraction_landuse(PLON,PLAT,ntype_landuse), STAT=error)
111  ALLOCATE(wrk(PLON,ntype_landuse), STAT=error) 
112  CALL xios_inca_recv_field("landuse_interp", wrk(:,:) ) 
113  fraction_landuse(:,1,:) = wrk(:,:)
114
115  CALL xios_inca_change_context("LMDZ")
116
117
118END SUBROUTINE XIOS_NPP_LANDUSE_INTI
Note: See TracBrowser for help on using the repository browser.