source: CONFIG/publications/ICOLMDZORINCA_CO2_Transport_GMD_2023/INCA/build/ppsrc/INCA_PARA/init_inca_para.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.8 KB
Line 
1
2
3
4
5
6
7
8
9
10
11
12!$Id: init_inca_para.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!!
22!! Anne Cozic, LSCE, anne.cozic@cea.fr
23!! Yann Meurdesoif, LSCE, yann.meurdesoif@cea.fr
24!!
25!! This software is a computer program whose purpose is to simulate the
26!! atmospheric gas phase and aerosol composition. The model is designed to be
27!! used within a transport model or a general circulation model. This version
28!! of INCA was designed to be coupled to the LMDz GCM. LMDz-INCA accounts
29!! for emissions, transport (resolved and sub-grid scale), photochemical
30!! transformations, and scavenging (dry deposition and washout) of chemical
31!! species and aerosols interactively in the GCM. Several versions of the INCA
32!! model are currently used depending on the envisaged applications with the
33!! chemistry-climate model.
34!!
35!! This software is governed by the CeCILL  license under French law and
36!! abiding by the rules of distribution of free software.  You can  use,
37!! modify and/ or redistribute the software under the terms of the CeCILL
38!! license as circulated by CEA, CNRS and INRIA at the following URL
39!! "http://www.cecill.info".
40!!
41!! As a counterpart to the access to the source code and  rights to copy,
42!! modify and redistribute granted by the license, users are provided only
43!! with a limited warranty  and the software's author,  the holder of the
44!! economic rights,  and the successive licensors  have only  limited
45!! liability.
46!!
47!! In this respect, the user's attention is drawn to the risks associated
48!! with loading,  using,  modifying and/or developing or reproducing the
49!! software by the user in light of its specific status of free software,
50!! that may mean  that it is complicated to manipulate,  and  that  also
51!! therefore means  that it is reserved for developers  and  experienced
52!! professionals having in-depth computer knowledge. Users are therefore
53!! encouraged to load and test the software's suitability as regards their
54!! requirements in conditions enabling the security of their systems and/or
55!! data to be ensured and,  more generally, to use and operate it in the
56!! same conditions as regards security.
57!!
58!! The fact that you are presently reading this means that you have had
59!! knowledge of the CeCILL license and that you accept its terms.
60!! =========================================================================
61
62
63SUBROUTINE INIT_INCA_PARA( &
64   iim      , &
65   jjp1     , &
66   llm      , &
67   nbp      , &
68   nb_proc  , &
69   distrib  , &
70   nvertex_lmdz, &
71   grid_type_lmdz, &
72   COMM_LMDZ)
73
74
75  USE MOD_INCA_PARA, mpi_root_x=>mpi_root
76  USE MOD_GRID_INCA
77  USE PRINT_INCA
78  USE xios
79
80  IMPLICIT NONE
81
82  include 'mpif.h'
83
84  INTEGER, INTENT(in) :: iim
85  INTEGER, INTENT(in) :: jjp1
86  INTEGER, INTENT(in) :: llm
87  INTEGER, INTENT(in) :: nbp
88  INTEGER, INTENT(in) :: nb_proc
89  INTEGER, INTENT(in) :: distrib(0:nb_proc-1)
90  INTEGER, INTENT(in) :: nvertex_lmdz
91  INTEGER, INTENT(in) :: grid_type_lmdz
92  INTEGER, INTENT(in) :: comm_lmdz
93  INTEGER :: index(nbp)
94  INTEGER :: pos,i
95  CHARACTER(len=*),PARAMETER      :: id="client"           !! Id for initialization of ORCHIDEE in 1
96  integer :: xios_comm
97  iim_glo=iim
98  jjm_glo=jjp1
99  iim_g=iim_glo
100  jjm_g=jjm_glo
101  nbp_glo=iim*jjp1-2*(iim-1)
102
103
104  nvertex = nvertex_lmdz
105
106
107  grid_type = grid_type_lmdz
108
109
110  CALL Init_mod_inca_para(iim,jjp1,llm,nb_proc,distrib,COMM_LMDZ)
111
112
113  ALLOCATE(nbp_para_nb(0:mpi_size-1))
114  ALLOCATE(nbp_para_begin(0:mpi_size-1))
115  ALLOCATE(nbp_para_end(0:mpi_size-1))
116
117  DO i=0,mpi_size-1
118     nbp_para_nb(i)=distrib(i)
119  ENDDO
120  nbp_para_begin(0)=1
121  nbp_para_end(0)=nbp_para_nb(0)
122  DO i=1,mpi_size-1
123     nbp_para_begin(i)=nbp_para_end(i-1)+1
124     nbp_para_end(i)=nbp_para_begin(i)+nbp_para_nb(i)-1
125  ENDDO
126
127  nbp_mpi=nbp_para_nb(mpi_rank)
128
129  index(1)=1
130  pos=iim_glo+1
131  DO i=2,nbp_glo
132     index(i)=pos
133     pos=pos+1
134  ENDDO
135
136  CALL init_inca_io_para
137
138
139END SUBROUTINE INIT_INCA_PARA
140
141SUBROUTINE INIT_INCA_IO_PARA
142
143  USE IOIPSL
144  USE INCA_DATA_PARA
145
146  IMPLICIT NONE
147
148  INTEGER,DIMENSION(2) :: ddid
149  INTEGER,DIMENSION(2) :: dsg
150  INTEGER,DIMENSION(2) :: dsl
151  INTEGER,DIMENSION(2) :: dpf
152  INTEGER,DIMENSION(2) :: dpl
153  INTEGER,DIMENSION(2) :: dhs
154  INTEGER,DIMENSION(2) :: dhe 
155
156  ddid=(/ 1,2 /)
157  dsg=(/ iim_glo, jjm_glo /)
158  dsl=(/ iim_glo, jj_nb /)
159  dpf=(/ 1,jj_begin /)
160  dpl=(/ iim_glo, jj_end /)
161  dhs=(/ ii_begin-1,0 /)
162  IF (mpi_rank==mpi_size-1) THEN
163      dhe=(/0,0/)
164  ELSE
165      dhe=(/ iim_glo-ii_end,0 /) 
166  ENDIF
167 
168  CALL flio_dom_set( &
169     mpi_size,mpi_rank, &
170     ddid,dsg,dsl,dpf,  &
171     dpl,dhs,dhe,       &
172     'APPLE',inca_domain_id)
173
174END SUBROUTINE Init_inca_io_para
Note: See TracBrowser for help on using the repository browser.