source: LMDZ6/branches/Portage_acc/libf/dynphy_lonlat/phylmd/iniphysiq_mod.F90 @ 4132

Last change on this file since 4132 was 4132, checked in by Laurent Fairhead, 2 years ago

Modifications to code to start using openacc directives
LF

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 6.9 KB
Line 
1!
2! $Id: iniphysiq_mod.F90 4132 2022-04-20 16:35:42Z fairhead $
3!
4MODULE iniphysiq_mod
5
6CONTAINS
7
8SUBROUTINE iniphysiq(ii,jj,nlayer, &
9                     nbp, communicator, &
10                     punjours, pdayref,ptimestep, &
11                     rlatudyn,rlatvdyn,rlonudyn,rlonvdyn,airedyn,cudyn,cvdyn, &
12                     prad,pg,pr,pcpp,iflag_phys)
13  USE dimphy, ONLY: init_dimphy
14  USE inigeomphy_mod, ONLY: inigeomphy
15  USE mod_grid_phy_lmdz, ONLY: nbp_lon,nbp_lat,nbp_lev,klon_glo ! number of atmospheric columns (on full grid)
16  USE mod_phys_lmdz_para, ONLY: klon_omp ! number of columns (on local omp grid)
17  USE vertical_layers_mod, ONLY : init_vertical_layers
18  USE infotrac, ONLY: nbtr,nqCO2,tracers,isotopes,type_trac,conv_flg,pbl_flg,nqtottr
19#ifdef CPP_StratAer
20  USE infotrac_phy, ONLY: nbtr_bin, nbtr_sulgas, id_OCS_strat, &
21                      id_SO2_strat, id_H2SO4_strat, id_BIN01_strat
22
23#endif
24#ifdef REPROBUS
25  USE CHEM_REP, ONLY : Init_chem_rep_phys
26#ifdef CPP_PARA
27  USE parallel_lmdz, ONLY : mpi_size, mpi_rank
28  USE bands, ONLY : distrib_phys
29#endif
30  USE mod_phys_lmdz_omp_data, ONLY: klon_omp
31#endif
32  USE control_mod, ONLY: dayref,anneeref,day_step,nday,offline, iphysiq, config_inca
33  USE inifis_mod, ONLY: inifis
34  USE time_phylmdz_mod, ONLY: init_time
35  USE temps_mod, ONLY: annee_ref, day_ini, day_ref, start_time, calend, year_len
36  USE infotrac_phy, ONLY: init_infotrac_phy
37  USE phystokenc_mod, ONLY: init_phystokenc
38  USE phyaqua_mod, ONLY: iniaqua
39  USE comconst_mod, ONLY: omeg, rad
40#ifdef INCA
41  USE indice_sol_mod, ONLY: nbsrf, is_oce, is_sic, is_ter, is_lic
42#ifdef CPP_PARA
43  USE parallel_lmdz, ONLY : mpi_size, mpi_rank
44  USE bands, ONLY : distrib_phys
45#endif
46  USE mod_phys_lmdz_omp_data, ONLY: klon_omp
47#endif
48  USE ioipsl_getin_p_mod, ONLY: getin_p
49  USE slab_heat_transp_mod, ONLY: ini_slab_transp_geom
50#ifdef _OPENACC
51    USE openacc
52#endif
53    IMPLICIT NONE
54
55  ! =======================================================================
56  ! Initialisation of the physical constants and some positional and
57  ! geometrical arrays for the physics
58  ! =======================================================================
59
60  include "dimensions.h"
61  include "paramet.h"
62  include "iniprint.h"
63  include "tracstoke.h"
64  include "comgeom.h"
65
66  REAL, INTENT (IN) :: prad ! radius of the planet (m)
67  REAL, INTENT (IN) :: pg ! gravitational acceleration (m/s2)
68  REAL, INTENT (IN) :: pr ! ! reduced gas constant R/mu
69  REAL, INTENT (IN) :: pcpp ! specific heat Cp
70  REAL, INTENT (IN) :: punjours ! length (in s) of a standard day
71  INTEGER, INTENT (IN) :: nlayer ! number of atmospheric layers
72  INTEGER, INTENT (IN) :: ii ! number of atmospheric columns along longitudes
73  INTEGER, INTENT (IN) :: jj ! number of atompsheric columns along latitudes
74  INTEGER, INTENT(IN) :: nbp ! number of physics columns for this MPI process
75  INTEGER, INTENT(IN) :: communicator ! MPI communicator
76  REAL, INTENT (IN) :: rlatudyn(jj+1) ! latitudes of the physics grid
77  REAL, INTENT (IN) :: rlatvdyn(jj) ! latitude boundaries of the physics grid
78  REAL, INTENT (IN) :: rlonvdyn(ii+1) ! longitudes of the physics grid
79  REAL, INTENT (IN) :: rlonudyn(ii+1) ! longitude boundaries of the physics grid
80  REAL, INTENT (IN) :: airedyn(ii+1,jj+1) ! area of the dynamics grid (m2)
81  REAL, INTENT (IN) :: cudyn((ii+1)*(jj+1)) ! cu coeff. (u_covariant = cu * u)
82  REAL, INTENT (IN) :: cvdyn((ii+1)*jj) ! cv coeff. (v_covariant = cv * v)
83  INTEGER, INTENT (IN) :: pdayref ! reference day of for the simulation
84  REAL, INTENT (IN) :: ptimestep !physics time step (s)
85  INTEGER, INTENT (IN) :: iflag_phys ! type of physics to be called
86
87  INTEGER :: ibegin, iend, offset
88  INTEGER :: i,j,k
89  CHARACTER (LEN=20) :: modname = 'iniphysiq'
90  CHARACTER (LEN=80) :: abort_message
91 
92  LOGICAL :: slab_hdiff
93  INTEGER :: slab_ekman
94  CHARACTER (LEN = 6) :: type_ocean
95
96#ifndef CPP_PARA
97  INTEGER,PARAMETER :: mpi_rank=0
98  INTEGER, PARAMETER :: mpi_size = 1
99  INTEGER :: distrib_phys(mpi_rank:mpi_rank)=(jjm-1)*iim+2
100#endif
101
102#ifdef _OPENACC
103    INTEGER :: numdev
104
105    !$acc init
106
107    ! get the number of NVIDIA devices on this node
108    numdev = acc_get_num_devices(ACC_DEVICE_NVIDIA)
109    PRINT *, 'init_physics : number of available GPU devices', numdev
110    IF (numdev < 1) STOP "Error: there are no devices available on this host. ABORTING"
111    CALL acc_init(ACC_DEVICE_NVIDIA)
112    numdev = acc_get_device_num(ACC_DEVICE_NVIDIA)
113    PRINT *, 'init_physics : GPU device id = ', numdev
114#endif
115
116
117
118
119
120  ! --> initialize physics distribution, global fields and geometry
121  ! (i.e. things in phy_common or dynphy_lonlat)
122  CALL inigeomphy(ii,jj,nlayer, &
123               nbp, communicator, &
124               rlatudyn,rlatvdyn, &
125               rlonudyn,rlonvdyn, &
126               airedyn,cudyn,cvdyn)
127
128  ! --> now initialize things specific to the phylmd physics package
129 
130!!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/)
131!       Copy all threadprivate variables in temps_mod
132!$OMP PARALLEL DEFAULT(SHARED) COPYIN(annee_ref,day_ini,day_ref,start_time)
133
134  ! Initialize physical constants in physics:
135  CALL inifis(punjours,prad,pg,pr,pcpp)
136
137  CALL init_time(annee_ref,day_ref,day_ini,start_time,nday,ptimestep)
138
139  ! Initialize dimphy module (unless in 1D where it has already been done)
140!  IF (klon_glo>1) CALL Init_dimphy(klon_omp,nlayer)
141
142  ! Copy over "offline" settings
143  CALL init_phystokenc(offline,istphy)
144
145  ! Initialization for slab heat transport
146  type_ocean="force"
147  CALL getin_p('type_ocean',type_ocean)
148  slab_hdiff=.FALSE.
149  CALL getin_p('slab_hdiff',slab_hdiff)
150  slab_ekman=0
151  CALL getin_p('slab_ekman',slab_ekman)
152  IF ((type_ocean=='slab').AND.(slab_hdiff.OR.(slab_ekman.GT.0))) THEN
153     CALL ini_slab_transp_geom(ip1jm,ip1jmp1,unsairez,fext,unsaire,&
154                                  cu,cuvsurcv,cv,cvusurcu, &
155                                  aire,apoln,apols, &
156                                  aireu,airev,rlatvdyn,rad,omeg)
157  END IF
158
159  ! Initialize tracer names, numbers, etc. for physics
160  CALL init_infotrac_phy(type_trac, tracers, isotopes, nqtottr, nqCO2, pbl_flg, conv_flg)
161
162  ! Initializations for Reprobus
163  IF (type_trac == 'repr') THEN
164#ifdef REPROBUS
165    call Init_chem_rep_phys(klon_omp,nlayer)
166    call init_reprobus_para( &
167          nbp_lon,nbp_lat,nbp_lev,klon_glo,mpi_size, &
168          distrib_phys,communicator)
169#endif
170  ENDIF
171!$OMP END PARALLEL
172
173
174  IF (type_trac == 'repr') THEN
175#ifdef REPROBUS
176    call init_reprobus_para( &
177          nbp_lon,nbp_lat,nbp_lev,klon_glo,mpi_size, &
178          distrib_phys,communicator)
179#endif
180  ENDIF
181
182!!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/)
183!$OMP PARALLEL DEFAULT(SHARED)
184  ! Additional initializations for aquaplanets
185  IF (iflag_phys>=100) THEN
186    CALL iniaqua(klon_omp,year_len,iflag_phys)
187  END IF
188
189  IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN
190#ifdef INCA
191     CALL init_inca_dim_reg(nbp_lon, nbp_lat - 1, &
192          rlonudyn, rlatudyn, rlonvdyn, rlatvdyn)
193#endif
194  END IF
195
196  IF (type_trac == 'repr') THEN
197#ifdef REPROBUS
198     CALL Init_chem_rep_phys(klon_omp,nbp_lev)
199#endif
200  END IF
201
202!$OMP END PARALLEL
203
204END SUBROUTINE iniphysiq
205
206END MODULE iniphysiq_mod
Note: See TracBrowser for help on using the repository browser.