source: trunk/LMDZ.VENUS/libf/phyvenus/iniphysiq.F @ 1198

Last change on this file since 1198 was 892, checked in by slebonnois, 12 years ago

SL: Important commit ! Adaptation of Venus physics to parallel computation / template for arch on the LMD servers using ifort / documentation for 1D column physics and for parallel computations

File size: 4.6 KB
RevLine 
[3]1!
2! $Header: /home/cvsroot/LMDZ4/libf/phylmd/iniphysiq.F,v 1.1.1.1 2004/05/19 12:53:08 lmdzadmin Exp $
3!
4c
5c
6      SUBROUTINE iniphysiq(ngrid,nlayer,
7     $           punjours,
8     $           pdayref,ptimestep,
9     $           plat,plon,parea,pcu,pcv,
[841]10     $           prad,pg,pr,pcpp,iflag_phys)
[101]11
[3]12c
13c=======================================================================
14c
15c   subject:
16c   --------
17c
18c   Initialisation for the physical parametrisations of the LMD
19c   martian atmospheric general circulation modele.
20c
21c   author: Frederic Hourdin 15 / 10 /93
22c   -------
23c
24c   arguments:
25c   ----------
26c
27c   input:
28c   ------
29c
30c    ngrid                 Size of the horizontal grid.
31c                          All internal loops are performed on that grid.
32c    nlayer                Number of vertical layers.
33c    pdayref               Day of reference for the simulation
34c    firstcall             True at the first call
35c    lastcall              True at the last call
36c    pday                  Number of days counted from the North. Spring
37c                          equinoxe.
38c
39c=======================================================================
40c
41c-----------------------------------------------------------------------
42c   declarations:
43c   -------------
44 
[892]45      USE dimphy, only : klev
46      USE mod_grid_phy_lmdz, only : klon_glo
47      USE mod_phys_lmdz_para, only : klon_omp,klon_omp_begin,
48     &                               klon_omp_end,klon_mpi_begin
49      USE comgeomphy, only : airephy,cuphy,cvphy,rlond,rlatd
[102]50      IMPLICIT NONE
[892]51#include "iniprint.h"
[3]52
[892]53      REAL,INTENT(IN) :: prad ! radius of the planet (m)
54      REAL,INTENT(IN) :: pg ! gravitational acceleration (m/s2)
55      REAL,INTENT(IN) :: pr ! ! reduced gas constant R/mu
56      REAL,INTENT(IN) :: pcpp ! specific heat Cp
57      REAL,INTENT(IN) :: punjours ! length (in s) of a standard day
58      INTEGER,INTENT(IN) :: ngrid ! number of horizontal grid points in the physics
59      INTEGER,INTENT(IN) :: nlayer ! number of atmospheric layers
60      REAL,INTENT(IN) :: plat(ngrid) ! latitudes of the physics grid
61      REAL,INTENT(IN) :: plon(ngrid) ! longitudes of the physics grid
62      REAL,INTENT(IN) :: parea(klon_glo) ! area (m2)
63      REAL,INTENT(IN) :: pcu(klon_glo) ! cu coeff. (u_covariant = cu * u)
64      REAL,INTENT(IN) :: pcv(klon_glo) ! cv coeff. (v_covariant = cv * v)
65      INTEGER,INTENT(IN) :: pdayref ! reference day of for the simulation
66      REAL,INTENT(IN) :: ptimestep !physics time step (s)
[841]67      INTEGER,INTENT(IN) :: iflag_phys ! type of physics to be called
[892]68
69      INTEGER :: ibegin,iend,offset
70      CHARACTER (LEN=20) :: modname='iniphysiq'
71      CHARACTER (LEN=80) :: abort_message
[3]72 
73      IF (nlayer.NE.klev) THEN
[892]74         write(lunout,*) 'STOP in ',trim(modname)
75         write(lunout,*) 'Problem with dimensions :'
76         write(lunout,*) 'nlayer     = ',nlayer
77         write(lunout,*) 'klev   = ',klev
78         abort_message = ''
79         CALL abort_gcm (modname,abort_message,1)
[3]80      ENDIF
81
[892]82      IF (ngrid.NE.klon_glo) THEN
83         write(lunout,*) 'STOP in ',trim(modname)
84         write(lunout,*) 'Problem with dimensions :'
85         write(lunout,*) 'ngrid     = ',ngrid
86         write(lunout,*) 'klon   = ',klon_glo
87         abort_message = ''
88         CALL abort_gcm (modname,abort_message,1)
[3]89      ENDIF
90
[892]91c$OMP PARALLEL PRIVATE(ibegin,iend)
92c$OMP+         SHARED(parea,pcu,pcv,plon,plat)
93     
94      offset=klon_mpi_begin-1
95      airephy(1:klon_omp)=parea(offset+klon_omp_begin:
96     &                          offset+klon_omp_end)
97      cuphy(1:klon_omp)=pcu(offset+klon_omp_begin:offset+klon_omp_end)
98      cvphy(1:klon_omp)=pcv(offset+klon_omp_begin:offset+klon_omp_end)
99      rlond(1:klon_omp)=plon(offset+klon_omp_begin:offset+klon_omp_end)
100      rlatd(1:klon_omp)=plat(offset+klon_omp_begin:offset+klon_omp_end)
[3]101
102      call suphec
[892]103
104c$OMP END PARALLEL
105
[3]106c     print*,'ATTENTION !!! TRAVAILLER SUR INIPHYSIQ'
107c     print*,'CONTROLE DES LATITUDES, LONGITUDES, PARAMETRES ...'
108
[892]109c      print*,'agagagagagagagagaga'
110c      print*,'klon_mpi_begin =', klon_mpi_begin
111c      print*,'klon_mpi_end =', klon_mpi_end
112c      print*,'klon_mpi =', klon_mpi
113c      print*,'klon_mpi_para_nb =', klon_mpi_para_nb
114c      print*,'klon_mpi_para_begin =', klon_mpi_para_begin
115c      print*,'klon_mpi_para_end  =', klon_mpi_para_end
116c      print*,'mpi_rank =', mpi_rank
117c      print*,'mpi_size =', mpi_size
118c      print*,'mpi_root =', mpi_root
119c      print*,'klon_glo =', klon_glo
120c      print*,'is_mpi_root =',is_mpi_root
121c      print*,'is_omp_root =',is_omp_root
[3]122
[892]123! pas d'inifis ici...
124! est-ce que cursor est utile ? Voir avec Aymeric
125!      cursor = klon_mpi_begin
126!      print*, "CURSOR !!!!", mpi_rank, cursor
127
[3]128      RETURN
129      END
Note: See TracBrowser for help on using the repository browser.