source: inundation/ga/storm_surge/Hobart/Landslide_1D.for @ 1452

Last change on this file since 1452 was 1444, checked in by chris, 20 years ago
File size: 22.2 KB
Line 
1      program sfbasic
2c============================================================
3c Combine evolution of w = h+z and h for shallow flows
4c============================================================
5
6      implicit none
7
8      integer md,nxmax,nxd, mn
9
10      parameter (md=3, nxmax=5000, nxd=nxmax+2*md, mn=2)
11      real*8 h(nxd), uh(nxd), w(nxd)
12      real*8 z(nxd),z2(nxd)
13      real*8 x(nxd),x2(nxd)
14     
15      integer terrain,bc_l,bc_r,initial,s_h,s_uh,s_semi_uh
16      common /setup/ terrain,bc_l,bc_r,initial,s_h,s_uh,s_semi_uh
17
18      integer nlow,nhigh,nx,nxx,dn,version,isteps     
19      common /ivariables/ nlow,nhigh,nx,nxx,version,isteps
20     
21      real*8 toll,cfl,theta
22      real*8 g,hf,dx,dt,dtmax
23      real*8 Tout,tf,tc,uhf
24      real*8 K,limith,length
25      real*8 manning,hl,hr,zb     
26      common /rvariables/ toll,cfl,theta,
27     .                    g,hf,dx,dt,dtmax,
28     .                    Tout,tf,tc,uhf,
29     .                    K,limith,length,
30     .                    manning,hl,hr
31         
32      integer io, i
33
34      call util_open_files
35
36      open(1,file='MacDonald.bed')
37c
38c Parameters
39c     
40      nx = 101
41      dtmax  = 1.0d0
42      Tout   = 1.0d0
43      tf = 200.0d0
44      length = 1000.0d0
45
46      nlow = md+2
47      nhigh = md+nx
48      nxx = nx+2*md
49     
50      limith = 1
51      dx = 10.d0
52      K = 0.0d0           
53
54      if (nx.gt.nxmax) write(*,*)'nx too large'
55      toll = 1.0d-10
56      cfl = 0.01d0
57      theta = 1.2d0
58      version = 10
59      g = 9.81d0
60      hl = 5.d0
61      hr = 0.d0
62      tc = 0.d0
63     
64c
65c ---- Setup Terrain, Boundary Values and Initial Values
66c
67
68c ---- Non-uniform terrain from MacDonald
69      do i = 1,nxx
70        read(1,*)x2(i),z2(i)
71        z2(i) = z2(i)*5.d0
72        x(i) = x2(i) - dx/2.d0
73      end do
74      do i = 2,nxx
75        z(i) = (z2(i-1)+z2(i))/2.d0
76      end do
77      z(1) = (3.d0*z2(1) - z2(2))/2.d0
78      z(nxx) = (3.d0*z2(nxx-1) - z2(nxx-2))/2.d0
79
80      call boundary_apply(x,h,uh,z)
81
82c ---- Rectangular pulse initial condition
83      do i = md+1, nx+md
84        if (x(i).lt.100.d0.or.x(i).gt.200.d0) then
85          h(i) = hr
86        else
87          h(i) = hl
88        endif
89        uh(i) = 0.0d0
90      end do 
91c
92c ---- Setup for Time looping
93c         
94      isteps = 0
95      tc = 0.0d0
96      call util_dump_solution(h,uh,z)
97c
98c ---- Evolve
99c
100      call evolver_euler(x,h,uh,z,z2)
101c
102c ---- Close down
103c
104      write(15,*)isteps,nxx,version
105      do i=1,nxx
106         write(16,*) x(i)
107      enddo
108     
109      do i=5,nxx-3
110         write(25,*) x(i)
111      enddo
112
113      call util_close_files
114
115      stop
116      end
117c===========================================================
118c Shallow Water Flux
119c===========================================================
120      subroutine flux_huh(f1,f2,h0,uh0,em_x,l1,l2,g,toll)
121      implicit none
122
123      real*8 f1,f2,h0,uh0,z,l1,l2
124      real*8 em_x,g,toll
125     
126      real*8 u,cvel,h,uh,w
127      integer i
128
129c-----------------------------------
130     
131      if(em_x.lt.1.0d-15) then
132         em_x = 1.d-15
133      endif
134 
135      uh = uh0
136      h = h0
137     
138      if(h.le.toll)then
139         u = 0.d0
140         h = 0.0d0
141         uh = 0.0d0
142      else
143         u = uh/h
144      endif
145   
146      cvel = dsqrt( g*h )
147      l1 = u - cvel
148      l2 = u + cvel
149      em_x = dmax1( em_x, dabs(u) + cvel )
150      f1 = uh
151      f2 = uh*u + 0.5d0*g*h**2
152     
153      return
154      end
155c===========================================================
156c Shallow Water Flux
157c===========================================================
158      subroutine flux_huh_old(f1,f2,h0,uh0,z,em_x,l1,l2,g,toll)
159      implicit none
160
161      real*8 f1,f2,h0,uh0,z,l1,l2
162      real*8 em_x,g,toll
163     
164      real*8 u,cvel,h,uh,w
165      integer i
166
167c-----------------------------------
168     
169      if(em_x.lt.1.0d-15) then
170         em_x = 1.d-15
171      endif
172 
173      w = h0+z
174      uh = uh0
175      h = h0
176     
177      if(h.le.toll)then
178         u = 0.d0
179         h = 0.0d0
180         uh = 0.0d0
181      else
182         u = uh / h
183      endif
184      if (abs(u).gt.1.0d1) then
185         u = dsign(1.0d0,u)*1.0d3
186         uh = u*h
187      end if     
188      cvel = dsqrt( g*h )
189      l1 = u - cvel
190      l2 = u + cvel
191      em_x = dmax1( em_x, dabs(u) + cvel )
192      f1 = uh
193      f2 = uh*u + 0.5d0*g*h**2
194     
195      return
196      end
197c===========================================================
198c Shallow Water Flux using h+z and uh variables
199c===========================================================
200      subroutine flux_wuh(f1,f2,w0,uh0,z,em_x,l1,l2,g,toll)
201      implicit none
202
203      real*8 f1,f2,w0,uh0,z
204      real*8 g,toll
205     
206      real*8 h,u,cvel,uh,w,l1,l2,em_x
207      integer i
208
209c-----------------------------------
210
211      if(em_x.lt.1.0d-15) then
212         em_x = 1.d-15
213      endif
214 
215      w = w0
216      uh = uh0
217     
218      h = w - z
219      if(h.le.toll)then
220         u = 0.d0
221         h = 0.0d0
222         uh = 0.0d0
223      else
224         u = uh / h
225      endif
226      if (abs(u).gt.1.0d3) then
227         u = dsign(1.0d0,u)*1.0d3
228         uh = u*h
229      end if     
230      cvel = dsqrt( g*h )
231      l1 = u - cvel
232      l2 = u + cvel
233      em_x = dmax1( em_x, dabs(u) + cvel )
234      f1 = uh
235      f2 = uh*u + 0.5d0*g*h**2
236 
237      return
238      end
239c===============================================================
240c array limiter
241c===============================================================
242      subroutine array_limit_h(h,uh,z2,z,uh_l,uh_r,h_l,h_r,h_2)
243
244      implicit none
245      integer md,nxmax,nxd, mn
246      parameter (md=3, nxmax=5000, nxd=nxmax+2*md, mn=2)
247      real*8 h(nxd), uh(nxd), w(nxd)
248      real*8 z(nxd),z2(nxd)
249      real*8 x(nxd),x2(nxd)
250 
251      integer terrain,bc_l,bc_r,initial,s_h,s_uh,s_semi_uh
252      common /setup/ terrain,bc_l,bc_r,initial,s_h,s_uh,s_semi_uh
253
254      integer nlow,nhigh,nx,nxx,dn,version,isteps     
255      common /ivariables/ nlow,nhigh,nx,nxx,version,isteps
256     
257      real*8 toll,cfl,theta
258      real*8 g,hf,dx,dt,dtmax
259      real*8 Tout,tf,tc,uhf
260      real*8 K,limith,length
261      real*8 manning,hl,hr     
262      common /rvariables/ toll,cfl,theta,
263     .                    g,hf,dx,dt,dtmax,
264     .                    Tout,tf,tc,uhf,
265     .                    K,limith,length,
266     .                    manning,hl,hr
267         
268      real*8 h_2(nxd)
269      real*8 h_l(nxd),h_r(nxd)
270      real*8 h1_l(nxd), h1_r(nxd)
271      real*8 uh_l(nxd), uh_r(nxd)
272     
273      integer sslope(nxd)
274      real*8 xmin,xmic,xminmod,a,b,c,t
275
276      xmin(a,b) = 0.5d0*(dsign(1.d0,a)+dsign(1.d0,b))*
277     .            dmin1(dabs(a),dabs(b))
278      xmic(t,a,b) = xmin(t*xmin(a,b), 0.5d0*(a+b) )
279      xminmod(a,b,c) = xmin(a,xmin(b,c))
280
281     
282      integer i   
283      real*8 dh, hmax, hmin , tt, cc
284      real*8 w0,w1,w2,d0h,d0w,d1h,d1w,d2h,d2w,ddh,ddw
285      real*8 h0,h1,h2,hz
286      real*8 ss0,ss1,ss
287      real*8 dz0,dz1,dz2
288      real*8 hx1,hx2,h_x
289      real*8 froud,d1,d2
290      real*8 gh3,uh2,duh, w_x,dz
291     
292c------------------------------------
293      g = 9.81d0     
294      cc = 0.1d0
295      ss0 = 0.01d0
296      ss1 = 0.01d0
297
298      do i=md,nx+md+2
299
300         h_2(i) = h(i)
301         h0 = h(i-1)
302         h1 = h(i)
303         h2 = h(i+1)
304         
305         dz0 = abs(z2(i-1)-z2(i-2))
306         dz1 = abs(z2(i)  -z2(i-1))
307         dz2 = abs(z2(i+1)-z2(i)  )
308
309         w0 = h0 + z(i-1)
310         w1 = h1 + z(i)
311         w2 = h2 + z(i+1)
312         
313         d1w = w1 - w0
314         d2w = w2 - w1
315         dz  = (z2(i) - z2(i-1))
316               
317c ------- W = H+Z           
318         h_x = xmin( d1w, d2w) - dz
319         
320c ------- Return the left and right values of h in an interval
321         h_l(i)  = h(i)   - 0.5d0*h_x
322         h_r(i)  = h(i)   + 0.5d0*h_x
323         
324c ------- Test for h_l or h_r negative
325         hmin = dmin1(h0,h1,h2)
326         if ( h_l(i) .le. hmin ) then
327            h_l(i) = hmin
328            h_r(i) = h(i) + (h(i) - h_l(i))
329         elseif ( h_r(i) .le. hmin ) then
330            h_r(i) = hmin
331            h_l(i) = h(i) + (h(i) - h_r(i))
332         endif
333      enddo
334c
335c ---- Enforce a minimum height
336c
337      do i=md,nx+md+2
338         hmax = dmax1(h_l(i),h_r(i))
339         if (hmax .lt. 1.0d-3 ) then
340           h_r(i)  = 0.0d0
341           uh_r(i) = 0.0d0
342           h_l(i)  = 0.0d0
343           uh_l(i) = 0.0d0
344           h(i)    = 0.0d0
345           uh(i)   = 0.0d0
346         endif
347      enddo
348c
349c ---- Try for a flat subinterval
350c
351      do i=md,nx+md+2
352         hmax = dmax1(h_l(i),h_r(i))
353         dz  = (z2(i) - z2(i-1))
354
355         if (h_l(i) .lt. 0.01d0*h_r(i) ) then
356           h_r(i)  = sqrt(abs(2.0d0*dz*h(i)))
357         endif
358
359         if (h_r(i) .lt. 0.01d0*h_l(i) ) then         
360           h_l(i)  = sqrt(abs(2.0d0*dz*h(i)))       
361         endif         
362      enddo
363           
364      return
365      end
366c===============================================================
367c array limiter
368c===============================================================
369      subroutine array_limit(u,u_l,u_r)
370
371      implicit none
372      integer md,nxmax,nxd, mn
373      parameter (md=3, nxmax=5000, nxd=nxmax+2*md, mn=2)
374      real*8 h(nxd), uh(nxd), w(nxd)
375      real*8 z(nxd),z2(nxd)
376      real*8 x(nxd),x2(nxd)
377   
378      integer terrain,bc_l,bc_r,initial,s_h,s_uh,s_semi_uh
379      common /setup/ terrain,bc_l,bc_r,initial,s_h,s_uh,s_semi_uh
380
381      integer nlow,nhigh,nx,nxx,dn,version,isteps     
382      common /ivariables/ nlow,nhigh,nx,nxx,version,isteps
383     
384      real*8 toll,cfl,theta
385      real*8 g,hf,dx,dt,dtmax
386      real*8 Tout,tf,tc,uhf
387      real*8 K,limith,length
388      real*8 manning,hl,hr     
389      common /rvariables/ toll,cfl,theta,
390     .                    g,hf,dx,dt,dtmax,
391     .                    Tout,tf,tc,uhf,
392     .                    K,limith,length,
393     .                    manning,hl,hr
394       
395      real*8 u(nxd), u_l(nxd),u_r(nxd)
396      real*8 u_x,d1,d2,d0,ux1
397      real*8 u1_l(nxd),u1_r(nxd)
398      integer i
399     
400      real*8 a,b,t,xmin,xmic
401         
402      xmin(a,b) = 0.5d0*(dsign(1.d0,a)+dsign(1.d0,b))*
403     .            dmin1(dabs(a),dabs(b))
404      xmic(t,a,b) = xmin(t*xmin(a,b), 0.5d0*(a+b) )
405         
406c------------------------------------
407     
408      do i=md,nx+md+2
409          d1 = u(i)   - u(i-1)
410          d2 = u(i+1) - u(i)
411          u_x = xmic( theta, d1, d2 )
412          u_l(i) = u(i) - 0.5d0*u_x
413          u_r(i) = u(i) + 0.5d0*u_x         
414      enddo
415             
416      return
417      end
418c===========================================================
419c Output Routine
420c===========================================================
421      subroutine util_dump_solution(h,uh,z)
422
423      implicit none
424      integer md,nxmax,nxd, mn
425      parameter (md=3, nxmax=5000, nxd=nxmax+2*md, mn=2)
426      real*8 h(nxd), uh(nxd), w(nxd)
427      real*8 z(nxd),z2(nxd)
428      real*8 x(nxd),x2(nxd)
429     
430      integer terrain,bc_l,bc_r,initial,s_h,s_uh,s_semi_uh
431      common /setup/ terrain,bc_l,bc_r,initial,s_h,s_uh,s_semi_uh
432
433      integer nlow,nhigh,nx,nxx,dn,version,isteps     
434      common /ivariables/ nlow,nhigh,nx,nxx,version,isteps
435     
436      real*8 toll,cfl,theta
437      real*8 g,hf,dx,dt,dtmax
438      real*8 Tout,tf,tc,uhf
439      real*8 K,limith,length
440      real*8 manning,hl,hr     
441      common /rvariables/ toll,cfl,theta,
442     .                    g,hf,dx,dt,dtmax,
443     .                    Tout,tf,tc,uhf,
444     .                    K,limith,length,
445     .                    manning,hl,hr
446     
447      integer ii,i
448
449      write(12,*)tc
450     
451      isteps = isteps + 1
452      write(*,*)isteps, tc
453
454      do i = 1, nx+2*md
455c------ Dump h
456           write(13,200)sngl(h(i))
457c------ Dump uh
458           write(14,200)sngl(uh(i))
459c------ Dump w
460           write(11,200)sngl(h(i)+z(i))
461  200 format(e20.8)
462      end do
463
464      return
465      end
466c===============================================================
467c The evolver using euler's method
468c===============================================================
469      subroutine evolver_euler(x,h,uh,z,z2)
470
471      implicit none
472      integer md,nxmax,nxd, mn
473      parameter (md=3, nxmax=5000, nxd=nxmax+2*md, mn=2)
474      real*8 h(nxd), uh(nxd), w(nxd)
475      real*8 z(nxd),z2(nxd)
476      real*8 x(nxd),x2(nxd)
477     
478      integer terrain,bc_l,bc_r,initial,s_h,s_uh,s_semi_uh
479c      common /setup/ terrain,bc_l,bc_r,initial,s_h,s_uh,s_semi_uh
480
481      integer nlow,nhigh,nx,nxx,dn,version,isteps     
482      common /ivariables/ nlow,nhigh,nx,nxx,version,isteps
483     
484      real*8 toll,cfl,theta
485      real*8 g,hf,dx,dt,dtmax
486      real*8 Tout,tf,tc,uhf
487      real*8 K,limith,length
488      real*8 manning,hl,hr     
489      common /rvariables/ toll,cfl,theta,
490     .                    g,hf,dx,dt,dtmax,
491     .                    Tout,tf,tc,uhf,
492     .                    K,limith,length,
493     .                    manning,hl,hr
494     
495      real*8 h_new(nxd),uh_new(nxd)
496      real*8 h_h(nxd),uh_h(nxd)
497      real*8 h_h_x(nxd),uh_h_x(nxd)
498      real*8 h_x(nxd), uh_x(nxd)
499      real*8 f_h(nxd), f_uh(nxd)
500      real*8 f_h_l(nxd), f_uh_l(nxd)
501      real*8 f_h_r(nxd), f_uh_r(nxd)
502      real*8 z_l(nxd),z_r(nxd)
503      real*8 h_2(nxd), uh_2(nxd)
504
505      real*8 h_l(nxd), h_r(nxd), uh_l(nxd), uh_r(nxd)     
506      real*8 z2l, z2r, zl, zr
507       
508      integer io, i, jj, ipos,ip
509      real*8 factor, Ki
510
511      integer istop,iout,nt,ii,oi,i2,m
512      real*8 a,b,t,Tleft,em_x,dtcdx,dtcdx2,dtcdx3
513      real*8 den, xmt,pre, Tnext, em_old, hh
514      real*8 aterm1 ,term1, aterm2 ,term2, aterm3 ,term3
515
516      integer kk
517      real*8 umax, umax2, vmin, q1,q2,q3,h1,h2
518      real*8 Kcal,k1,k2,za,zb,pi
519
520      real*8 fh_l, fuh_l, fh_r, fuh_r
521      real*8 l1_l, l2_l, l1_r, l2_r
522      real*8 a_max, a_min, aa, axa
523 
524c----------------------------------------------------------
525c
526      pi = 2.d0*dtan(1.d0)
527      factor = 1.0d0
528      em_old = 1.0d0
529      tc = 0.d0
530      istop = 0
531      iout = 0
532      nt =0
533      Tleft = dmin1(Tout,tf)
534      Tnext = dmin1(Tout,tf)
535      dt = dmin1(dtmax,Tleft)
536     
537      do i=1,nxx
538         f_h(i)  = 0.0d0
539         f_uh(i) = 0.0d0
540         h_l(i)  = h(i)
541         h_r(i)  = h(i)
542         uh_l(i) = uh(i)
543         uh_r(i) = uh(i)
544      enddo
545
546      call boundary_apply(x,h,uh,z)
547      call array_limit  (uh,uh_l,uh_r)         
548      call array_limit_h(h,uh,z2,z,uh_l,uh_r,h_l,h_r,h_2)
549           
550      do i=1,nxx
551         if ( h(i) .lt. 0.0d0 ) then
552           write(*,*)'i=',i,' h(i) = ',h(i)
553         endif
554      enddo
555
556c------------------------------------------------------
557c
558      do while (.true.)
559c          write(*,*)nt
560          nt = nt+1
561          ii = 1
562
563          call boundary_apply(x,h,uh,z)
564 
565          call array_limit  (uh,uh_l,uh_r)         
566          call array_limit_h(h,uh,z2,z,uh_l,uh_r,h_l,h_r,h_2)
567     
568          do i=1,nxx
569            if ( h(i) .lt. 0.0d0 ) then
570              write(*,*)'i=',i,' h(i) = ',h(i),' nt = ',nt
571            endif
572          enddo   
573
574c-------------------------
575c Flux Calculation
576c-------------------------
577          call numerical_flux_central(h,uh,z2,z,uh_l,uh_r,h_l,h_r,h_2,
578     .                       f_h,f_uh, em_x)
579
580c-----------------------------------------------------
581c Compute time step size according to the input CFL #
582c-----------------------------------------------------
583 1002     dt = dmin1(factor*cfl*dx/em_x,dtmax,Tout)
584c          write(*,*)'dt = ',dt,' factor = ',factor
585          if( ( tc + dt ) .ge. Tnext ) then
586              dt = (Tnext - tc )
587              iout = 1
588              Tnext = Tnext+Tout
589          end if
590          if (Tnext.gt.tf ) then
591              istop = 1
592          endif
593         
594c-------------------------------------------------
595c Compute the values of 'u' at the next time level
596c-------------------------------------------------
597          ipos = 0
598
599          do i = md+2, md+nx
600             
601             h_new(i)  =  h(i)  - dt/dx*( f_h(i)  - f_h(i-1) )
602             uh_new(i) =  uh(i) - dt/dx*( f_uh(i) - f_uh(i-1))
603     .              - dt/dx*g*(z2(i)-z2(i-1))*(h(i))
604
605             if (h_new(i).lt.-1.0d-5) then
606                write(*,*)'h_new(',i,') = ',h_new(i)
607                ipos=1
608             endif
609             
610             if (h_new(i).le.0.0d0) then
611                h_new(i) = 0.0d0
612c - my statement
613                uh_new(i) = 0.d0
614             endif
615             
616          end do
617
618          if(ipos.eq.1) then
619             factor = factor/2.0d0
620             write(*,*)'factor = ',factor
621             goto 1002
622          endif
623
624          do i = md+2,nx+md
625             h(i) = h_new(i)
626             uh(i) = uh_new(i)
627          enddo
628         
629          factor = 1.0d0
630          tc = tc + dt
631
632          if(iout.eq.1) then
633             call util_dump_solution(h,uh,z)
634             
635             call boundary_apply(x,h,uh,z)
636             call array_limit  (uh,uh_l,uh_r)         
637             call array_limit_h(h,uh,z2,z,uh_l,uh_r,h_l,h_r,h_2)
638             iout = 0
639          endif         
640          if(istop.eq.1) go to 1001
641c
642c End timestep
643c
644      end do
645c
646 1001 write(*,*)isteps
647
648      return
649
650      end
651c===========================================================
652c Boundary Conditions
653c
654c Naive Boundary Conditions
655c Inflow, or reflective
656c
657c===========================================================
658      subroutine boundary_apply(x,h,uh,z)
659
660      implicit none
661      integer md,nxmax,nxd, mn
662      parameter (md=3, nxmax=5000, nxd=nxmax+2*md, mn=2)
663      real*8 h(nxd), uh(nxd), w(nxd)
664      real*8 z(nxd),z2(nxd)
665      real*8 x(nxd),x2(nxd)
666     
667      integer terrain,bc_l,bc_r,initial,s_h,s_uh,s_semi_uh
668      common /setup/ terrain,bc_l,bc_r,initial,s_h,s_uh,s_semi_uh
669
670      integer nlow,nhigh,nx,nxx,dn,version,isteps     
671      common /ivariables/ nlow,nhigh,nx,nxx,version,isteps
672     
673      real*8 toll,cfl,theta
674      real*8 g,hf,dx,dt,dtmax
675      real*8 Tout,tf,tc,uhf
676      real*8 K,limith,length
677      real*8 manning,hl,hr     
678      common /rvariables/ toll,cfl,theta,
679     .                    g,hf,dx,dt,dtmax,
680     .                    Tout,tf,tc,uhf,
681     .                    K,limith,length,
682     .                    manning,hl,hr
683           
684      real*8 du,dh,uf,h0,u0,uh0
685      integer ii,i
686     
687c--------------------------------------------------
688
689      do i = 1, md     
690c==================
691c Left Boundary
692c==================
693
694c --- Zero
695        h(i)  =  0.d0
696        uh(i) =  0.d0
697      end do
698             
699      do i = 1, md         
700c==================
701c Right Boundary
702c==================
703
704c --- Zero
705        h(nx+md+i)  =  0.d0
706        uh(nx+md+i) =  0.d0
707c        h(nx+md+1) = h(nx-1)
708c        uh(nx+md+1) = uh(nx-1)
709      end do
710
711      return
712      end
713c===========================================================
714c Numerical Central Flux
715c===========================================================
716      subroutine numerical_flux_central(h,uh,z2,z,uh_l,uh_r,h_l,h_r,
717     .          h_2,f_h,f_uh, em_x)
718
719      implicit none
720      integer md,nxmax,nxd, mn
721      parameter (md=3, nxmax=5000, nxd=nxmax+2*md, mn=2)
722      real*8 h(nxd), uh(nxd), w(nxd)
723      real*8 z(nxd),z2(nxd)
724      real*8 x(nxd),x2(nxd)
725
726c      integer terrain,bc_l,bc_r,initial,s_h,s_uh,s_semi_uh
727c      common /setup/ terrain,bc_l,bc_r,initial,s_h,s_uh,s_semi_uh
728
729      integer nlow,nhigh,nx,nxx,dn,version,isteps     
730      common /ivariables/ nlow,nhigh,nx,nxx,version,isteps
731     
732      real*8 toll,cfl,theta
733      real*8 g,hf,dx,dt,dtmax
734      real*8 Tout,tf,tc,uhf
735      real*8 K,limith,length
736      real*8 manning,hl,hr     
737      common /rvariables/ toll,cfl,theta,
738     .                    g,hf,dx,dt,dtmax,
739     .                    Tout,tf,tc,uhf,
740     .                    K,limith,length,
741     .                    manning,hl,hr
742     
743      real*8 f_h(nxd), f_uh(nxd)
744      real*8 h_2(nxd), uh_2(nxd)
745      real*8 h_l(nxd), h_r(nxd), uh_l(nxd), uh_r(nxd)
746           
747
748      real*8 fh_l, fuh_l, fh_r, fuh_r
749      real*8 l1_l, l2_l, l1_r, l2_r
750      real*8 a_max, a_min, aa, axa
751     
752      integer istop,iout,nt,ii,oi,i2,m,i
753      real*8 a,b,t,Tleft,em_x,dtcdx,dtcdx2,dtcdx3
754c      real*8 den, xmt,pre, Tnext, em_old, hh
755c      real*8 aterm1 ,term1, aterm2 ,term2, aterm3 ,term3
756           
757c-----------------------------------
758   
759      em_x = 1.0d-15
760
761      do i = md,nxx-md+1
762
763c
764c ---- Calculate flux
765c
766
767         call flux_huh(fh_l,fuh_l,h_r(i),uh_r(i),
768     .                 em_x,l1_l,l2_l,g,toll)
769         call flux_huh(fh_r,fuh_r,h_l(i+1),uh_l(i+1),
770     .                 em_x,l1_r,l2_r,g,toll)
771c
772c --- Calculate max wave speed
773c         
774         a_max = dmax1(l2_l,l2_r,0.0d0)
775         a_min = dmin1(l1_l,l1_r,0.0d0)         
776c
777c --- Compute the numerical flux
778c
779         aa = a_max - a_min
780         axa = a_max*a_min
781         if ( aa .gt.  dx*dt/1000.0d0) then
782            h_2(i)  =(a_max*h_l(i+1) - a_min*h_r(i) -
783     .                fh_r + fh_l )/aa
784            f_h(i)  =(a_max*fh_l  - a_min*fh_r  +
785     .                axa*(h_l(i+1)-h_r(i)))/aa
786            f_uh(i) =(a_max*fuh_l - a_min*fuh_r +
787     .                axa*(uh_l(i+1)-uh_r(i)))/aa
788         else
789            h_2(i)  = 0.0d0
790            f_h(i)  = 0.0d0
791            f_uh(i) = 0.0d0
792         endif
793           
794      enddo
795     
796      return
797      end
798c===========================================================
799c Open Files
800c===========================================================
801      subroutine util_open_files
802     
803      open(11,file='data.w')
804      open(12,file='data.t')
805      open(13,file='data.h')
806      open(14,file='data.uh')
807      open(15,file='data.n')
808      open(16,file='data.x')
809
810
811      open(25,file='data.xx')
812     
813      return
814      end
815c===========================================================
816c Close Files
817c===========================================================
818      subroutine util_close_files
819     
820      close(11)
821      close(12)
822      close(13)
823      close(14)
824      close(15)
825      close(16)
826
827      close(25)
828                 
829      return
830      end
Note: See TracBrowser for help on using the repository browser.