流体伝熱基礎講座 - nagoya institute of...

36
Nagoya Institute of Technology 名古屋工業大学大学院 物理工学専攻 後藤俊幸 流体伝熱基礎講座 第2回 午後 中部CAE懇話会

Upload: others

Post on 18-Feb-2021

1 views

Category:

Documents


0 download

TRANSCRIPT

  • Nagoya Institute of Technology

    名古屋工業大学大学院

    物理工学専攻

    後藤俊幸

    流体伝熱基礎講座

    第2回 午後

    中部CAE懇話会

  • Nagoya Institute of Technology

    拡散方程式

    境界条件

    初期条件

    素解 ( f(x)=δ(x-x0) に対する解 無限領域)

  • Nagoya Institute of Technology

    保存量(計算のチェック)

    離散化 (単純オイラー法)

    境界条件はノイマン条件

    u の総量は保存される

  • Nagoya Institute of Technology

    ! Diffusion equation in 1D by Simple Eulerimplicit real*8 (a-h,o-z)integer pout,gdraw,nx,tmaxreal*8 kappaparameter(nx=50, kappa=0.1, dt=0.001, ibs=0)

    !(x軸の格子点数、拡散係数、 dt、 境界条件のスイッチ)parameter(tmax=400, gdraw=40)

    !(時間ステップ数、結果を書き出す時間幅)dimension u(0:nx),uold(0:nx)

    dx=1.d0/dfloat(nx)dx2i=1.d0/dx/dxpi=4.d0*atan(1.d0)amp=1.d-1 t_init=0.001

    ! *** 初期条件x0=dx*(nx/2)do i=0,nx

    x=i*dxu(i)=amp/sqrt(2.*pi*t_init)*exp(-(x-x0)*(x-x0)/4/kappa/t_init)if(u(i).lt.1.d-20) u(i)=0.d0

    end do

  • Nagoya Institute of Technology

    ! *** 境界条件if(ibs.eq.0) then

    ! * データファイルのオープンwrite(6,*) ' Dirichlet Condition'open(10, file='diffusion_d.dat')

    ! * ディリクレ条件u(0)=0.d0u(nx)=0.d0

    elsewrite(6,*) ' Neumann Condition'open(10, file='diffusion_n.dat')

    ! * ノイマン条件u(0)=u(1)u(nx)=u(nx-1)

    endif ! ! *** Write u(x=1/2,t) !

    t=0.d0write(6,1001)

    1001 format(/,' Evolution of u(1/2,t) ', /)write(6,1000) t,u(nx/2)

    do i=0,nxwrite(10,1000) i*dx, u(i)

    end dowrite(10,1000)

  • Nagoya Institute of Technology! *** 単純オイラー法による時間発展

    do n=1,tmaxdo i=0,nx

    uold(i)=u(i) ! uをu_oldにコピーend do

    ! 時間を1つ進めるdo i=1,nx-1

    diff=kappa*(uold(i+1)-2.d0*uold(i)+uold(i-1))*dx2iu(i)=uold(i)+diff*dt

    end do! *** 境界条件を課す

    if(ibs.eq.0) then u(0)=0.d0 ! ディリクレ条件u(nx)=0.d0

    elseu(0)=u(1) ! ノイマン条件u(nx)=u(nx-1)

    endif ! *** データを書き出す

    if(mod(n,gdraw).eq.0) thendo i=0,nx

    write(10,1000) i*dx, u(i)end do write(10,1000)

    t=n*dtwrite(6,1000) t,u(nx/2)

    endifend do

    1000 format(1x, 1pe10.3, 2x, 1pe12.6)stopend

  • Nagoya Institute of Technology

  • Nagoya Institute of Technology

    レイリーの問題

    x

    y

    U0

    u(y,t)

  • Nagoya Institute of Technology

  • Nagoya Institute of Technology

    拡散方程式の数値解の安定性条件

  • Nagoya Institute of Technology

    ∆x

    t=0

    t=∆t

    t=2∆t

    -∆x

  • Nagoya Institute of Technology

    ∆t

    ∆x

    ∆t/4

    ∆x/2

    x= 2κ t

    y

  • Nagoya Institute of Technology

    安定な数値解法

    Crank-Nicolson法 (陰的解法)

  • Nagoya Institute of Technology

    ディリクレ境界条件の場合

  • Nagoya Institute of Technology

    ! *** Time advancing by Crank-Nicolsondo n=1,tmax

    ! *** Enforce Boundary conditions at x=0if(ibs.eq.0) then

    alpha(0)=0.d0beta(0)=0.d0

    elsealpha(0)=2.d0/(2.d0+bi)beta(0)=(u(1)-(2.d0-bi)*u(0)+u(1))/(2.d0+bi) ! u(i) is at t=n.

    endif ! *** Forward elimination

    do i=1,nx-1sigmai=1.d0/( 2.d0+bi-alpha(i-1) )alpha(i)=sigmaidiff=u(i+1)-(2.d0-bi)*u(i)+u(i-1) ! u(i) is at t=n.beta(i)=sigmai*( diff+beta(i-1) )

    end do! *** Enforce Boundary conditions at x=1

    if(ibs.eq.0) then u(nx)=0.d0 ! u(nx) is at t=n+1.

    elsealpha(nx)=2.d0/(2.d0+bi)beta(nx)=(u(nx-1)-(2.d0-bi)*u(nx)+u(nx-1))/(2.d0+bi) ! u(i) is at t=n.u(nx)=alpha(nx)*u(nx-1)+beta(nx) ! u(nx) is at t=n+1, while u(nx-1) is at t=n.

    endif! ! *** Backward substitution

    do i=nx,1,-1u(i-1)=alpha(i-1)*u(i)+beta(i-1) ! u(i-1) and u(i) are at t=n+1

    end doend do

    Crank-Nicolsonプログラムのコア部分

  • Nagoya Institute of Technology

    比較

    単純オイラー法 クランク・ニコルソン法

  • Nagoya Institute of Technology

    2次元拡散方程式

    境界条件

    初期条件

    離散化

    1

    10

    y

    x

  • Nagoya Institute of Technology

    ! Diffusion equation in 2D by Simple Euler!

    implicit real*8 (a-h,o-z)integer pout,gdraw,nx,tmaxreal*8 kappa_x,kappa_yparameter(nx=50, ny=50, kappa_x=0.05, kappa_y=0.05, dt=0.001, ibs=1)parameter(tmax=200, gdraw=20, int=10)dimension u(0:nx, 0:ny),uold(0:nx, 0:ny)character:: filename*14

    ! *** Make parameters dx=1.d0/dfloat(nx); dy=1.d0/dfloat(ny)dx2i=1.d0/dx/dx; dy2i=1.d0/dy/dypi=4.d0*atan(1.d0); amp=1.d-1 t_init=0.01

    ! *** Initial conditionx0=dx*(nx/2); y0=dy*(ny/2)do j=0,ny

    do i=0,nxx=i*dx; y=j*dyu(i,j)=amp/(2.*pi*t_init)*exp(-((x-x0)**2+(y-y0)**2)/4/kappa_x/t_init)if(u(i,j).lt.1.d-20) u(i,j)=0.d0

    end doend do

    ! *** Boundary conditionif(ibs.eq.0) then

    u(0,:)=0.d0; u(:,0)=0.d0u(nx,:)=0.d0; u(:,ny)=0.d0

    elseu(0,:)=u(1,:); u(nx,:)=u(nx-1,:)u(:,0)=0.d0; u(:,ny)=0.d0

    endif

  • Nagoya Institute of Technology

    ! write initial dataqsum=0.d0do j=0,ny

    do i=0,nxqsum=qsum+u(i,j)

    end doend doqint=qsum*dx*dyqint_0=qintwrite(6,*) 'time u(nx/2,ny/2,t) Q(t)/Q(0)'write(6,1000) nt*dt, u(nx/2,ny/2), qint/qint_0

    no=0write(filename, '(A7, I3.3, A4)'), 'field_u', no , '.dat'open(20,file=filename,status='unknown')do j=0,ny

    do i=0,nxu_tmp=u(i,j)if(u_tmp.lt.1.e-20) u_tmp=1.d-20write(20,2000) i*dx, j*dy, u_tmp

    end do write(20,2000)

    end do

    1000 format(1x,1pe10.3,3x,1pe10.3,3x,1pe10.3)2000 format(2(1x, 1pe10.3), 2x, 1pe12.6)

  • Nagoya Institute of Technology

    ! *** Time advancing by simple Eulerdo nt=1,tmax

    ! *** Copy u to uolddo j=0,nydo i=0,nx

    uold(i,j)=u(i,j)end doend do

    ! *** Compute u(t+dt) by simple Eulerdo j=1,ny-1do i=1,nx-1

    diff_x=kappa_x*(uold(i+1,j)-2.d0*uold(i,j)+uold(i-1,j))*dx2idiff_y=kappa_y*(uold(i,j+1)-2.d0*uold(i,j)+uold(i,j-1))*dy2iu(i,j)=uold(i,j)+(diff_x+diff_y)*dt

    end doend do

    ! *** Enforce Boundary conditions! * For zero flux at x=0 and 1

    if(ibs==1) then u(0,:)=u(1,:)u(nx,:)=u(nx-1,:)

    endif

  • Nagoya Institute of Technology

    ! *** Output data for t>0 if(mod(nt,int)==0) then

    qsum=0.d0do j=0,nydo i=0,nx

    qsum=qsum+u(i,j)end doend doqint=qsum*dx*dywrite(6,1000) nt*dt, u(nx/2,ny/2), qint/qint_0

    endif

    if(mod(nt,gdraw).eq.0) thenno=nt/gdrawwrite(filename, '(A7, I3.3, A4)'), 'field_u', no , '.dat'open(20,file=filename,status='unknown')

    do j=0,nydo i=0,nx

    u_tmp=u(i,j)if(u_tmp.lt.1.e-20) u_tmp=1.d-20write(20,2000) i*dx, j*dy, u_tmp

    end do write(20,2000)

    end doclose(20)

    endif

    end do

    stopend

  • Nagoya Institute of Technology

    例題 2-1

    境界条件

    初期条件

    1

    10

    y

    x

  • Nagoya Institute of Technology

    移流方程式

    代入してみると

    流す作用

    すなわち特定の(x、t)の組についてξ =x-ct が一定なら f も一定

  • Nagoya Institute of Technology

    特性曲線

    すなわち特定の(x、t)の組についてξ =x-ct が一定なら f も一定特性曲線

  • Nagoya Institute of Technology

    初期条件

    離散化

    周期境界条件

    x0

    0.1

  • Nagoya Institute of Technology

    中心差分による結果

  • Nagoya Institute of Technology

    風上差分

    まとめて

    数値粘性項

    ∆x

    クーラン数

  • Nagoya Institute of Technology

    風上(1次精度)差分による結果

  • Nagoya Institute of Technology

    ラックスヴェンドルフの方法

    数値粘性項

  • Nagoya Institute of Technology

    中心差分 ラックスヴェンドルフ風上差分

    滑らかな初期条件

  • Nagoya Institute of Technology

    ! Convective equation in 1D by Lax-Wendroff

    ! *** Choice of the numerical scheme ! switch=0: Central difference ! switch=1: Lax-Wendroff

    ! *** Choice of the initial condition! init_type=0: Top hat! init_type=1: Gaussian

    implicit real*8 (a-h,o-z)integer kint,kdraw,nx,nt,tmax,switch

    ! parameter(nx=100, tmax=40, kint=2, kdraw=20)parameter(nx=100, tmax=100, kint=2, kdraw=20)parameter(c=1.d0, dt=0.002, width=0.05, init_type=0, switch=0)dimension u(0:nx),uold(0:nx)character*20 file(0:2)

    ! *** Make parameters dx=1.d0/dfloat(nx)pi=4.d0*atan(1.d0)sigma2=width*widthamp=1.d-1/sqrt(2.*pi*sigma2)

    ! r=abs(c)*dt/dxr=c*dt/dxfile(0)=' Central_difference'file(1)=' Lax-Wendroff '

    if(switch==0) open(10,file='Central_difference.dat')if(switch==1) open(10,file='Lax-Wendroff.dat')

    write(6,1000) file(switch),r 1000 format(1x,A20,1x,'Courant Number=',1pe10.3,/)

    write(6,*) ' Conservation of Q'

    ラックスヴェンドルフのプログラム例

  • Nagoya Institute of Technology

    ! *** Initial condition and ! computation of total Q(t)=¥int u(x,t)dx ***

    x0=dx*(nx/2)do i=0,nx

    x=i*dxu(i)=0.d0if(init_type==0 .and. abs(x-x0)

  • Nagoya Institute of Technology

    ! *** Output data for t>0

    call output(u,dx,dt,nx,nt,kint,kdraw)end dostopend

    ! ******************************************************************** subroutine output(u,dx,dt,nx,nt,kint,kdraw)implicit real*8 (a-h,o-z)real*8 u(0:nx)save Q_init

    ! **** write Q if(mod(nt,kint).eq.0) then

    Q=0.d0do i=0,nx

    Q=Q+u(i)end doQ=Q*dxif(nt==0) Q_init=Qwrite(6,1000) nt*dt,Q/Q_init

    endif

    ! *** write u(x,t)if(mod(nt,kdraw).eq.0) then

    do i=0,nxwrite(10,2000) i*dx,u(i)

    end dowrite(10,2000)

    endif

    1000 format(1x,2(1pe10.3,1x))2000 format(1x,2(1pe12.5,1x))

    returnend

  • Nagoya Institute of Technology

    例題 2-2

    境界条件

    初期条件

    1

    10

    y

    x

    cx はO(1)のパラメータ

  • Nagoya Institute of Technology

    バーガース 方程式

    数学的解析のしやすさからBurgers により乱流の最も簡単なモデルとして導入された

    非線形性散逸性圧縮性

    ショック解

  • Nagoya Institute of Technology

    いくつかの現象のモデル

    ・界面の成長 (KPZ eq.) ・ 宇宙の大規模泡構造(Zeldovich)

    http://www.nhk.or.jp/school/junior/yougo26.html#010

    de Lapparent et al. (1986)

    2d Burgers 3d Burgers

    Takahashi and Gotoh (2000)

    div u

    スライド番号 1スライド番号 2スライド番号 3スライド番号 4スライド番号 5スライド番号 6スライド番号 7スライド番号 8スライド番号 9スライド番号 10スライド番号 11スライド番号 12スライド番号 13スライド番号 14スライド番号 15スライド番号 16スライド番号 17スライド番号 18スライド番号 19スライド番号 20スライド番号 21スライド番号 22スライド番号 23スライド番号 24スライド番号 25スライド番号 26スライド番号 27スライド番号 28スライド番号 29スライド番号 30スライド番号 31スライド番号 32スライド番号 33スライド番号 34スライド番号 35スライド番号 36