source: trunk/LMDZ.COMMON/libf/dynlonlat_phylonlat/phytitan/iniphysiq_mod.F90 @ 1523

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

All models: More updates to make planetary codes (+Earth) setups converge.

  • in dyn3d_common:
  • convmas.F => convmas.F90
  • enercin.F => enercin.F90
  • flumass.F => flumass.F90
  • massbar.F => massbar.F90
  • tourpot.F => tourpot.F90
  • vitvert.F => vitvert.F90
  • in misc:
  • move "q_sat" from "dyn3d_common" to "misc" (in Earth model, it is also called by the physics)
  • move "write_field" from "dyn3d_common" to "misc"(may be called from physics or dynamics and depends on neither).
  • in phy_common:
  • move "write_field_phy" here since it may be called from any physics package)
  • add module "regular_lonlat_mod" to store global information on lon-lat grid
  • in dynlonlat_phylonlat/phy*:
  • turn "iniphysiq.F90" into module "iniphysiq_mod.F90" (and of course adapt gcm.F[90] and 1D models accordingly)

EM

File size: 8.8 KB
Line 
1!
2! $Id: iniphysiq.F90 2225 2015-03-11 14:55:23Z emillour $
3!
4MODULE iniphysiq_mod
5
6CONTAINS
7
8SUBROUTINE iniphysiq(iim,jjm,nlayer,punjours, pdayref,ptimestep,         &
9                     rlatu,rlatv,rlonu,rlonv,aire,cu,cv,                 &
10                     prad,pg,pr,pcpp,iflag_phys)
11  USE dimphy, ONLY: klev ! number of atmospheric levels
12  USE mod_grid_phy_lmdz, ONLY: klon_glo ! number of atmospheric columns
13                                        ! (on full grid)
14  USE mod_phys_lmdz_para, ONLY: klon_omp, & ! number of columns (on local omp grid)
15                                klon_omp_begin, & ! start index of local omp subgrid
16                                klon_omp_end, & ! end index of local omp subgrid
17                                klon_mpi_begin ! start indes of columns (on local mpi grid)
18  USE comgeomphy, ONLY: initcomgeomphy, &
19                        airephy, & ! physics grid area (m2)
20                        cuphy, & ! cu coeff. (u_covariant = cu * u)
21                        cvphy, & ! cv coeff. (v_covariant = cv * v)
22                        rlond, & ! longitudes
23                        rlatd ! latitudes
24  USE regular_lonlat_mod, ONLY : init_regular_lonlat, &
25                                 east, west, north, south, &
26                                 north_east, north_west, &
27                                 south_west, south_east
28  USE nrtype, ONLY: pi
29  IMPLICIT NONE
30
31  ! =======================================================================
32  ! Initialisation of the physical constants and some positional and
33  ! geometrical arrays for the physics
34  ! =======================================================================
35
36  include "YOMCST.h"
37  include "iniprint.h"
38
39  REAL, INTENT (IN) :: prad ! radius of the planet (m)
40  REAL, INTENT (IN) :: pg ! gravitational acceleration (m/s2)
41  REAL, INTENT (IN) :: pr ! ! reduced gas constant R/mu
42  REAL, INTENT (IN) :: pcpp ! specific heat Cp
43  REAL, INTENT (IN) :: punjours ! length (in s) of a standard day
44  INTEGER, INTENT (IN) :: nlayer ! number of atmospheric layers
45  INTEGER, INTENT (IN) :: iim ! number of atmospheric columns along longitudes
46  INTEGER, INTENT (IN) :: jjm ! number of atompsheric columns along latitudes
47  REAL, INTENT (IN) :: rlatu(jjm+1) ! latitudes of the physics grid
48  REAL, INTENT (IN) :: rlatv(jjm) ! latitude boundaries of the physics grid
49  REAL, INTENT (IN) :: rlonv(iim+1) ! longitudes of the physics grid
50  REAL, INTENT (IN) :: rlonu(iim+1) ! longitude boundaries of the physics grid
51  REAL, INTENT (IN) :: aire(iim+1,jjm+1) ! area of the dynamics grid (m2)
52  REAL, INTENT (IN) :: cu((iim+1)*(jjm+1)) ! cu coeff. (u_covariant = cu * u)
53  REAL, INTENT (IN) :: cv((iim+1)*jjm) ! cv coeff. (v_covariant = cv * v)
54  INTEGER, INTENT (IN) :: pdayref ! reference day of for the simulation
55  REAL, INTENT (IN) :: ptimestep !physics time step (s)
56  INTEGER, INTENT (IN) :: iflag_phys ! type of physics to be called
57
58  INTEGER :: ibegin, iend, offset
59  INTEGER :: i,j
60  CHARACTER (LEN=20) :: modname = 'iniphysiq'
61  CHARACTER (LEN=80) :: abort_message
62  REAL :: total_area_phy, total_area_dyn
63
64  ! boundaries, on global grid
65  REAL,ALLOCATABLE :: boundslon_reg(:,:)
66  REAL,ALLOCATABLE :: boundslat_reg(:,:)
67
68  ! global array, on full physics grid:
69  REAL,ALLOCATABLE :: latfi(:)
70  REAL,ALLOCATABLE :: lonfi(:)
71  REAL,ALLOCATABLE :: cufi(:)
72  REAL,ALLOCATABLE :: cvfi(:)
73  REAL,ALLOCATABLE :: airefi(:)
74
75  IF (nlayer/=klev) THEN
76    WRITE (lunout, *) 'STOP in ', trim(modname)
77    WRITE (lunout, *) 'Problem with dimensions :'
78    WRITE (lunout, *) 'nlayer     = ', nlayer
79    WRITE (lunout, *) 'klev   = ', klev
80    abort_message = ''
81    CALL abort_gcm(modname, 'Problem with dimensions', 1)
82  END IF
83
84  !call init_phys_lmdz(iim,jjm+1,llm,1,(/(jjm-1)*iim+2/))
85 
86  ! init regular global longitude-latitude grid points and boundaries
87  ALLOCATE(boundslon_reg(iim,2))
88  ALLOCATE(boundslat_reg(jjm+1,2))
89 
90  DO i=1,iim
91   boundslon_reg(i,east)=rlonu(i)
92   boundslon_reg(i,west)=rlonu(i+1)
93  ENDDO
94
95  boundslat_reg(1,north)= PI/2
96  boundslat_reg(1,south)= rlatv(1)
97  DO j=2,jjm
98   boundslat_reg(j,north)=rlatv(j-1)
99   boundslat_reg(j,south)=rlatv(j)
100  ENDDO
101  boundslat_reg(jjm+1,north)= rlatv(jjm)
102  boundslat_reg(jjm+1,south)= -PI/2
103
104  ! Write values in module regular_lonlat_mod
105  CALL init_regular_lonlat(iim,jjm+1, rlonv(1:iim), rlatu, &
106                           boundslon_reg, boundslat_reg)
107
108  ! Generate global arrays on full physics grid
109  ALLOCATE(latfi(klon_glo),lonfi(klon_glo),cufi(klon_glo),cvfi(klon_glo))
110  ALLOCATE(airefi(klon_glo))
111
112  IF (klon_glo>1) THEN ! general case
113    ! North pole
114    latfi(1)=rlatu(1)
115    lonfi(1)=0.
116    cufi(1) = cu(1)
117    cvfi(1) = cv(1)
118    DO j=2,jjm
119      DO i=1,iim
120        latfi((j-2)*iim+1+i)= rlatu(j)
121        lonfi((j-2)*iim+1+i)= rlonv(i)
122        cufi((j-2)*iim+1+i) = cu((j-1)*(iim+1)+i)
123        cvfi((j-2)*iim+1+i) = cv((j-1)*(iim+1)+i)
124      ENDDO
125    ENDDO
126    ! South pole
127    latfi(klon_glo)= rlatu(jjm+1)
128    lonfi(klon_glo)= 0.
129    cufi(klon_glo) = cu((iim+1)*jjm+1)
130    cvfi(klon_glo) = cv((iim+1)*jjm-iim)
131
132    ! build airefi(), mesh area on physics grid
133    CALL gr_dyn_fi(1,iim+1,jjm+1,klon_glo,aire,airefi)
134    ! Poles are single points on physics grid
135    airefi(1)=sum(aire(1:iim,1))
136    airefi(klon_glo)=sum(aire(1:iim,jjm+1))
137
138    ! Sanity check: do total planet area match between physics and dynamics?
139    total_area_dyn=sum(aire(1:iim,1:jjm+1))
140    total_area_phy=sum(airefi(1:klon_glo))
141    IF (total_area_dyn/=total_area_phy) THEN
142      WRITE (lunout, *) 'iniphysiq: planet total surface discrepancy !!!'
143      WRITE (lunout, *) '     in the dynamics total_area_dyn=', total_area_dyn
144      WRITE (lunout, *) '  but in the physics total_area_phy=', total_area_phy
145      IF (abs(total_area_dyn-total_area_phy)>0.00001*total_area_dyn) THEN
146        ! stop here if the relative difference is more than 0.001%
147        abort_message = 'planet total surface discrepancy'
148        CALL abort_gcm(modname, abort_message, 1)
149      ENDIF
150    ENDIF
151  ELSE ! klon_glo==1, running the 1D model
152    ! just copy over input values
153    latfi(1)=rlatu(1)
154    lonfi(1)=rlonv(1)
155    cufi(1)=cu(1)
156    cvfi(1)=cv(1)
157    airefi(1)=aire(1,1)
158  ENDIF ! of IF (klon_glo>1)
159
160!$OMP PARALLEL
161  ! Now generate local lon/lat/cu/cv/area arrays
162  CALL initcomgeomphy
163
164  offset = klon_mpi_begin - 1
165  airephy(1:klon_omp) = airefi(offset+klon_omp_begin:offset+klon_omp_end)
166  cuphy(1:klon_omp) = cufi(offset+klon_omp_begin:offset+klon_omp_end)
167  cvphy(1:klon_omp) = cvfi(offset+klon_omp_begin:offset+klon_omp_end)
168  rlond(1:klon_omp) = lonfi(offset+klon_omp_begin:offset+klon_omp_end)
169  rlatd(1:klon_omp) = latfi(offset+klon_omp_begin:offset+klon_omp_end)
170
171  ! Initialize some physical constants
172  call suphec
173
174!$OMP END PARALLEL
175
176  ! check that physical constants set in 'suphec' are coherent
177  ! with values set in the dynamics:
178  IF (rday/=punjours) THEN
179    WRITE (lunout, *) 'iniphysiq: length of day discrepancy!!!'
180    WRITE (lunout, *) '  in the dynamics punjours=', punjours
181    WRITE (lunout, *) '   but in the physics RDAY=', rday
182    IF (abs(rday-punjours)>0.01*punjours) THEN
183        ! stop here if the relative difference is more than 1%
184      abort_message = 'length of day discrepancy'
185      CALL abort_gcm(modname, abort_message, 1)
186    END IF
187  END IF
188
189  IF (rg/=pg) THEN
190    WRITE (lunout, *) 'iniphysiq: gravity discrepancy !!!'
191    WRITE (lunout, *) '     in the dynamics pg=', pg
192    WRITE (lunout, *) '  but in the physics RG=', rg
193    IF (abs(rg-pg)>0.01*pg) THEN
194        ! stop here if the relative difference is more than 1%
195      abort_message = 'gravity discrepancy'
196      CALL abort_gcm(modname, abort_message, 1)
197    END IF
198  END IF
199  IF (ra/=prad) THEN
200    WRITE (lunout, *) 'iniphysiq: planet radius discrepancy !!!'
201    WRITE (lunout, *) '   in the dynamics prad=', prad
202    WRITE (lunout, *) '  but in the physics RA=', ra
203    IF (abs(ra-prad)>0.01*prad) THEN
204        ! stop here if the relative difference is more than 1%
205      abort_message = 'planet radius discrepancy'
206      CALL abort_gcm(modname, abort_message, 1)
207    END IF
208  END IF
209  IF (rd/=pr) THEN
210    WRITE (lunout, *) 'iniphysiq: reduced gas constant discrepancy !!!'
211    WRITE (lunout, *) '     in the dynamics pr=', pr
212    WRITE (lunout, *) '  but in the physics RD=', rd
213    IF (abs(rd-pr)>0.01*pr) THEN
214        ! stop here if the relative difference is more than 1%
215      abort_message = 'reduced gas constant discrepancy'
216      CALL abort_gcm(modname, abort_message, 1)
217    END IF
218  END IF
219  IF (rcpd/=pcpp) THEN
220    WRITE (lunout, *) 'iniphysiq: specific heat discrepancy !!!'
221    WRITE (lunout, *) '     in the dynamics pcpp=', pcpp
222    WRITE (lunout, *) '  but in the physics RCPD=', rcpd
223    IF (abs(rcpd-pcpp)>0.01*pcpp) THEN
224        ! stop here if the relative difference is more than 1%
225      abort_message = 'specific heat discrepancy'
226      CALL abort_gcm(modname, abort_message, 1)
227    END IF
228  END IF
229
230END SUBROUTINE iniphysiq
231
232END MODULE iniphysiq_mod
Note: See TracBrowser for help on using the repository browser.