source: trunk/LMDZ.GENERIC/libf/phystd/iniphysiq.F90 @ 1395

Last change on this file since 1395 was 1395, checked in by emillour, 10 years ago

All GCMS:
Some cleanup and tidying on the dynamics/physics interface.
Essentially affects the "iniphysiq" routine in all physics packages.
EM

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