source: LMDZ5/trunk/libf/phydev/iniphysiq.F @ 1907

Last change on this file since 1907 was 1907, checked in by lguez, 10 years ago

Added a copyright property to every file of the distribution, except
for the fcm files (which have their own copyright). Use svn propget on
a file to see the copyright. For instance:

$ svn propget copyright libf/phylmd/physiq.F90
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

Also added the files defining the CeCILL version 2 license, in French
and English, at the top of the LMDZ tree.

  • 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: 4.0 KB
Line 
1!
2! $Id: iniphysiq.F 1403 2010-07-01 09:02:53Z fairhead $
3!
4      SUBROUTINE iniphysiq(ngrid,nlayer,
5     $           punjours,
6     $           pdayref,ptimestep,
7     $           plat,plon,parea,pcu,pcv,
8     $           prad,pg,pr,pcpp,iflag_phys)
9      USE dimphy, only : klev
10      USE mod_grid_phy_lmdz, only : klon_glo
11      USE mod_phys_lmdz_para, only : klon_omp,klon_omp_begin,
12     &                               klon_omp_end,klon_mpi_begin
13      USE comgeomphy, only : airephy,cuphy,cvphy,rlond,rlatd
14      USE comcstphy, only : rradius,rg,rr,rcpp
15
16      IMPLICIT NONE
17c
18c=======================================================================
19c
20c   Initialisation of the physical constants and some positional and
21c   geometrical arrays for the physics
22c
23c
24c    ngrid                 Size of the horizontal grid.
25c                          All internal loops are performed on that grid.
26c    nlayer                Number of vertical layers.
27c    pdayref               Day of reference for the simulation
28c
29c=======================================================================
30 
31 
32cym#include "dimensions.h"
33cym#include "dimphy.h"
34cym#include "comgeomphy.h"
35#include "iniprint.h"
36
37      REAL,INTENT(IN) :: prad ! radius of the planet (m)
38      REAL,INTENT(IN) :: pg ! gravitational acceleration (m/s2)
39      REAL,INTENT(IN) :: pr ! ! reduced gas constant R/mu
40      REAL,INTENT(IN) :: pcpp ! specific heat Cp
41      REAL,INTENT(IN) :: punjours ! length (in s) of a standard day
42      INTEGER,INTENT(IN) :: ngrid ! number of horizontal grid points in the physics
43      INTEGER,INTENT(IN) :: nlayer ! number of atmospheric layers
44      REAL,INTENT(IN) :: plat(ngrid) ! latitudes of the physics grid
45      REAL,INTENT(IN) :: plon(ngrid) ! longitudes of the physics grid
46      REAL,INTENT(IN) :: parea(klon_glo) ! area (m2)
47      REAL,INTENT(IN) :: pcu(klon_glo) ! cu coeff. (u_covariant = cu * u)
48      REAL,INTENT(IN) :: pcv(klon_glo) ! cv coeff. (v_covariant = cv * v)
49      INTEGER,INTENT(IN) :: pdayref ! reference day of for the simulation
50      REAL,INTENT(IN) :: ptimestep !physics time step (s)
51      INTEGER,INTENT(IN) :: iflag_phys ! type of physics to be called
52
53      INTEGER :: ibegin,iend,offset
54      CHARACTER (LEN=20) :: modname='iniphysiq'
55      CHARACTER (LEN=80) :: abort_message
56 
57      IF (nlayer.NE.klev) THEN
58         write(lunout,*) 'STOP in ',trim(modname)
59         write(lunout,*) 'Problem with dimensions :'
60         write(lunout,*) 'nlayer     = ',nlayer
61         write(lunout,*) 'klev   = ',klev
62         abort_message = ''
63         CALL abort_gcm (modname,abort_message,1)
64      ENDIF
65
66      IF (ngrid.NE.klon_glo) THEN
67         write(lunout,*) 'STOP in ',trim(modname)
68         write(lunout,*) 'Problem with dimensions :'
69         write(lunout,*) 'ngrid     = ',ngrid
70         write(lunout,*) 'klon   = ',klon_glo
71         abort_message = ''
72         CALL abort_gcm (modname,abort_message,1)
73      ENDIF
74
75!$OMP PARALLEL PRIVATE(ibegin,iend)
76!$OMP+         SHARED(parea,pcu,pcv,plon,plat)
77     
78      offset=klon_mpi_begin-1
79      airephy(1:klon_omp)=parea(offset+klon_omp_begin:
80     &                          offset+klon_omp_end)
81      cuphy(1:klon_omp)=pcu(offset+klon_omp_begin:offset+klon_omp_end)
82      cvphy(1:klon_omp)=pcv(offset+klon_omp_begin:offset+klon_omp_end)
83      rlond(1:klon_omp)=plon(offset+klon_omp_begin:offset+klon_omp_end)
84      rlatd(1:klon_omp)=plat(offset+klon_omp_begin:offset+klon_omp_end)
85
86! copy some fundamental parameters to physics
87      rradius=prad
88      rg=pg
89      rr=pr
90      rcpp=pcpp
91
92!$OMP END PARALLEL
93
94!      print*,'ATTENTION !!! TRAVAILLER SUR INIPHYSIQ'
95!      print*,'CONTROLE DES LATITUDES, LONGITUDES, PARAMETRES ...'
96
97! Additional initializations for aquaplanets
98!$OMP PARALLEL
99      if (iflag_phys>=100) then
100        call iniaqua(klon_omp,rlatd,rlond,iflag_phys)
101      endif
102!$OMP END PARALLEL
103
104!      RETURN
105!9999  CONTINUE
106!      abort_message ='Cette version demande les fichier rnatur.dat
107!     & et surf.def'
108!      CALL abort_gcm (modname,abort_message,1)
109
110      END
Note: See TracBrowser for help on using the repository browser.