! ! $Id: iniphysiq.F 1403 2010-07-01 09:02:53Z fairhead $ ! c c SUBROUTINE iniphysiq(ngrid,nlayer, $ punjours, $ pdayref,ptimestep, $ plat,plon,parea,pcu,pcv, $ prad,pg,pr,pcpp,iflag_phys) USE dimphy USE mod_grid_phy_lmdz USE mod_phys_lmdz_para USE comgeomphy USE infotrac, only: nqtot #ifdef CPP_IOIPSL use IOIPSL #else ! if not using IOIPSL, we still need to use (a local version of) getin use ioipsl_getincom #endif IMPLICIT NONE c c======================================================================= c c subject: c -------- c c Initialisation for the physical parametrisations of the LMD c martian atmospheric general circulation modele. c c author: Frederic Hourdin 15 / 10 /93 c ------- c c arguments: c ---------- c c input: 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 firstcall True at the first call c lastcall True at the last call c pday Number of days counted from the North. Spring c equinoxe. c c======================================================================= c c AS: modified for generic physiq c c----------------------------------------------------------------------- c declarations: c ------------- cym#include "dimensions.h" cym#include "dimphy.h" cym#include "comgeomphy.h" #include "dimensions.h" #include "dimphys.h" !#include "advtrac.h" !iadv is already in infotrac but not invoked here #include "control.h" REAL prad,pg,pr,pcpp,punjours INTEGER ngrid,nlayer !REAL plat(ngrid),plon(ngrid),parea(klon_glo) REAL plat(ngrid),plon(ngrid),parea(ngrid) REAL pcu(ngrid),pcv(ngrid) INTEGER pdayref INTEGER :: ibegin,iend,offset INTEGER,INTENT(IN) :: iflag_phys ! type of physics to be called INTEGER :: ngrid_sub REAL ptimestep CHARACTER (LEN=20) :: modname='iniphysiq' CHARACTER (LEN=80) :: abort_message IF (nlayer.NE.klev) THEN PRINT*,'STOP in iniphysiq' PRINT*,'Probleme de dimensions :' PRINT*,'nlayer = ',nlayer PRINT*,'klev = ',klev abort_message = '' CALL abort_gcm (modname,abort_message,1) ENDIF ngrid_sub = klon_mpi_end - klon_mpi_begin + 1 IF (ngrid_sub.NE.klon) THEN PRINT*,'STOP in iniphysiq' PRINT*,'Probleme de dimensions :' PRINT*,'ngrid = ', ngrid_sub PRINT*,'klon = ', klon abort_message = '' CALL abort_gcm (modname,abort_message,1) ENDIF !!!! WE HAVE TO FILL control.h FOR GENERIC PHYSICS !!! -- NOT USED: periodav, nday, iperiod, iconser, idissip, anneeref !!! -- NEEDED : day_step, iphysiq, ecritphy !!!! 1. not done in conf_gcm ecritphy=1 call getin("ecritphy",ecritphy) PRINT*,"ecritphy = ",ecritphy !!!! 2. done in conf_gcm, present in control_mod, !!!! but conflict if both control_mod.F90 and control.h! day_step=240 call getin("day_step",day_step) PRINT*,"day_step = ",day_step iphysiq = 5 call getin("iphysiq",iphysiq) PRINT*,"iphysiq = ",iphysiq c$OMP PARALLEL PRIVATE(ibegin,iend) c$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) !call suphel print*,'not earth physics. we do not call suphel.' c$OMP END PARALLEL !print*,'ATTENTION !!! TRAVAILLER SUR INIPHYSIQ' !print*,'CONTROLE DES LATITUDES, LONGITUDES, PARAMETRES ...' !print*, "BEFORE CORREC....", RA, RG, RD, RCPD !print*, '------------------' !print*, 'RAD ', prad, RA, 100.*abs((prad - RA)/RA) !if (100.*abs((prad - RA)/RA) .gt. 0.1) RA = prad !print*, '------------------' !print*, 'G ', pg, RG, 100.*abs((pg - RG)/RG) !if (100.*abs((pg - RG)/RG) .gt. 0.1) RG = pg !print*, '------------------' !print*, 'R ', pr, RD, 100.*abs((pr - RD)/RD) !if (100.*abs((pr - RD)/RD) .gt. 0.1) RD = pr !print*, '------------------' !print*, 'CP ', pcpp, RCPD, 100.*abs((pcpp - RCPD)/RCPD) !if (100.*abs((pcpp - RCPD)/RCPD) .gt. 0.1) RCPD = pcpp !print*, "AFTER CORREC....", RA, RG, RD, RCPD print*,'agagagagagagagagaga' print*,'klon_mpi_begin =', klon_mpi_begin print*,'klon_mpi_end =', klon_mpi_end print*,'klon_mpi =', klon_mpi print*,'klon_mpi_para_nb =', klon_mpi_para_nb print*,'klon_mpi_para_begin =', klon_mpi_para_begin print*,'klon_mpi_para_end =', klon_mpi_para_end print*,'mpi_rank =', mpi_rank print*,'mpi_size =', mpi_size print*,'mpi_root =', mpi_root print*,'klon_glo =', klon_glo print*,'is_mpi_root =',is_mpi_root print*,'is_omp_root =',is_omp_root !!! AS: CALL inifis (previously done in calfis in planeto version of GCM) !!! punjours --> daysec !!! pdayref --> day_ini print*, "START INIFIS !!!!" call inifis(klon,nlayer, $ pdayref,punjours,ptimestep, $ plat(klon_mpi_begin:klon_mpi_end), $ plon(klon_mpi_begin:klon_mpi_end), $ parea(klon_mpi_begin:klon_mpi_end), $ prad,pg,pr,pcpp) print*, "END INIFIS !!!!" !! this is an addition to dimphys.h !! initialized in inifis for sequential runs with previous dyn core !! modified here for parallel runs cursor = klon_mpi_begin print*, "CURSOR !!!!", mpi_rank, cursor !!OKOKOKOKOK !!print*, plat,plon,parea,prad,pg,pr,pcpp ! RETURN !9999 CONTINUE ! abort_message ='Cette version demande les fichier rnatur.dat ! & et surf.def' ! CALL abort_gcm (modname,abort_message,1) END