source: lmdz_wrf/WRFV3/lmdz/iniphysiq.F90 @ 1

Last change on this file since 1 was 1, checked in by lfita, 10 years ago
  • -- --- Opening of the WRF+LMDZ coupling repository --- -- -

WRF: version v3.3
LMDZ: version v1818

More details in:

File size: 6.6 KB
Line 
1!
2! $Id: iniphysiq.F 1707 2013-01-11 09:19:19Z fairhead $
3!
4!c
5!c
6      SUBROUTINE iniphysiq(ngrid,nlayer,                                             &
7       &           punjours,                                                         &
8       &           pdayref,ptimestep,                                                &
9       &           plat,plon,parea,pcu,pcv,                                          &
10       &           prad,pg,pr,pcpp,iflag_phys)
11      USE dimphy, only : klev
12      USE mod_grid_phy_lmdz, only : klon_glo
13      USE mod_phys_lmdz_para, only : klon_omp,klon_omp_begin,                        &
14       &                               klon_omp_end,klon_mpi_begin
15      USE comgeomphy, only : airephy,cuphy,cvphy,rlond,rlatd
16
17      IMPLICIT NONE
18!c
19!c=======================================================================
20!c
21!c   Initialisation of the physical constants and some positional and
22!c   geometrical arrays for the physics
23!c
24!c
25!c    ngrid                 Size of the horizontal grid.
26!c                          All internal loops are performed on that grid.
27!c    nlayer                Number of vertical layers.
28!c    pdayref               Day of reference for the simulation
29!c
30!c=======================================================================
31 
32!cym#include "dimensions.h"
33!cym#include "dimphy.h"
34!cym#include "comgeomphy.h"
35#include "YOMCST.h"
36#include "iniprint.h"
37
38      REAL,INTENT(IN) :: prad ! radius of the planet (m)
39      REAL,INTENT(IN) :: pg ! gravitational acceleration (m/s2)
40      REAL,INTENT(IN) :: pr ! ! reduced gas constant R/mu
41      REAL,INTENT(IN) :: pcpp ! specific heat Cp
42      REAL,INTENT(IN) :: punjours ! length (in s) of a standard day
43      INTEGER,INTENT(IN) :: ngrid ! number of horizontal grid points in the physics
44      INTEGER,INTENT(IN) :: nlayer ! number of atmospheric layers
45      REAL,INTENT(IN) :: plat(ngrid) ! latitudes of the physics grid
46      REAL,INTENT(IN) :: plon(ngrid) ! longitudes of the physics grid
47      REAL,INTENT(IN) :: parea(klon_glo) ! area (m2)
48      REAL,INTENT(IN) :: pcu(klon_glo) ! cu coeff. (u_covariant = cu * u)
49      REAL,INTENT(IN) :: pcv(klon_glo) ! 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      CHARACTER (LEN=20) :: modname='iniphysiq'
56      CHARACTER (LEN=80) :: abort_message
57 
58      INTEGER :: ix,iy
59
60      IF (nlayer.NE.klev) THEN
61         write(lunout,*) 'STOP in ',trim(modname)
62         write(lunout,*) 'Problem with dimensions :'
63         write(lunout,*) 'nlayer     = ',nlayer
64         write(lunout,*) 'klev   = ',klev
65         abort_message = ''
66         CALL abort_gcm (modname,abort_message,1)
67      ENDIF
68
69      IF (ngrid.NE.klon_glo) THEN
70         write(lunout,*) 'STOP in ',trim(modname)
71         write(lunout,*) 'Problem with dimensions :'
72         write(lunout,*) 'ngrid     = ',ngrid
73         write(lunout,*) 'klon   = ',klon_glo
74         abort_message = ''
75         CALL abort_gcm (modname,abort_message,1)
76      ENDIF
77
78!$OMP PARALLEL PRIVATE(ibegin,iend)
79!$OMP+         SHARED(parea,pcu,pcv,plon,plat)
80     
81      offset=klon_mpi_begin-1
82      airephy(1:klon_omp)=parea(offset+klon_omp_begin:                               &
83       &                          offset+klon_omp_end)
84      cuphy(1:klon_omp)=pcu(offset+klon_omp_begin:offset+klon_omp_end)
85      cvphy(1:klon_omp)=pcv(offset+klon_omp_begin:offset+klon_omp_end)
86      rlond(1:klon_omp)=plon(offset+klon_omp_begin:offset+klon_omp_end)
87      rlatd(1:klon_omp)=plat(offset+klon_omp_begin:offset+klon_omp_end)
88
89      ! suphel => initialize some physical constants (orbital parameters,
90      !           geoid, gravity, thermodynamical constants, etc.) in the
91      !           physics
92      call suphel
93      PRINT *,'Lluis after suphel'
94     
95!$OMP END PARALLEL
96
97      ! check that physical constants set in 'suphel' are coherent
98      ! with values set in the dynamics:
99      if (RDAY.ne.punjours) then
100        write(lunout,*) "iniphysiq: length of day discrepancy!!!"
101        write(lunout,*) "  in the dynamics punjours=",punjours
102        write(lunout,*) "   but in the physics RDAY=",RDAY
103        if (abs(RDAY-punjours).gt.0.01) then
104          ! stop here if the relative difference is more than 1%
105          abort_message = 'length of day discrepancy'
106          CALL abort_gcm (modname,abort_message,1)
107        endif
108      endif
109      if (RG.ne.pg) then
110        write(lunout,*) "iniphysiq: gravity discrepancy !!!"
111        write(lunout,*) "     in the dynamics pg=",pg
112        write(lunout,*) "  but in the physics RG=",RG
113        if (abs(RG-pg).gt.0.01) then
114          ! stop here if the relative difference is more than 1%
115          abort_message = 'gravity discrepancy'
116          CALL abort_gcm (modname,abort_message,1)
117        endif
118      endif
119      if (RA.ne.prad) then
120        write(lunout,*) "iniphysiq: planet radius discrepancy !!!"
121        write(lunout,*) "   in the dynamics prad=",prad
122        write(lunout,*) "  but in the physics RA=",RA
123        if (abs(RA-prad).gt.0.01) then
124          ! stop here if the relative difference is more than 1%
125          abort_message = 'planet radius discrepancy'
126          CALL abort_gcm (modname,abort_message,1)
127        endif
128      endif
129      if (RD.ne.pr) then
130        write(lunout,*)"iniphysiq: reduced gas constant discrepancy !!!"
131        write(lunout,*)"     in the dynamics pr=",pr
132        write(lunout,*)"  but in the physics RD=",RD
133        if (abs(RD-pr).gt.0.01) then
134          ! stop here if the relative difference is more than 1%
135          abort_message = 'reduced gas constant discrepancy'
136          CALL abort_gcm (modname,abort_message,1)
137        endif
138      endif
139      if (RCPD.ne.pcpp) then
140        write(lunout,*)"iniphysiq: specific heat discrepancy !!!"
141        write(lunout,*)"     in the dynamics pcpp=",pcpp
142        write(lunout,*)"  but in the physics RCPD=",RCPD
143        if (abs(RCPD-pcpp).gt.0.01) then
144          ! stop here if the relative difference is more than 1%
145          abort_message = 'specific heat discrepancy'
146          CALL abort_gcm (modname,abort_message,1)
147        endif
148      endif
149
150      PRINT *,'Lluis before iniaqua'
151
152! Additional initializations for aquaplanets
153!$OMP PARALLEL
154      if (iflag_phys>=100) then
155        call iniaqua(klon_omp,rlatd,rlond,iflag_phys)
156      endif
157!$OMP END PARALLEL
158      PRINT *,'Lluis after iniaqua'
159
160!      RETURN
161!9999  CONTINUE
162!      abort_message ='Cette version demande les fichier rnatur.dat
163!     & et surf.def'
164!      CALL abort_gcm (modname,abort_message,1)
165
166      END
Note: See TracBrowser for help on using the repository browser.