source: trunk/LMDZ.GENERIC/libf/dynlonlat_phylonlat/phystd/iniphysiq_mod.F90 @ 1525

Last change on this file since 1525 was 1525, checked in by emillour, 9 years ago

All GCMs:
More on enforcing dynamics/physics separation: get rid of references to "control_mod" from physics packages.
EM

File size: 6.5 KB
Line 
1MODULE iniphysiq_mod
2
3CONTAINS
4
5subroutine iniphysiq(ii,jj,nlayer,punjours, pdayref,ptimestep,           &
6                     rlatu,rlatv,rlonu,rlonv,aire,cu,cv,                 &
7                     prad,pg,pr,pcpp,iflag_phys)
8
9use dimphy, only : klev ! number of atmospheric levels
10use mod_grid_phy_lmdz, only : klon_glo ! number of atmospheric columns
11                                       ! (on full grid)
12use mod_phys_lmdz_para, only : klon_omp, & ! number of columns (on local omp grid)
13                               klon_omp_begin, & ! start index of local omp subgrid
14                               klon_omp_end, & ! end index of local omp subgrid
15                               klon_mpi_begin ! start indes of columns (on local mpi grid)
16use control_mod, only: nday
17use comgeomphy, only : initcomgeomphy, &
18                       airephy, & ! physics grid area (m2)
19                       cuphy, & ! cu coeff. (u_covariant = cu * u)
20                       cvphy, & ! cv coeff. (v_covariant = cv * v)
21                       rlond, & ! longitudes
22                       rlatd ! latitudes
23use infotrac, only : nqtot ! number of advected tracers
24use planete_mod, only: ini_planete_mod
25USE comvert_mod, ONLY: ap,bp,preff
26use inifis_mod, only: inifis
27use regular_lonlat_mod, only: init_regular_lonlat, &
28                              east, west, north, south, &
29                              north_east, north_west, &
30                              south_west, south_east
31
32implicit none
33include "dimensions.h"
34include "iniprint.h"
35
36real,intent(in) :: prad ! radius of the planet (m)
37real,intent(in) :: pg ! gravitational acceleration (m/s2)
38real,intent(in) :: pr ! ! reduced gas constant R/mu
39real,intent(in) :: pcpp ! specific heat Cp
40real,intent(in) :: punjours ! length (in s) of a standard day
41!integer,intent(in) :: ngrid ! number of horizontal grid points in the physics (full grid)
42integer,intent(in) :: nlayer ! number of atmospheric layers
43integer,intent(in) :: ii ! number of atmospheric coulumns along longitudes
44integer,intent(in) :: jj  ! number of atompsheric columns along latitudes
45real,intent(in) :: rlatu(jj+1) ! latitudes of the physics grid
46real,intent(in) :: rlatv(jj) ! latitude boundaries of the physics grid
47real,intent(in) :: rlonv(ii+1) ! longitudes of the physics grid
48real,intent(in) :: rlonu(ii+1) ! longitude boundaries of the physics grid
49real,intent(in) :: aire(ii+1,jj+1) ! area of the dynamics grid (m2)
50real,intent(in) :: cu((ii+1)*(jj+1)) ! cu coeff. (u_covariant = cu * u)
51real,intent(in) :: cv((ii+1)*jj) ! cv coeff. (v_covariant = cv * v)
52integer,intent(in) :: pdayref ! reference day of for the simulation
53real,intent(in) :: ptimestep !physics time step (s)
54integer,intent(in) :: iflag_phys ! type of physics to be called
55
56integer :: ibegin,iend,offset
57integer :: i,j
58character(len=20) :: modname='iniphysiq'
59character(len=80) :: abort_message
60real :: total_area_phy, total_area_dyn
61real :: pi
62
63! boundaries, on global grid
64real,allocatable :: boundslon_reg(:,:)
65real,allocatable :: boundslat_reg(:,:)
66
67! global array, on full physics grid:
68real,allocatable :: latfi(:)
69real,allocatable :: lonfi(:)
70real,allocatable :: cufi(:)
71real,allocatable :: cvfi(:)
72real,allocatable :: airefi(:)
73
74pi=2.*asin(1.0)
75
76IF (nlayer.NE.klev) THEN
77  write(*,*) 'STOP in ',trim(modname)
78  write(*,*) 'Problem with dimensions :'
79  write(*,*) 'nlayer     = ',nlayer
80  write(*,*) 'klev   = ',klev
81  abort_message = ''
82  CALL abort_gcm (modname,abort_message,1)
83ENDIF
84
85!IF (ngrid.NE.klon_glo) THEN
86!  write(*,*) 'STOP in ',trim(modname)
87!  write(*,*) 'Problem with dimensions :'
88!  write(*,*) 'ngrid     = ',ngrid
89!  write(*,*) 'klon   = ',klon_glo
90!  abort_message = ''
91!  CALL abort_gcm (modname,abort_message,1)
92!ENDIF
93
94!call init_phys_lmdz(iim,jjm+1,llm,1,(/(jjm-1)*iim+2/))
95
96! init regular global longitude-latitude grid points and boundaries
97ALLOCATE(boundslon_reg(ii,2))
98ALLOCATE(boundslat_reg(jj+1,2))
99 
100DO i=1,ii
101   boundslon_reg(i,east)=rlonu(i)
102   boundslon_reg(i,west)=rlonu(i+1)
103ENDDO
104
105boundslat_reg(1,north)= PI/2
106boundslat_reg(1,south)= rlatv(1)
107DO j=2,jj
108   boundslat_reg(j,north)=rlatv(j-1)
109   boundslat_reg(j,south)=rlatv(j)
110ENDDO
111boundslat_reg(jj+1,north)= rlatv(jj)
112boundslat_reg(jj+1,south)= -PI/2
113
114! Write values in module regular_lonlat_mod
115CALL init_regular_lonlat(ii,jj+1, rlonv(1:ii), rlatu, &
116                         boundslon_reg, boundslat_reg)
117
118! Generate global arrays on full physics grid
119allocate(latfi(klon_glo),lonfi(klon_glo),cufi(klon_glo),cvfi(klon_glo))
120latfi(1)=rlatu(1)
121lonfi(1)=0.
122cufi(1) = cu(1)
123cvfi(1) = cv(1)
124DO j=2,jj
125  DO i=1,ii
126    latfi((j-2)*ii+1+i)= rlatu(j)
127    lonfi((j-2)*ii+1+i)= rlonv(i)
128    cufi((j-2)*ii+1+i) = cu((j-1)*(ii+1)+i)
129    cvfi((j-2)*ii+1+i) = cv((j-1)*(ii+1)+i)
130  ENDDO
131ENDDO
132latfi(klon_glo)= rlatu(jj+1)
133lonfi(klon_glo)= 0.
134cufi(klon_glo) = cu((ii+1)*jj+1)
135cvfi(klon_glo) = cv((ii+1)*jj-ii)
136
137! build airefi(), mesh area on physics grid
138allocate(airefi(klon_glo))
139CALL gr_dyn_fi(1,ii+1,jj+1,klon_glo,aire,airefi)
140! Poles are single points on physics grid
141airefi(1)=sum(aire(1:ii,1))
142airefi(klon_glo)=sum(aire(1:ii,jj+1))
143
144! Sanity check: do total planet area match between physics and dynamics?
145total_area_dyn=sum(aire(1:ii,1:jj+1))
146total_area_phy=sum(airefi(1:klon_glo))
147IF (total_area_dyn/=total_area_phy) THEN
148  WRITE (lunout, *) 'iniphysiq: planet total surface discrepancy !!!'
149  WRITE (lunout, *) '     in the dynamics total_area_dyn=', total_area_dyn
150  WRITE (lunout, *) '  but in the physics total_area_phy=', total_area_phy
151  IF (abs(total_area_dyn-total_area_phy)>0.00001*total_area_dyn) THEN
152    ! stop here if the relative difference is more than 0.001%
153    abort_message = 'planet total surface discrepancy'
154    CALL abort_gcm(modname, abort_message, 1)
155  ENDIF
156ENDIF
157
158
159!$OMP PARALLEL
160! Now generate local lon/lat/cu/cv/area arrays
161call initcomgeomphy
162
163!!!!$OMP PARALLEL PRIVATE(ibegin,iend) &
164!!!     !$OMP SHARED(airefi,cufi,cvfi,lonfi,latfi)
165
166offset=klon_mpi_begin-1
167airephy(1:klon_omp)=airefi(offset+klon_omp_begin:offset+klon_omp_end)
168cuphy(1:klon_omp)=cufi(offset+klon_omp_begin:offset+klon_omp_end)
169cvphy(1:klon_omp)=cvfi(offset+klon_omp_begin:offset+klon_omp_end)
170rlond(1:klon_omp)=lonfi(offset+klon_omp_begin:offset+klon_omp_end)
171rlatd(1:klon_omp)=latfi(offset+klon_omp_begin:offset+klon_omp_end)
172
173! copy over preff , ap() and bp()
174call ini_planete_mod(nlayer,preff,ap,bp)
175
176! copy some fundamental parameters to physics
177! and do some initializations
178call inifis(klon_omp,nlayer,nqtot,pdayref,punjours,nday,ptimestep, &
179            rlatd,rlond,airephy,prad,pg,pr,pcpp)
180
181!$OMP END PARALLEL
182
183
184end subroutine iniphysiq
185
186
187END MODULE iniphysiq_mod
Note: See TracBrowser for help on using the repository browser.