source: CONFIG/publications/ICOLMDZORINCA_CO2_Transport_GMD_2023/INCA/build/ppsrc/INCA_MOD/print_inca.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.3 KB
Line 
1
2
3
4
5
6
7
8
9
10
11
12!$Id: chem_mod.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!! Anne Cozic, LSCE, anne.cozic@cea.fr
22!!
23!! This software is a computer program whose purpose is to simulate the
24!! atmospheric gas phase and aerosol composition. The model is designed to be
25!! used within a transport model or a general circulation model. This version
26!! of INCA was designed to be coupled to the LMDz GCM. LMDz-INCA accounts
27!! for emissions, transport (resolved and sub-grid scale), photochemical
28!! transformations, and scavenging (dry deposition and washout) of chemical
29!! species and aerosols interactively in the GCM. Several versions of the INCA
30!! model are currently used depending on the envisaged applications with the
31!! chemistry-climate model.
32!!
33!! This software is governed by the CeCILL  license under French law and
34!! abiding by the rules of distribution of free software.  You can  use,
35!! modify and/ or redistribute the software under the terms of the CeCILL
36!! license as circulated by CEA, CNRS and INRIA at the following URL
37!! "http://www.cecill.info".
38!!
39!! As a counterpart to the access to the source code and  rights to copy,
40!! modify and redistribute granted by the license, users are provided only
41!! with a limited warranty  and the software's author,  the holder of the
42!! economic rights,  and the successive licensors  have only  limited
43!! liability.
44!!
45!! In this respect, the user's attention is drawn to the risks associated
46!! with loading,  using,  modifying and/or developing or reproducing the
47!! software by the user in light of its specific status of free software,
48!! that may mean  that it is complicated to manipulate,  and  that  also
49!! therefore means  that it is reserved for developers  and  experienced
50!! professionals having in-depth computer knowledge. Users are therefore
51!! encouraged to load and test the software's suitability as regards their
52!! requirements in conditions enabling the security of their systems and/or
53!! data to be ensured and,  more generally, to use and operate it in the
54!! same conditions as regards security.
55!!
56!! The fact that you are presently reading this means that you have had
57!! knowledge of the CeCILL license and that you accept its terms.
58!! =========================================================================
59
60
61MODULE PRINT_INCA
62
63  IMPLICIT NONE
64  INTEGER, SAVE :: lunout
65!$OMP THREADPRIVATE(lunout)
66  INTEGER, SAVE :: outxml
67!$OMP THREADPRIVATE(outxml)
68
69CONTAINS
70
71  SUBROUTINE INIT_PRINT_INCA()
72
73    USE MOD_INCA_MPI_DATA, ONLY : is_ok_mpi, mpi_rank
74    USE MOD_INCA_OMP_DATA, ONLY : is_ok_omp, omp_rank
75    USE mod_inca_mpi_data, ONLY : is_mpi_root
76
77    IMPLICIT NONE
78    CHARACTER(len=8) :: namefile
79    INTEGER :: ierr2
80    CHARACTER(len=255) :: fileout
81    CHARACTER(len=4)  :: num_mpi
82    CHARACTER(len=4)  :: num_omp
83    INTEGER,PARAMETER :: base_lunout=350
84    INTEGER           :: ierr
85
86
87    namefile='inca.out'
88   IF (is_ok_mpi) THEN
89       WRITE(num_mpi,'(I4.4)') mpi_rank
90    ENDIF
91   
92    IF (is_ok_omp) THEN
93       WRITE(num_omp,'(I4.4)') omp_rank
94    ENDIF
95
96    IF (is_ok_mpi .AND. is_ok_omp) THEN
97       fileout=TRIM(namefile)//'_'//num_mpi//'.'//num_omp
98       lunout=base_lunout+omp_rank
99    ELSE IF (is_ok_mpi .AND. (.NOT. is_ok_omp)) THEN
100       fileout=TRIM(namefile)//'_'//num_mpi
101       lunout=base_lunout
102    ELSE IF ((.NOT. is_ok_mpi) .AND. is_ok_omp) THEN
103       fileout=TRIM(namefile)//'_'//num_omp
104       lunout=base_lunout+omp_rank
105    ELSE
106       fileout=TRIM(namefile)
107       lunout=base_lunout
108    ENDIF
109    !open(UNIT=lunout,file=fileout, action='write',status='unknown', form='formatted', iostat=ierr2)
110    !IF (ierr2 /= 0) THEN
111    !   stop 'print_inca'
112    !endif
113    lunout = 6
114
115   
116!$OMP MASTER
117    IF (is_mpi_root) THEN
118       outxml=base_lunout*10
119       open(UNIT=outxml,file='inca_IDxml.out', action='write',status='unknown', form='formatted', iostat=ierr2) 
120       IF (ierr2 /= 0) THEN
121          stop 'print_inca xml'
122       endif
123    endif
124   
125!$OMP END MASTER
126
127
128  END SUBROUTINE INIT_PRINT_INCA
129END MODULE PRINT_INCA
Note: See TracBrowser for help on using the repository browser.