source: LMDZ5/branches/testing/libf/phydev/iniphysiq.F90 @ 1999

Last change on this file since 1999 was 1999, checked in by Laurent Fairhead, 10 years ago

Merged trunk changes r1920:1997 into testing branch

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 3.4 KB
Line 
1!
2! $Id: iniphysiq.F 1403 2010-07-01 09:02:53Z fairhead $
3!
4SUBROUTINE iniphysiq(ngrid, nlayer, punjours, pdayref, ptimestep, plat, plon, &
5    parea, pcu, pcv, prad, pg, pr, pcpp, iflag_phys)
6  USE dimphy, ONLY: klev
7  USE mod_grid_phy_lmdz, ONLY: klon_glo
8  USE mod_phys_lmdz_para, ONLY: klon_omp, klon_omp_begin, klon_omp_end, &
9    klon_mpi_begin
10  USE comgeomphy, ONLY: airephy, cuphy, cvphy, rlond, rlatd
11  USE comcstphy, ONLY: rradius, rg, rr, rcpp
12  USE phyaqua_mod, ONLY: iniaqua
13  IMPLICIT NONE
14  !
15  !=======================================================================
16  !
17  !   Initialisation of the physical constants and some positional and
18  !   geometrical arrays for the physics
19  !
20  !
21  !    ngrid                 Size of the horizontal grid.
22  !                          All internal loops are performed on that grid.
23  !    nlayer                Number of vertical layers.
24  !    pdayref               Day of reference for the simulation
25  !
26  !=======================================================================
27 
28 
29  include "iniprint.h"
30
31  REAL,INTENT(IN) :: prad ! radius of the planet (m)
32  REAL,INTENT(IN) :: pg ! gravitational acceleration (m/s2)
33  REAL,INTENT(IN) :: pr ! ! reduced gas constant R/mu
34  REAL,INTENT(IN) :: pcpp ! specific heat Cp
35  REAL,INTENT(IN) :: punjours ! length (in s) of a standard day
36  INTEGER,INTENT(IN) :: ngrid ! number of horizontal grid points in the physics
37  INTEGER,INTENT(IN) :: nlayer ! number of atmospheric layers
38  REAL,INTENT(IN) :: plat(ngrid) ! latitudes of the physics grid
39  REAL,INTENT(IN) :: plon(ngrid) ! longitudes of the physics grid
40  REAL,INTENT(IN) :: parea(klon_glo) ! area (m2)
41  REAL,INTENT(IN) :: pcu(klon_glo) ! cu coeff. (u_covariant = cu * u)
42  REAL,INTENT(IN) :: pcv(klon_glo) ! cv coeff. (v_covariant = cv * v)
43  INTEGER,INTENT(IN) :: pdayref ! reference day of for the simulation
44  REAL,INTENT(IN) :: ptimestep !physics time step (s)
45  INTEGER,INTENT(IN) :: iflag_phys ! type of physics to be called
46
47  INTEGER :: ibegin,iend,offset
48  CHARACTER (LEN=20) :: modname='iniphysiq'
49  CHARACTER (LEN=80) :: abort_message
50 
51  IF (nlayer.NE.klev) THEN
52    WRITE(lunout,*) 'STOP in ',trim(modname)
53    WRITE(lunout,*) 'Problem with dimensions :'
54    WRITE(lunout,*) 'nlayer     = ',nlayer
55    WRITE(lunout,*) 'klev   = ',klev
56    abort_message = ''
57    CALL abort_gcm (modname,abort_message,1)
58  ENDIF
59
60  IF (ngrid.NE.klon_glo) THEN
61    WRITE(lunout,*) 'STOP in ',trim(modname)
62    WRITE(lunout,*) 'Problem with dimensions :'
63    WRITE(lunout,*) 'ngrid     = ',ngrid
64    WRITE(lunout,*) 'klon   = ',klon_glo
65    abort_message = ''
66    CALL abort_gcm (modname,abort_message,1)
67  ENDIF
68
69  !$OMP PARALLEL PRIVATE(ibegin,iend) &
70  !$OMP          SHARED(parea,pcu,pcv,plon,plat)
71     
72  offset = klon_mpi_begin - 1
73  airephy(1:klon_omp) = parea(offset+klon_omp_begin:offset+klon_omp_end)
74  cuphy(1:klon_omp) = pcu(offset+klon_omp_begin:offset+klon_omp_end)
75  cvphy(1:klon_omp) = pcv(offset+klon_omp_begin:offset+klon_omp_end)
76  rlond(1:klon_omp) = plon(offset+klon_omp_begin:offset+klon_omp_end)
77  rlatd(1:klon_omp) = plat(offset+klon_omp_begin:offset+klon_omp_end)
78
79  ! copy some fundamental parameters to physics
80  rradius=prad
81  rg=pg
82  rr=pr
83  rcpp=pcpp
84
85  !$OMP END PARALLEL
86
87  ! Additional initializations for aquaplanets
88  !$OMP PARALLEL
89  IF (iflag_phys>=100) THEN
90    CALL iniaqua(klon_omp,rlatd,rlond,iflag_phys)
91  ENDIF
92  !$OMP END PARALLEL
93
94END SUBROUTINE iniphysiq
Note: See TracBrowser for help on using the repository browser.