source: dynamico_lmdz/simple_physics/phyparam/dynphy_lonlat/iniphysiq_mod.F90 @ 4236

Last change on this file since 4236 was 4236, checked in by dubos, 5 years ago

simple_physics : some Python bindings

File size: 4.7 KB
Line 
1!
2! $Id: iniphysiq.F 1403 2010-07-01 09:02:53Z fairhead $
3!
4MODULE iniphysiq_mod
5  IMPLICIT NONE
6 
7CONTAINS
8 
9  SUBROUTINE iniphysiq(iim,jjm,nlayer, &
10       &               nbp, communicator, &
11       &               punjours, pdayref,ptimestep, &
12       &               rlatu,rlatv,rlonu,rlonv,aire,cu,cv, &
13       &               prad,pg,pr,pcpp,iflag_phys)
14    USE dimphy, ONLY: init_dimphy
15    USE inigeomphy_mod, ONLY: inigeomphy
16    USE iniphyparam_mod, ONLY : iniphyparam
17    USE mod_phys_lmdz_para, ONLY: klon_omp ! number of columns (on local omp grid)
18    USE infotrac, ONLY: nqtot, type_trac
19    USE infotrac_phy, ONLY: init_infotrac_phy
20    USE inifis_mod, ONLY: inifis
21    USE phyaqua_mod, ONLY: iniaqua
22    USE nrtype, ONLY: pi
23!    USE vertical_layers_mod, ONLY : presnivs
24
25    !
26    !=======================================================================
27    !   Initialisation of the physical constants and some positional and
28    !   geometrical arrays for the physics
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) :: iim ! number of atmospheric coulumns along longitudes
40    INTEGER, INTENT (IN) :: jjm  ! 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(jjm+1) ! latitudes of the physics grid
44    REAL, INTENT (IN) :: rlatv(jjm) ! latitude boundaries of the physics grid
45    REAL, INTENT (IN) :: rlonv(iim+1) ! longitudes of the physics grid
46    REAL, INTENT (IN) :: rlonu(iim+1) ! longitude boundaries of the physics grid
47    REAL, INTENT (IN) :: aire(iim+1,jjm+1) ! area of the dynamics grid (m2)
48    REAL, INTENT (IN) :: cu((iim+1)*(jjm+1)) ! cu coeff. (u_covariant = cu * u)
49    REAL, INTENT (IN) :: cv((iim+1)*jjm) ! 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    print*,'INInnn   iniphysiq_mod'
61   
62    ! --> initialize physics distribution, global fields and geometry
63    ! (i.e. things in phy_common or dynphy_lonlat)
64    CALL inigeomphy(iim,jjm,nlayer, &
65         nbp, communicator, &
66         rlatu,rlatv, &
67         rlonu,rlonv, &
68         aire,cu,cv)
69   
70    ! --> now initialize things specific to the phydev physics package
71   
72    !$OMP PARALLEL
73   
74    ! Initialize physical constants in physics:
75    CALL inifis(prad,pg,pr,pcpp)
76   
77    ! Initialize tracer names, numbers, etc. for physics
78    CALL init_infotrac_phy(nqtot,type_trac)
79   
80    ! Additional initializations for aquaplanets
81    IF (iflag_phys>=100) THEN
82       CALL iniaqua(klon_omp,iflag_phys)
83    ENDIF
84!
85!    call iophys_ini('phys.nc    ',presnivs)
86
87    CALL setup_phyparam
88
89    CALL iniphyparam(ptimestep, punjours, prad, pg, pr, pcpp)
90   
91    !$OMP END PARALLEL
92   
93   
94  END SUBROUTINE iniphysiq
95 
96  SUBROUTINE setup_phyparam
97    USE comgeomfi,          ONLY : nlayermx, init_comgeomfi
98    USE dimphy,             ONLY : klon, klev
99    USE mod_grid_phy_lmdz,  ONLY : klon_glo
100    USE mod_phys_lmdz_para, ONLY : klon_omp
101    USE geometry_mod,       ONLY : longitude,latitude
102    USE read_param_mod
103    USE phyparam_plugins_lmdz
104
105    read_paramr_plugin => read_paramr
106    read_parami_plugin => read_parami
107    read_paramb_plugin => read_paramb
108
109    CALL init_comgeomfi(klon_omp, klev, longitude, latitude)
110
111    IF (klon.NE.klon_omp) THEN
112       PRINT*,'STOP in setup_phyparam'
113       PRINT*,'Probleme de dimensions :'
114       PRINT*,'klon     = ',klon
115       PRINT*,'klon_omp   = ',klon_omp
116       STOP
117    ENDIF
118
119    IF (klev.NE.nlayermx) THEN
120       PRINT*,'STOP in setup_phyparam'
121       PRINT*,'Probleme de dimensions :'
122       PRINT*,'nlayer     = ',klev
123       PRINT*,'nlayermx   = ',nlayermx
124       STOP
125    ENDIF
126
127    IF (klon_omp.NE.klon_glo) THEN
128       PRINT*,'STOP in setup_phyparam'
129       PRINT*,'Probleme de dimensions :'
130       PRINT*,'ngrid     = ', klon_omp
131       PRINT*,'ngridmax   = ',klon_glo
132       STOP
133    ENDIF
134
135  END SUBROUTINE setup_phyparam
136 
137END MODULE iniphysiq_mod
Note: See TracBrowser for help on using the repository browser.