source: CONFIG/publications/ICOLMDZORINCA_CO2_Transport_GMD_2023/INCA/build/ppsrc/INCA_PARA/inca_write_field_p.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: 6.5 KB
Line 
1
2
3
4
5
6
7
8
9
10
11
12!$Id: inca_write_field_p.F90 10 2007-08-09 12:43:01Z 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
62MODULE inca_Write_field_p
63
64  INTERFACE WriteField_p
65    MODULE PROCEDURE WriteField_1d_p,WriteField_2d_p, WriteField_3d_p
66  END INTERFACE
67 
68  INTERFACE WriteFieldI_p
69    MODULE PROCEDURE WriteFieldI_2d_p
70  END INTERFACE
71 
72 
73CONTAINS
74
75  SUBROUTINE INIT_WRITEFIELD_P(index)
76    USE MOD_INCA_PARA
77    USE inca_Write_Field, ONLY : Init_WriteField
78    IMPLICIT NONE
79    INTEGER,INTENT(in) :: INDEX(nbp_loc)
80   
81    INTEGER :: index_p(nbp_loc)
82    INTEGER :: index_g(nbp_glo)
83   
84    index_p(:)=INDEX(:)+(jj_begin-1)*iim_g
85    CALL gather(index_p,index_g)
86   
87!$OMP MASTER
88    IF (is_mpi_root) CALL Init_WriteField(iim_g,jjm_g,nbp_glo,index_g)
89!$OMP END MASTER
90   
91  END SUBROUTINE init_WriteField_p
92
93
94  SUBROUTINE WriteField_1d_p(name,Field)
95
96    USE INCA_DIM
97    USE MOD_INCA_PARA
98    USE MOD_GRID_INCA
99    USE INCA_WRITE_FIELD, ONLY : WriteField
100   
101    IMPLICIT NONE
102
103    CHARACTER(len=*)   :: name
104    INTEGER :: ll
105    REAL, DIMENSION(plon_omp) :: Field
106    REAL,SAVE,ALLOCATABLE :: Field_tmp(:,:)
107    REAL, DIMENSION(plon_glo):: New_Field
108    REAL, DIMENSION(iim_glo,jjm_glo):: Field_2d
109
110    CALL Gather(Field,New_Field)
111!$OMP MASTER
112    IF (is_mpi_root) THEN       
113      CALL Grid1Dto2D_glo(New_Field,Field_2D)
114      CALL WriteField(name,Field_2d)
115    ENDIF
116!$OMP END MASTER
117!$OMP BARRIER
118
119
120  END SUBROUTINE WriteField_1d_p
121
122!------------------------------------------------
123
124  SUBROUTINE WriteField_2d_p(name,Field,ll)
125
126    USE INCA_DIM
127    USE MOD_INCA_PARA
128    USE MOD_GRID_INCA
129    USE INCA_WRITE_FIELD, ONLY : WriteField
130   
131    IMPLICIT NONE
132
133    CHARACTER(len=*)   :: name
134    INTEGER :: ll
135    REAL, DIMENSION(plon_omp,ll) :: Field
136    REAL,SAVE,ALLOCATABLE :: Field_tmp(:,:)
137    REAL, DIMENSION(plon_glo,ll):: New_Field
138    REAL, DIMENSION(iim_glo,jjm_glo,ll):: Field_2d
139
140    CALL Gather(Field,New_Field)
141!$OMP MASTER
142    IF (is_mpi_root) THEN       
143      CALL Grid1Dto2D_glo(New_Field,Field_2D)
144      CALL WriteField(name,Field_2d)
145    ENDIF
146!$OMP END MASTER
147!$OMP BARRIER
148
149
150  END SUBROUTINE WriteField_2d_p
151
152!------------------------------------------------
153!------------------------------------------------
154
155  SUBROUTINE WriteField_3d_p(name,Field,ll,mm)
156   
157    USE INCA_DIM
158    USE MOD_INCA_PARA
159    USE MOD_GRID_INCA
160    USE inca_Write_field, ONLY : WriteField
161   
162    IMPLICIT NONE
163
164    CHARACTER(len=*)   :: name
165    INTEGER :: ll, mm, m
166    REAL, DIMENSION(plon_omp,ll,mm) :: Field
167    REAL, DIMENSION(plon_glo,ll,mm):: New_Field
168    REAL, DIMENSION(iim_glo,jjm_glo,ll,mm):: Field_2d
169    REAL, DIMENSION(plon_omp,ll) :: Field_tmp
170    REAL, DIMENSION(plon_glo,ll):: New_Field_tmp
171
172    DO m= 1, mm
173       Field_tmp(:,:) = Field(:,:,m)
174       CALL Gather(Field_tmp,New_Field_tmp)
175       New_Field(:,:,m) = New_Field_tmp(:,:)
176    ENDDO
177!$OMP MASTER
178    IF (is_mpi_root) THEN       
179       DO m= 1, mm
180          CALL Grid1Dto2D_glo(New_Field(:,:,m),Field_2D(:,:,:,m))
181       ENDDO
182       CALL WriteField(name,Field_2d)
183    ENDIF
184!$OMP END MASTER
185!$OMP BARRIER
186
187  END SUBROUTINE WriteField_3d_p
188 
189!------------------------------------------------
190
191  SUBROUTINE WriteFieldI_2d_p(name,Field)
192    USE MOD_INCA_PARA
193    USE inca_Write_field, ONLY : WriteFieldI
194    IMPLICIT NONE
195    CHARACTER(len=*) :: name
196    REAL, DIMENSION(:,:) :: Field 
197    INTEGER, DIMENSION(2) :: Dim
198   
199    REAL, ALLOCATABLE, DIMENSION(:,:) :: Field_g
200     
201    Dim=SHAPE(Field)
202     
203    ALLOCATE(Field_g(nbp_glo,DIM(2)))
204    CALL gather(Field,Field_g)
205   
206!$OMP MASTER
207    IF (is_mpi_root) CALL WriteFieldI(name,Field_g) 
208!$OMP END MASTER
209     
210    DEALLOCATE(Field_g)
211  END SUBROUTINE WriteFieldI_2d_p
212
213  function int2str(int)
214    implicit none
215    integer, parameter :: MaxLen=10
216    integer,intent(in) :: int
217    character(len=MaxLen) :: int2str
218    logical :: flag
219    integer :: i
220    flag=.true.
221   
222    i=int
223   
224    int2str=''
225    do while (flag)
226      int2str=CHAR(MOD(i,10)+48)//int2str
227      i=i/10
228      if (i==0) flag=.false.
229    enddo
230  end function int2str
231
232
233END MODULE inca_Write_field_p
234
235
236
Note: See TracBrowser for help on using the repository browser.