10 punjours, pdayref,ptimestep, &
16 nbp_lon, nbp_lat, nbp_lev
33 USE chem_rep
, ONLY : init_chem_rep_phys
61 include
"dimensions.h"
68 REAL,
INTENT (IN) :: prad
69 REAL,
INTENT (IN) :: pg
70 REAL,
INTENT (IN) :: pr
71 REAL,
INTENT (IN) :: pcpp
72 REAL,
INTENT (IN) :: punjours
73 INTEGER,
INTENT (IN) :: nlayer
74 INTEGER,
INTENT (IN) :: ii
75 INTEGER,
INTENT (IN) :: jj
76 INTEGER,
INTENT(IN) :: nbp
77 INTEGER,
INTENT(IN) :: communicator
78 REAL,
INTENT (IN) :: rlatu(jj+1)
79 REAL,
INTENT (IN) :: rlatv(jj)
80 REAL,
INTENT (IN) :: rlonv(ii+1)
81 REAL,
INTENT (IN) :: rlonu(ii+1)
82 REAL,
INTENT (IN) :: aire(ii+1,jj+1)
83 REAL,
INTENT (IN) :: cu((ii+1)*(jj+1))
84 REAL,
INTENT (IN) :: cv((ii+1)*jj)
85 INTEGER,
INTENT (IN) :: pdayref
86 REAL,
INTENT (IN) :: ptimestep
87 INTEGER,
INTENT (IN) :: iflag_phys
89 INTEGER :: ibegin, iend, offset
91 CHARACTER (LEN=20) :: modname =
'iniphysiq'
92 CHARACTER (LEN=80) :: abort_message
93 REAL :: total_area_phy, total_area_dyn
96 REAL,
ALLOCATABLE :: boundslon_reg(:,:)
97 REAL,
ALLOCATABLE :: boundslat_reg(:,:)
100 REAL,
ALLOCATABLE :: latfi_glo(:)
101 REAL,
ALLOCATABLE :: lonfi_glo(:)
102 REAL,
ALLOCATABLE :: cufi_glo(:)
103 REAL,
ALLOCATABLE :: cvfi_glo(:)
104 REAL,
ALLOCATABLE :: airefi_glo(:)
105 REAL,
ALLOCATABLE :: boundslonfi_glo(:,:)
106 REAL,
ALLOCATABLE :: boundslatfi_glo(:,:)
109 REAL,
ALLOCATABLE,
SAVE :: latfi(:)
110 REAL,
ALLOCATABLE,
SAVE :: lonfi(:)
111 REAL,
ALLOCATABLE,
SAVE :: cufi(:)
112 REAL,
ALLOCATABLE,
SAVE :: cvfi(:)
113 REAL,
ALLOCATABLE,
SAVE :: airefi(:)
114 REAL,
ALLOCATABLE,
SAVE :: boundslonfi(:,:)
115 REAL,
ALLOCATABLE,
SAVE :: boundslatfi(:,:)
121 nbp,ii,jj+1,nlayer,communicator)
124 1,1,1,nlayer,communicator)
129 ALLOCATE(boundslon_reg(ii,2))
130 ALLOCATE(boundslat_reg(jj+1,2))
133 boundslon_reg(i,
east)=rlonu(i)
134 boundslon_reg(i,
west)=rlonu(i+1)
138 boundslat_reg(1,
south)= rlatv(1)
140 boundslat_reg(j,
north)=rlatv(j-1)
141 boundslat_reg(j,
south)=rlatv(j)
143 boundslat_reg(jj+1,
north)= rlatv(jj)
144 boundslat_reg(jj+1,
south)= -
pi/2
148 boundslon_reg, boundslat_reg)
154 ALLOCATE(boundslonfi_glo(
klon_glo,4))
155 ALLOCATE(boundslatfi_glo(
klon_glo,4))
160 latfi_glo(1)=rlatu(1)
175 latfi_glo(k)= rlatu(j)
176 lonfi_glo(k)= rlonv(i)
177 cufi_glo(k) = cu((j-1)*(ii+1)+i)
178 cvfi_glo(k) = cv((j-1)*(ii+1)+i)
192 cufi_glo(
klon_glo) = cu((ii+1)*jj+1)
193 cvfi_glo(
klon_glo) = cv((ii+1)*jj-ii)
206 airefi_glo(1)=sum(aire(1:ii,1))
207 airefi_glo(
klon_glo)=sum(aire(1:ii,jj+1))
210 total_area_dyn=sum(aire(1:ii,1:jj+1))
211 total_area_phy=sum(airefi_glo(1:
klon_glo))
212 IF (total_area_dyn/=total_area_phy)
THEN
213 WRITE (
lunout, *)
'iniphysiq: planet total surface discrepancy !!!'
214 WRITE (
lunout, *)
' in the dynamics total_area_dyn=', total_area_dyn
215 WRITE (
lunout, *)
' but in the physics total_area_phy=', total_area_phy
216 IF (abs(total_area_dyn-total_area_phy)>0.00001*total_area_dyn)
THEN
218 abort_message =
'planet total surface discrepancy'
219 CALL abort_gcm(modname, abort_message, 1)
224 latfi_glo(1)=rlatu(1)
225 lonfi_glo(1)=rlonv(1)
228 airefi_glo(1)=aire(1,1)
247 offset = klon_mpi_begin - 1
248 airefi(1:
klon_omp) = airefi_glo(offset+klon_omp_begin:offset+klon_omp_end)
249 cufi(1:
klon_omp) = cufi_glo(offset+klon_omp_begin:offset+klon_omp_end)
250 cvfi(1:
klon_omp) = cvfi_glo(offset+klon_omp_begin:offset+klon_omp_end)
251 lonfi(1:
klon_omp) = lonfi_glo(offset+klon_omp_begin:offset+klon_omp_end)
252 latfi(1:
klon_omp) = latfi_glo(offset+klon_omp_begin:offset+klon_omp_end)
253 boundslonfi(1:
klon_omp,:) = boundslonfi_glo(offset+klon_omp_begin:offset+klon_omp_end,:)
254 boundslatfi(1:
klon_omp,:) = boundslatfi_glo(offset+klon_omp_begin:offset+klon_omp_end,:)
265 CALL inifis(punjours,prad,pg,pr,pcpp)
289 CALL init_chem_rep_phys(
klon_omp,nlayer)
296 call init_const_lmdz( &
301 call init_inca_para( &
309 IF (iflag_phys>=100)
THEN
315 CALL init_inca_dim(
klon_omp,nbp_lev,nbp_lon,nbp_lat - 1, &
316 rlonu,rlatu,rlonv,rlatv)
character(len=8), dimension(:), allocatable, save solsym
character(len=23), dimension(:), allocatable, save ttext
integer, dimension(:), allocatable distrib_phys
subroutine iniphysiq(iim, jjm, nlayer, nbp, communicator, punjours, pdayref, ptimestep, rlatu, rlatv, rlonu, rlonv, aire, cu, cv, prad, pg, pr, pcpp, iflag_phys)
integer, parameter is_ter
integer, dimension(:), allocatable, save nqdesc
subroutine init_vertical_layers(nlayer, preff_, scaleheight_, ap_, bp_, presnivs_, pseudoalt_)
integer, save ntraceurs_zone
real, dimension(niso_possibles), save tnat
!$Header!common tracstoke istphy
subroutine init_interface_dyn_phys
logical, save ok_iso_verif
integer, dimension(:), allocatable, save phase_num
subroutine abort_gcm(modname, message, ierr)
integer, dimension(:,:), allocatable, save index_trac
!$Id mode_top_bound COMMON comconstr && pi
!$Header!CDK comgeom COMMON comgeom aire
integer, dimension(:), allocatable, save conv_flg
!$Header!CDK comgeom COMMON comgeom rlatu
subroutine inifis(prad, pg, pr, pcpp)
logical, save ok_init_iso
!$Id ysinus ok_gradsfile hybrid COMMON logici iflag_phys
subroutine iniaqua(nlon, iflag_phys)
integer, dimension(:,:), allocatable, save iqfils
integer, dimension(:,:), allocatable, save iqiso
subroutine init_dimphy(klon0, klev0)
subroutine init_time(annee_ref_, day_ref_, day_ini_, start_time_, ndays_, pdtphys_)
integer, dimension(niso_possibles), save indnum_fn_num
integer, dimension(:), allocatable, save zone_num
integer, parameter is_lic
integer, parameter north_west
!$Header!CDK comgeom COMMON comgeom rlonu
!$Header!CDK comgeom COMMON comgeom rlatv
logical, dimension(niso_possibles), save use_iso
character(len=20), dimension(:), allocatable, save tname
character(len=4), save type_trac
subroutine gr_dyn_fi(nfield, im, jm, ngrid, pdyn, pfi)
!$Id!Parameters for parameters that control the rate of approach!to quasi equilibrium noff nlm real tlcrit real entp real sigd real coeffs real dtmax real cu real betad real damp real delta COMMON cvparam nlm tlcrit sigd coeffs cu
integer, dimension(:), allocatable, save niadv
!$Id pseudoalt(llm) common/comverti/disvert_type
real, dimension(niso_possibles), save alpha_ideal
integer, dimension(:), allocatable, save nqfils
subroutine init_geometry(klon, longitude_, latitude_, boundslon_, boundslat_, cell_area_, dx_, dy_)
integer, dimension(:), allocatable, save pbl_flg
logical, save ok_isotopes
integer, parameter is_sic
integer, dimension(:), allocatable, save iqpere
subroutine init_infotrac_phy(nqtot_, type_trac_)
!$Header!CDK comgeom COMMON comgeom cv
subroutine init_regular_lonlat(nbp_lon, nbp_lat, lon_reg_, lat_reg_, boundslon_reg_, boundslat_reg_)
integer, parameter north_east
subroutine init_phystokenc(offline_dyn, istphy_dyn)
integer, dimension(:), allocatable, save iso_num
integer, parameter south_east
integer, parameter south_west
integer, dimension(:), allocatable, save iso_indnum
integer, parameter is_oce
!$Header!gestion des impressions de sorties et de débogage la sortie standard prt_level COMMON comprint lunout
subroutine init_physics_distribution(grid_type, nvertex, nbp, nbp_lon, nbp_lat, nbp_lev, communicator)
!$Header!CDK comgeom COMMON comgeom rlonv