source: LMDZ5/trunk/libf/dynphy_lonlat/phymar/iniphysiq_mod.F90 @ 2588

Last change on this file since 2588 was 2588, checked in by Ehouarn Millour, 8 years ago

-Small change in the dynamics/physics interface organization:
externalize (from iniphysiq) operations wich initialize settings
common to all physics packages (e.g. global grid definitions;
in practice initializations for routines either in phy_common
or in dynphy_lonlat) in inigeomphy (located in dynphy_lonlat).
iniphysiq should only initialize settings in the corresponding
physics package (e.g. phylmd for dynphy_lonlat/phylmd/iniphysiq).

  • Bug fix in phydev/iophy: is_south_pole_dyn replaces

is_south_pole since rev. 2429.

EM

File size: 3.4 KB
Line 
1!
2! $Id: iniphysiq.F 1403 2010-07-01 09:02:53Z fairhead $
3!
4MODULE iniphysiq_mod
5
6CONTAINS
7
8SUBROUTINE iniphysiq(ii,jj,nlayer, &
9                     nbp, communicator, &
10                     punjours, pdayref,ptimestep, &
11                     rlatu,rlatv,rlonu,rlonv,aire,cu,cv,         &
12                     prad,pg,pr,pcpp,iflag_phys)
13  USE dimphy, ONLY: init_dimphy
14  USE inigeomphy_mod, ONLY: inigeomphy
15  USE infotrac, ONLY: nqtot
16  USE comcstphy, ONLY: rradius, & ! planet radius (m)
17                       rr, & ! recuced gas constant: R/molar mass of atm
18                       rg, & ! gravity
19                       rcpp  ! specific heat of the atmosphere
20  USE infotrac_phy, ONLY: init_infotrac_phy
21  USE nrtype, ONLY: pi
22  IMPLICIT NONE
23  !
24  !=======================================================================
25  !   Initialisation of the physical constants and some positional and
26  !   geometrical arrays for the physics
27  !=======================================================================
28 
29 
30  include "iniprint.h"
31
32  REAL,INTENT(IN) :: prad ! radius of the planet (m)
33  REAL,INTENT(IN) :: pg ! gravitational acceleration (m/s2)
34  REAL,INTENT(IN) :: pr ! ! reduced gas constant R/mu
35  REAL,INTENT(IN) :: pcpp ! specific heat Cp
36  REAL,INTENT(IN) :: punjours ! length (in s) of a standard day
37  INTEGER, INTENT (IN) :: nlayer ! number of atmospheric layers
38  INTEGER, INTENT (IN) :: ii ! number of atmospheric coulumns along longitudes
39  INTEGER, INTENT (IN) :: jj  ! number of atompsheric columns along latitudes
40  INTEGER, INTENT(IN) :: nbp ! number of physics columns for this MPI process
41  INTEGER, INTENT(IN) :: communicator ! MPI communicator
42  REAL, INTENT (IN) :: rlatu(jj+1) ! latitudes of the physics grid
43  REAL, INTENT (IN) :: rlatv(jj) ! latitude boundaries of the physics grid
44  REAL, INTENT (IN) :: rlonv(ii+1) ! longitudes of the physics grid
45  REAL, INTENT (IN) :: rlonu(ii+1) ! longitude boundaries of the physics grid
46  REAL, INTENT (IN) :: aire(ii+1,jj+1) ! area of the dynamics grid (m2)
47  REAL, INTENT (IN) :: cu((ii+1)*(jj+1)) ! cu coeff. (u_covariant = cu * u)
48  REAL, INTENT (IN) :: cv((ii+1)*jj) ! cv coeff. (v_covariant = cv * v)
49  INTEGER, INTENT (IN) :: pdayref ! reference day of for the simulation
50  REAL,INTENT(IN) :: ptimestep !physics time step (s)
51  INTEGER,INTENT(IN) :: iflag_phys ! type of physics to be called
52
53  INTEGER :: ibegin,iend,offset
54  INTEGER :: i,j,k
55  CHARACTER (LEN=20) :: modname='iniphysiq'
56  CHARACTER (LEN=80) :: abort_message
57
58
59  ! --> initialize physics distribution, global fields and geometry
60  ! (i.e. things in phy_common or dynphy_lonlat)
61  CALL inigeomphy(ii,jj,nlayer, &
62               nbp, communicator, &
63               rlatu,rlatv, &
64               rlonu,rlonv, &
65               aire,cu,cv)
66
67  ! --> now initialize things specific to the phymar physics package
68 
69!$OMP PARALLEL
70
71  ! Initialize tracer names, numbers, etc. for physics
72  CALL init_infotrac_phy(nqtot)
73
74! copy some fundamental parameters to physics
75  rradius=prad
76  rg=pg
77  rr=pr
78  rcpp=pcpp
79
80!$OMP END PARALLEL
81
82!      print*,'ATTENTION !!! TRAVAILLER SUR INIPHYSIQ'
83!      print*,'CONTROLE DES LATITUDES, LONGITUDES, PARAMETRES ...'
84
85! Additional initializations for aquaplanets
86!!$OMP PARALLEL
87!      if (iflag_phys>=100) then
88!        call iniaqua(klon_omp,rlatd,rlond,iflag_phys)
89!      endif
90!!$OMP END PARALLEL
91
92END SUBROUTINE iniphysiq
93
94END MODULE iniphysiq_mod
Note: See TracBrowser for help on using the repository browser.