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

Last change on this file since 2786 was 2786, checked in by Ehouarn Millour, 7 years ago

Further convergence with planetary models:

  • move vertical_layers_mod.F90 to phy_common and call init_vertical_layers in inigeomphy_mod
  • add aps and bps (mid-layer coordinates) to vertical_layers_mod.F90
  • same adaptations for the 1D case

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