Changeset 2160 for LMDZ5/branches/testing/libf/dyn3dpar
- Timestamp:
- Nov 28, 2014, 4:36:29 PM (10 years ago)
- Location:
- LMDZ5/branches/testing
- Files:
-
- 1 deleted
- 8 edited
- 1 copied
Legend:
- Unmodified
- Added
- Removed
-
LMDZ5/branches/testing
- Property svn:mergeinfo changed
/LMDZ5/trunk merged: 2072,2075-2115,2117-2126,2128-2158
- Property svn:mergeinfo changed
-
LMDZ5/branches/testing/libf/dyn3dpar/abort_gcm.F
r1910 r2160 27 27 C ierr = severity of situation ( = 0 normal ) 28 28 29 character(len=*) modname29 character(len=*), intent(in):: modname 30 30 integer ierr, ierror_mpi 31 character(len=*) message31 character(len=*), intent(in):: message 32 32 33 33 write(lunout,*) 'in abort_gcm' … … 53 53 write(lunout,*) 'Everything is cool' 54 54 else 55 write(lunout,*) 'Houston, we have a problem ', ierr55 write(lunout,*) 'Houston, we have a problem, ierr = ', ierr 56 56 #ifdef CPP_MPI 57 57 C$OMP CRITICAL (MPI_ABORT_GCM) -
LMDZ5/branches/testing/libf/dyn3dpar/gcm.F
r2056 r2160 175 175 !#ifdef CPP_IOIPSL 176 176 CALL conf_gcm( 99, .TRUE. , clesphy0 ) 177 if (mod(iphysiq, iperiod) /= 0) call abort_gcm("conf_gcm", 178 s "iphysiq must be a multiple of iperiod", 1) 177 179 !#else 178 180 ! CALL defrun( 99, .TRUE. , clesphy0 ) -
LMDZ5/branches/testing/libf/dyn3dpar/getparam.F90
r1910 r2160 11 11 12 12 INTERFACE getpar 13 MODULE PROCEDURE ini_getparam,fin_getparam,getparamr,getparami,getparaml13 MODULE PROCEDURE getparamr,getparami,getparaml 14 14 END INTERFACE 15 private getparamr,getparami,getparaml 15 16 16 17 INTEGER, PARAMETER :: out_eff=99 -
LMDZ5/branches/testing/libf/dyn3dpar/guide_p_mod.F90
r2056 r2160 67 67 68 68 SUBROUTINE guide_init 69 69 70 70 USE control_mod 71 71 72 IMPLICIT NONE 72 73 … … 74 75 INCLUDE "paramet.h" 75 76 INCLUDE "netcdf.inc" 77 78 ! For grossismx: 79 include "serre.h" 76 80 77 81 INTEGER :: error,ncidpl,rid,rcod … … 93 97 CALL getpar('guide_add',.false.,guide_add,'for�age constant?') 94 98 CALL getpar('guide_zon',.false.,guide_zon,'guidage moy zonale') 99 if (guide_zon .and. abs(grossismx - 1.) > 0.01) & 100 call abort_gcm("guide_init", & 101 "zonal nudging requires grid regular in longitude", 1) 95 102 96 103 ! Constantes de rappel. Unite : fraction de jour … … 113 120 ! frequences f>0: fx/jour; f<0: tous les f jours; f=0: 1 seule fois. 114 121 IF (iguide_sav.GT.0) THEN 115 iguide_sav=day_step/iguide_sav 122 iguide_sav=day_step/iguide_sav 123 ELSE if (iguide_sav == 0) then 124 iguide_sav = huge(0) 116 125 ELSE 117 126 iguide_sav=day_step*iguide_sav 118 127 ENDIF 119 128 … … 155 164 ncidpl=-99 156 165 if (guide_plevs.EQ.1) then 157 if (ncidpl.eq.-99) then 166 if (ncidpl.eq.-99) then 158 167 rcod=nf90_open('apbp.nc',Nf90_NOWRITe, ncidpl) 159 168 if (rcod.NE.NF_NOERR) THEN … … 163 172 endif 164 173 elseif (guide_plevs.EQ.2) then 165 if (ncidpl.EQ.-99) then 174 if (ncidpl.EQ.-99) then 166 175 rcod=nf90_open('P.nc',Nf90_NOWRITe,ncidpl) 167 176 if (rcod.NE.NF_NOERR) THEN … … 374 383 ENDIF 375 384 376 PRINT *,'---> on rentre dans guide_main'377 385 ! CALL AllGather_Field(ucov,ip1jmp1,llm) 378 386 ! CALL AllGather_Field(vcov,ip1jm,llm) … … 1250 1258 enddo 1251 1259 ENDIF ! guide_reg 1260 1261 if (.not. guide_add) alpha = 1. - exp(- alpha) 1252 1262 1253 1263 END SUBROUTINE tau2alpha -
LMDZ5/branches/testing/libf/dyn3dpar/iniacademic.F90
r2056 r2160 4 4 SUBROUTINE iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0) 5 5 6 use exner_hyb_m, only: exner_hyb 7 use exner_milieu_m, only: exner_milieu 8 USE filtreg_mod 6 USE filtreg_mod, ONLY: inifilr 9 7 USE infotrac, ONLY : nqtot 10 8 USE control_mod, ONLY: day_step,planet_type 11 9 #ifdef CPP_IOIPSL 12 USE IOIPSL 10 USE IOIPSL, ONLY: getin 13 11 #else 14 12 ! if not using IOIPSL, we still need to use (a local version of) getin 15 USE ioipsl_getincom 13 USE ioipsl_getincom, ONLY: getin 16 14 #endif 17 15 USE Write_Field 16 use exner_hyb_m, only: exner_hyb 17 use exner_milieu_m, only: exner_milieu 18 18 19 19 ! Author: Frederic Hourdin original: 15/01/93 … … 40 40 ! ---------- 41 41 42 real time_0 43 44 ! variables dynamiques 45 REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants 46 REAL teta(ip1jmp1,llm) ! temperature potentielle 47 REAL q(ip1jmp1,llm,nqtot) ! champs advectes 48 REAL ps(ip1jmp1) ! pression au sol 49 REAL masse(ip1jmp1,llm) ! masse d'air 50 REAL phis(ip1jmp1) ! geopotentiel au sol 42 REAL,INTENT(OUT) :: time_0 43 44 ! fields 45 REAL,INTENT(OUT) :: vcov(ip1jm,llm) ! meridional covariant wind 46 REAL,INTENT(OUT) :: ucov(ip1jmp1,llm) ! zonal covariant wind 47 REAL,INTENT(OUT) :: teta(ip1jmp1,llm) ! potential temperature (K) 48 REAL,INTENT(OUT) :: q(ip1jmp1,llm,nqtot) ! advected tracers (.../kg_of_air) 49 REAL,INTENT(OUT) :: ps(ip1jmp1) ! surface pressure (Pa) 50 REAL,INTENT(OUT) :: masse(ip1jmp1,llm) ! air mass in grid cell (kg) 51 REAL,INTENT(OUT) :: phis(ip1jmp1) ! surface geopotential 51 52 52 53 ! Local: … … 76 77 character(len=80) :: abort_message 77 78 79 80 ! Sanity check: verify that options selected by user are not incompatible 81 if ((iflag_phys==1).and. .not. read_start) then 82 write(lunout,*) trim(modname)," error: if read_start is set to ", & 83 " false then iflag_phys should not be 1" 84 write(lunout,*) "You most likely want an aquaplanet initialisation", & 85 " (iflag_phys >= 100)" 86 call abort_gcm(modname,"incompatible iflag_phys==1 and read_start==.false.",1) 87 endif 88 78 89 !----------------------------------------------------------------------- 79 90 ! 1. Initializations for Earth-like case … … 224 235 CALL pression ( ip1jmp1, ap, bp, ps, p ) 225 236 if (pressure_exner) then 226 CALL exner_hyb( ip1jmp1, ps, p, pks, pk 237 CALL exner_hyb( ip1jmp1, ps, p, pks, pk) 227 238 else 228 239 call exner_milieu(ip1jmp1,ps,p,pks,pk) -
LMDZ5/branches/testing/libf/dyn3dpar/integrd_p.F
r1910 r2160 137 137 138 138 IF( .NOT. checksum ) THEN 139 write(lunout,*) "integrd: negative surface pressure ", 140 & ps(stop_it) 139 write(lunout,*) "integrd: ps = ", ps(stop_it) 141 140 write(lunout,*) " at node ij =", stop_it 142 141 ! since ij=j+(i-1)*jjp1 , we have … … 145 144 write(lunout,*) " lon = ",rlonv(i)*180./pi, " deg", 146 145 & " lat = ",rlatu(j)*180./pi, " deg" 146 call abort_gcm("integrd_p", "negative surface pressure", 1) 147 147 ENDIF 148 148 -
LMDZ5/branches/testing/libf/dyn3dpar/leapfrog_p.F
r2056 r2160 717 717 CALL exner_milieu_p( ip1jmp1, ps, p, pks, pk, pkf ) 718 718 endif 719 c$OMP BARRIER 719 720 ! Appel a geopot ajoute le 2014/05/08 pour garantir la convergence numerique 720 721 ! avec dyn3dmem 721 CALL geopot ( ip1jmp1, teta , pk , pks, phis , phi )722 c$OMP BARRIER 722 CALL geopot_p ( ip1jmp1, teta , pk , pks, phis , phi ) 723 723 724 jD_cur = jD_ref + day_ini - day_ref 724 725 $ + itau/day_step
Note: See TracChangeset
for help on using the changeset viewer.