! ! $Id: iniphysiq.F 1403 2010-07-01 09:02:53Z fairhead $ ! SUBROUTINE iniphysiq(ngrid,nlayer, $ punjours, $ pdayref,ptimestep, $ plat,plon,parea,pcu,pcv, $ prad,pg,pr,pcpp,iflag_phys) USE dimphy, only : klev USE mod_grid_phy_lmdz, only : klon_glo USE mod_phys_lmdz_para, only : klon_omp,klon_omp_begin, & klon_omp_end,klon_mpi_begin USE comgeomphy, only : airephy,cuphy,cvphy,rlond,rlatd USE comcstphy, only : rradius,rg,rr,rcpp IMPLICIT NONE c c======================================================================= c c Initialisation of the physical constants and some positional and c geometrical arrays for the physics c c c ngrid Size of the horizontal grid. c All internal loops are performed on that grid. c nlayer Number of vertical layers. c pdayref Day of reference for the simulation c c======================================================================= cym#include "dimensions.h" cym#include "dimphy.h" cym#include "comgeomphy.h" #include "iniprint.h" REAL,INTENT(IN) :: prad ! radius of the planet (m) REAL,INTENT(IN) :: pg ! gravitational acceleration (m/s2) REAL,INTENT(IN) :: pr ! ! reduced gas constant R/mu REAL,INTENT(IN) :: pcpp ! specific heat Cp REAL,INTENT(IN) :: punjours ! length (in s) of a standard day INTEGER,INTENT(IN) :: ngrid ! number of horizontal grid points in the physics INTEGER,INTENT(IN) :: nlayer ! number of atmospheric layers REAL,INTENT(IN) :: plat(ngrid) ! latitudes of the physics grid REAL,INTENT(IN) :: plon(ngrid) ! longitudes of the physics grid REAL,INTENT(IN) :: parea(klon_glo) ! area (m2) REAL,INTENT(IN) :: pcu(klon_glo) ! cu coeff. (u_covariant = cu * u) REAL,INTENT(IN) :: pcv(klon_glo) ! cv coeff. (v_covariant = cv * v) INTEGER,INTENT(IN) :: pdayref ! reference day of for the simulation REAL,INTENT(IN) :: ptimestep !physics time step (s) INTEGER,INTENT(IN) :: iflag_phys ! type of physics to be called INTEGER :: ibegin,iend,offset CHARACTER (LEN=20) :: modname='iniphysiq' CHARACTER (LEN=80) :: abort_message IF (nlayer.NE.klev) THEN write(lunout,*) 'STOP in ',trim(modname) write(lunout,*) 'Problem with dimensions :' write(lunout,*) 'nlayer = ',nlayer write(lunout,*) 'klev = ',klev abort_message = '' CALL abort_gcm (modname,abort_message,1) ENDIF IF (ngrid.NE.klon_glo) THEN write(lunout,*) 'STOP in ',trim(modname) write(lunout,*) 'Problem with dimensions :' write(lunout,*) 'ngrid = ',ngrid write(lunout,*) 'klon = ',klon_glo abort_message = '' CALL abort_gcm (modname,abort_message,1) ENDIF !$OMP PARALLEL PRIVATE(ibegin,iend) !$OMP+ SHARED(parea,pcu,pcv,plon,plat) offset=klon_mpi_begin-1 airephy(1:klon_omp)=parea(offset+klon_omp_begin: & offset+klon_omp_end) cuphy(1:klon_omp)=pcu(offset+klon_omp_begin:offset+klon_omp_end) cvphy(1:klon_omp)=pcv(offset+klon_omp_begin:offset+klon_omp_end) rlond(1:klon_omp)=plon(offset+klon_omp_begin:offset+klon_omp_end) rlatd(1:klon_omp)=plat(offset+klon_omp_begin:offset+klon_omp_end) ! copy some fundamental parameters to physics rradius=prad rg=pg rr=pr rcpp=pcpp !$OMP END PARALLEL ! print*,'ATTENTION !!! TRAVAILLER SUR INIPHYSIQ' ! print*,'CONTROLE DES LATITUDES, LONGITUDES, PARAMETRES ...' ! Additional initializations for aquaplanets !$OMP PARALLEL if (iflag_phys>=100) then call iniaqua(klon_omp,rlatd,rlond,iflag_phys) endif !$OMP END PARALLEL ! RETURN !9999 CONTINUE ! abort_message ='Cette version demande les fichier rnatur.dat ! & et surf.def' ! CALL abort_gcm (modname,abort_message,1) END