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

Last change on this file since 1615 was 1615, checked in by Ehouarn Millour, 12 years ago

Introducing "phydev", the minimal physics package.
makegcm and makelmdz_fcm script have been updated to add CPP_PHYS preprocessing key when building with physics and CPP_EARTH for Earth (LMD physics) related routines or instructions in the dynamics.
Checked (on Vargas) that "dev" physics package compiles and runs well in all (seq/mpi/omp/mpi_omp) modes and that introduced changes do not modify results when using the "lmd" physics package.
EM + FH

File size: 3.2 KB
Line 
1!
2! $Id: iniphysiq.F 1403 2010-07-01 09:02:53Z fairhead $
3!
4c
5c
6      SUBROUTINE iniphysiq(ngrid,nlayer,
7     $           punjours,
8     $           pdayref,ptimestep,
9     $           plat,plon,parea,pcu,pcv,
10     $           prad,pg,pr,pcpp)
11      USE dimphy
12      USE mod_grid_phy_lmdz
13      USE mod_phys_lmdz_para
14      USE comgeomphy
15
16      IMPLICIT NONE
17c
18c=======================================================================
19c
20c   subject:
21c   --------
22c
23c   Initialisation for the physical parametrisations of the LMD
24c   martian atmospheric general circulation modele.
25c
26c   author: Frederic Hourdin 15 / 10 /93
27c   -------
28c
29c   arguments:
30c   ----------
31c
32c   input:
33c   ------
34c
35c    ngrid                 Size of the horizontal grid.
36c                          All internal loops are performed on that grid.
37c    nlayer                Number of vertical layers.
38c    pdayref               Day of reference for the simulation
39c    firstcall             True at the first call
40c    lastcall              True at the last call
41c    pday                  Number of days counted from the North. Spring
42c                          equinoxe.
43c
44c=======================================================================
45c
46c-----------------------------------------------------------------------
47c   declarations:
48c   -------------
49 
50cym#include "dimensions.h"
51cym#include "dimphy.h"
52cym#include "comgeomphy.h"
53#include "comcstphy.h"
54      REAL prad,pg,pr,pcpp,punjours
55 
56      INTEGER ngrid,nlayer
57      REAL plat(ngrid),plon(ngrid),parea(klon_glo)
58      REAL pcu(klon_glo),pcv(klon_glo)
59      INTEGER pdayref
60      INTEGER :: ibegin,iend,offset
61 
62      REAL ptimestep
63      CHARACTER (LEN=20) :: modname='iniphysiq'
64      CHARACTER (LEN=80) :: abort_message
65 
66      IF (nlayer.NE.klev) THEN
67         PRINT*,'STOP in inifis'
68         PRINT*,'Probleme de dimensions :'
69         PRINT*,'nlayer     = ',nlayer
70         PRINT*,'klev   = ',klev
71         abort_message = ''
72         CALL abort_gcm (modname,abort_message,1)
73      ENDIF
74
75      IF (ngrid.NE.klon_glo) THEN
76         PRINT*,'STOP in inifis'
77         PRINT*,'Probleme de dimensions :'
78         PRINT*,'ngrid     = ',ngrid
79         PRINT*,'klon   = ',klon_glo
80         abort_message = ''
81         CALL abort_gcm (modname,abort_message,1)
82      ENDIF
83c$OMP PARALLEL PRIVATE(ibegin,iend)
84c$OMP+         SHARED(parea,pcu,pcv,plon,plat)
85     
86      offset=klon_mpi_begin-1
87      airephy(1:klon_omp)=parea(offset+klon_omp_begin:
88     &                          offset+klon_omp_end)
89      cuphy(1:klon_omp)=pcu(offset+klon_omp_begin:offset+klon_omp_end)
90      cvphy(1:klon_omp)=pcv(offset+klon_omp_begin:offset+klon_omp_end)
91      rlond(1:klon_omp)=plon(offset+klon_omp_begin:offset+klon_omp_end)
92      rlatd(1:klon_omp)=plat(offset+klon_omp_begin:offset+klon_omp_end)
93
94!     call suphel
95!     prad,pg,pr,pcpp
96      rradius=prad
97      rg=pg
98      rr=pr
99      rcpp=pcpp
100
101     
102
103c$OMP END PARALLEL
104
105      print*,'ATTENTION !!! TRAVAILLER SUR INIPHYSIQ'
106      print*,'CONTROLE DES LATITUDES, LONGITUDES, PARAMETRES ...'
107
108      RETURN
1099999  CONTINUE
110      abort_message ='Cette version demande les fichier rnatur.dat
111     & et surf.def'
112      CALL abort_gcm (modname,abort_message,1)
113
114      END
Note: See TracBrowser for help on using the repository browser.