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

Last change on this file since 4187 was 4182, checked in by dubos, 5 years ago

simple_physics : ongoing cleanup

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      REAL prad,pg,pr,pcpp,punjours
53 
54      INTEGER ngrid,nlayer,iflag_phys
55      REAL plat(ngrid),plon(ngrid),parea(klon_glo)
56      REAL pcu(klon_glo),pcv(klon_glo)
57      INTEGER pdayref
58      INTEGER :: ibegin,iend,offset,indmin,indmax
59      REAL pi
60 
61      REAL ptimestep
62      CHARACTER (LEN=20) :: modname='iniphysiq'
63      CHARACTER (LEN=80) :: abort_message
64
65      pi=2.*asin(1.)
66      print*,'INInnn ENTREE DANS INIPHYSIQ'
67      IF (nlayer.NE.klev) THEN
68         PRINT*,'STOP in inifis'
69         PRINT*,'Probleme de dimensions :'
70         PRINT*,'nlayer     = ',nlayer
71         PRINT*,'klev   = ',klev
72         abort_message = ''
73         CALL abort_gcm (modname,abort_message,1)
74      ENDIF
75
76      IF (ngrid.NE.klon_omp) THEN
77         PRINT*,'STOP in inifis'
78         PRINT*,'Probleme de dimensions :'
79         PRINT*,'ngrid     = ',ngrid
80         PRINT*,'klon   = ',klon_omp
81         abort_message = ''
82         CALL abort_gcm (modname,abort_message,1)
83      ENDIF
84c$OMP PARALLEL PRIVATE(ibegin,iend)
85c$OMP+         SHARED(parea,pcu,pcv,plon,plat)
86     
87      print*,'Dans iniphysiq '
88      offset=klon_mpi_begin-1
89!     cell_area(1:klon_omp)=parea(offset+klon_omp_begin:
90!    &                          offset+klon_omp_end)
91      !cuphy(1:klon_omp)=pcu(offset+klon_omp_begin:offset+klon_omp_end)
92      !cvphy(1:klon_omp)=pcv(offset+klon_omp_begin:offset+klon_omp_end)
93      indmin=offset+klon_omp_begin
94      indmax=offset+klon_omp_end
95!     longitude_deg(1:klon_omp)=180./pi*lonfi(indmin:indmax)
96!     latitude_deg(1:klon_omp)=180./pi*latfi(indmin:indmax)
97       print*,'latitude0 deg ',latitude_deg(1),latitude_deg(klon_omp)
98
99!     call suphel
100!     prad,pg,pr,pcpp
101!      rradius=prad
102!      rg=pg
103!      rr=pr
104!      rcpp=pcpp
105
106!     return
107     
108      CALL iniphyparam(ngrid,nlayer,
109     $           punjours,
110     $           pdayref,ptimestep,
111     $           prad,pg,pr,pcpp)
112
113
114      print*,'OK iniphyparam ',size(plat)
115
116c$OMP END PARALLEL
117
118      print*,'ATTENTION !!! TRAVAILLER SUR INIPHYSIQ'
119      print*,'CONTROLE DES LATITUDES, LONGITUDES, PARAMETRES ...'
120
121      RETURN
1229999  CONTINUE
123      abort_message ='Cette version demande les fichier rnatur.dat
124     & et surf.def'
125      CALL abort_gcm (modname,abort_message,1)
126
127
128      END
Note: See TracBrowser for help on using the repository browser.