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

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

Cleanup in the dynamics: turn comvert.h into module comvert_mod.F90
EM

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