source: dynamico_lmdz/simple_physics/phyparam/param/iniphysiq_param.F @ 4181

Last change on this file since 4181 was 4176, checked in by dubos, 6 years ago

simple_physics : copy code from FH

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