subroutine waq_hyd ( start_time, dtout , nrec , nolay , sigma , & & out_prefix, ns , np , version, nopenbndnodes ) ! Deltares Software Centre !>\file !> Makes call to write Delwaq .hyd file !> !> - Selfe variables are converted towards Delft3D variables !> - Standard Delft3D wrwaqhyd call is made to write a Delwaq .hyd file ! Created : January 2013 By Leo Postma ! Modified : ! Subroutines called : wrwaqhyd ! Logical units : LUN(27) = unit stripped DELWAQ input file implicit none ! Parameters : ! kind function name Descriptipon character(48), intent(in ) :: start_time !< Start time string Selfe real ( 4), intent(in ) :: dtout !< Time step in the Selfe files integer ( 4), intent(in ) :: nrec !< Number of records in the Selfe files integer ( 4), intent(in ) :: nolay !< Number of vertical layers real ( 4), intent(in ) :: sigma(nolay+1) !< Sigma layer thickness character( *), intent(in ) :: out_prefix !< Output files prefix string integer ( 4), intent(in ) :: ns !< Number of horizontal edges 1 layer integer ( 4), intent(in ) :: np !< Number of nodes 1 layer character(48), intent(in ) :: version !< Selfe documentation string integer ( 4), intent(in ) :: nopenbndnodes !< Number of open boundary nodes ! Locals integer ( 4) id, im, iy, ih, imin, is ! integers to store time information integer ( 4) itdate ! Delwaq YYYMMDD integer real ( 4) tstart ! Start time in minutes since itdate real ( 4) dt ! Time step size in minutes real ( 4) tstop ! Stop time in minutes since itdate integer ( 4) itwqff ! First time step number Delwaq integer ( 4) itwqfl ! Last time step number Delwaq integer ( 4) itwqfi ! First Delwaq step in this sequence integer ( 4) aggre ! -1 is no horizontal aggregation character(20) flaggr ! Name of the aggregation file character(128) out_hyd ! Name of the aggregation file integer ( 4) kmax ! Number of Delwaq layers integer ( 4) i ! loop variable integer ( 4) lsal, ltem, lsed ! If > 0 salinity, temperature and sediment logical chez ! If true: Chezy info integer ( 4) nsrc ! Number of point sources integer ( 4) nowalk ! Number of walking discharges logical zmodel ! If true: Call comes from z-model integer ( 4) nd ! Number of domains for domain decomposition integer ( 4) nlb, nub, mlb, mub ! Delft3D array bounds integer ( 4) ns2 ! ns + open boundary links real ( 4), allocatable :: thick (:) ! Sigma thickness of the layers integer ( 4), allocatable :: mnksrc(:,:) ! Location of the sources character(20), allocatable :: namsrc(:) ! Names of the sources integer ( 4), allocatable :: ksrwaq(:) ! Layer information of the sources integer ( 4), allocatable :: iwlk (:) ! Sequence numbers of walking discharges integer ( 4), allocatable :: ilaggr(:) ! Layer aggregation info integer ( 4), allocatable :: kfsmin(:,:) ! Variable lowest active layer (z-model-only) ! The hyd file out_hyd = out_prefix i = len_trim(out_hyd) out_hyd(i:i) = '.' ! Make the timings read ( start_time(1:19), '(i2,1x,i2,1x,i4,1x,i2,1x,i2,1x,i2)' ) im, id, iy, ih, imin, is itdate = iy*10000 + im*100 + id tstart = ih*60 + imin + float(is)/60.0 dt = dtout/60.0 tstop = tstart + float(nrec)*dt tstart = tstart + dt itwqff = tstart/dt + 0.5 itwqfl = tstop /dt + 0.5 itwqfi = 1 ! Horizontal schematisation aggre = -1 flaggr = ' ' ! Layer administration kmax = nolay ns2 = ns + nopenbndnodes allocate ( thick (kmax) ) allocate ( ilaggr(kmax) ) do i = 1, kmax thick (i) = sigma(nolay-i+2) - sigma(nolay-i+1) ilaggr(i) = i enddo ! Z-layer specific zmodel = .false. nd = 1 nlb = 1 ; nub = 1 ; mlb = 1 ; mub = 1 allocate ( kfsmin(nlb:nub,mlb:mub) ) ! Additional variables in output lsal = 0 ltem = 0 lsed = 0 chez = .false. ! Point sources and walking discharges nsrc = 0 allocate ( mnksrc(7,max(1,nsrc)), namsrc(max(1,nsrc)) ) nowalk = 0 allocate ( ksrwaq(2*max(1,nsrc)), iwlk (max(1,nsrc)) ) ! Now write the .hyd file (file of files) call wrwaqhyd ( out_hyd , itdate , tstart , tstop , dt , & & itwqff , itwqfl , itwqfi , ns2 , np , & & kmax , thick , lsal , ltem , lsed , & & chez , nsrc , mnksrc , namsrc , version , & & nowalk , iwlk , aggre , flaggr , zmodel , & & ilaggr , nd , nlb , nub , mlb , & & mub , kfsmin , ksrwaq ) return end