⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 blend.f90

📁 FORTRAN程序 共有8个插值程序 希望能帮到大家
💻 F90
📖 第 1 页 / 共 5 页
字号:
  do i = 2, m1 - 1
    r = real ( i - 1 ) / real ( m1 - 1 )
    do k = 2, m3 - 1
      t = real ( k - 1 ) / real ( m3 - 1 )

      call blend_112 ( r, t, x(1,1,1), x(1,1,m3), x(m1,1,1), x(m1,1,m3), &
        x(i,1,1), x(i,1,m3), x(1,1,k), x(m1,1,k), x(i,1,k) )

      call blend_112 ( r, t, x(1,m2,1), x(1,m2,m3), x(m1,m2,1), x(m1,m2,m3), &
        x(i,m2,1), x(i,m2,m3), x(1,m2,k), x(m1,m2,k), x(i,m2,k) )

    end do
  end do 

  do i = 2, m1 - 1
    r = real ( i - 1 ) / real ( m1 - 1 )
    do j = 2, m2 - 1
      s = real ( j - 1 ) / real ( m2 - 1 )

      call blend_112 ( r, s, x(1,1,1), x(1,m2,1), x(m1,1,1), x(m1,m2,1), &
        x(i,1,1), x(i,m2,1), x(1,j,1), x(m1,j,1), x(i,j,1) )

      call blend_112 ( r, s, x(1,1,m3), x(1,m2,m3), x(m1,1,m3), x(m1,m2,m3), &
        x(i,1,m3), x(i,m2,m3), x(1,j,m3), x(m1,j,m3), x(i,j,m3) )

    end do
  end do
!
!  Interpolate values in the interior.
!
  do i = 2, m1 - 1

    r = real ( i - 1 ) / real ( m1 - 1 )

    do j = 2, m2 - 1

      s = real ( j - 1 ) / real ( m2 - 1 )

      do k = 2, m3 - 1

        t = real ( k - 1 ) / real ( m3 - 1 )

        call blend_123 ( r, s, t, &
          x( 1,1,1), x( 1, 1,m3), x( 1,m2,1), x( 1,m2,m3), &
          x(m1,1,1), x(m1, 1,m3), x(m1,m2,1), x(m1,m2,m3), &
          x( i,1,1), x( i, 1,m3), x( i,m2,1), x( i,m2,m3), &
          x( 1,j,1), x( 1, j,m3), x(m1, j,1), x(m1, j,m3), &
          x( 1,1,k), x( 1,m2, k), x(m1, 1,k), x(m1,m2, k), &
          x( 1,j,k), x(m1, j, k), x( i, 1,k), x( i,m2, k), &
          x( i,j,1), x( i, j,m3), x( i, j,k) )

      end do

    end do

  end do

  return
end
subroutine blend_ijk_2d1 ( x, m1, m2, m3 )
!
!*******************************************************************************
!
!! BLEND_IJK_2D1 extends indexed scalar face data into a cubic table.
!
!
!  Diagram:
!
!    ( X111    X121    X131    X141    X151    X1M21   )
!    ( X211    X221    X231    X241    X251    X2M21   )
!    ( X311    X321    X331    X341    X351    X3M21   )   Layer 1
!    ( X411    X421    X431    X441    X451    X4M21   )
!    ( XM111   XM121   XM131   XM141   XM151   XM1M21  )
!
!    ( X11K    X12K    X13K    X14K    X15K    X1M2K   )
!    ( X21K    ...     ....    ....    ....    X2M2K   )
!    ( X31K    ...     ....    ....    ....    X3M2K   )   Layer K
!    ( X41K    ...     ....    ....    ....    X4M2K   )   1 < K < M3
!    ( XM11K   XM12K   XM13K   XM14K   XM15K   XM1M2K  )
!
!    ( X11M3   X12M3   X13M3   X14M3   X15M3   X1M2M3  )
!    ( X21M3   X22M3   X23M3   X24M3   X25M3   X2M2M3  )
!    ( X31M3   X32M3   X33M3   X34M3   X35M3   X3M2M3  )   Layer M3
!    ( X41M3   X42M3   X43M3   X44M3   X45M3   X4M2M3  )
!    ( XM11M3  XM12M3  XM13M3  XM14M3  XM15M3  XM1M2M3 )
!
!  Reference:
!
!    William Gordon,
!    Blending-Function Methods of Bivariate and Multivariate Interpolation
!      and Approximation,
!    SIAM Journal on Numerical Analysis,
!    Volume 8, Number 1, March 1971, pages 158-177.
!
!    William Gordon and Charles Hall,
!    Transfinite Element Methods: Blending-Function Interpolation over
!      Arbitrary Curved Element Domains,
!    Numerische Mathematik,
!    Volume 21, Number 1, 1973, pages 109-129.
!
!    William Gordon and Charles Hall,
!    Construction of Curvilinear Coordinate Systems and Application to
!      Mesh Generation,
!    International Journal of Numerical Methods in Engineering,
!    Volume 7, 1973, pages 461-477.
!
!    Joe Thompson, Bharat Soni, Nigel Weatherill,
!    Handbook of Grid Generation,
!    CRC Press, 1999.
!
!  Modified:
!
!    16 December 1998
!
!  Author:
!
!    John Burkardt
!
!  Parameters:
!
!    Input/output, real X(M1,M2,M3).  
!
!    On input, there is already scalar data in the entries X(I,J,K) 
!    corresponding to "faces" of the table, that is, entries for which
!    at least one of the three indices I, J and K is equal to their
!    minimum or maximum possible values.
!    
!    On output, all entries in X have been assigned a value, using the
!    table indices as independent variables.
!
!    Input, integer M1, M2, M3, the number of rows, columns, and 
!    layers in X.
!
  implicit none
!
  integer m1
  integer m2
  integer m3
!
  integer i
  integer j
  integer k
  real r
  real s
  real t
  real x(m1,m2,m3)
!
!  Interpolate values in the interior.
!
  do i = 2, m1 - 1

    r = real ( i - 1 ) / real ( m1 - 1 )

    do j = 2, m2 - 1

      s = real ( j - 1 ) / real ( m2 - 1 )

      do k = 2, m3 - 1

        t = real ( k - 1 ) / real ( m3 - 1 )

        call blend_123 ( r, s, t, &
          x( 1,1,1), x( 1, 1,m3), x( 1,m2,1), x( 1,m2,m3), &
          x(m1,1,1), x(m1, 1,m3), x(m1,m2,1), x(m1,m2,m3), &
          x( i,1,1), x( i, 1,m3), x( i,m2,1), x( i,m2,m3), &
          x( 1,j,1), x( 1, j,m3), x(m1, j,1), x(m1, j,m3), &
          x( 1,1,k), x( 1,m2, k), x(m1, 1,k), x(m1,m2, k), &
          x( 1,j,k), x(m1, j, k), x( i, 1,k), x( i,m2, k), &
          x( i,j,1), x( i, j,m3), x( i, j,k) )

      end do

    end do

  end do

  return
end
subroutine blend_r_0dn ( r, x, n, bound_r )
!
!*******************************************************************************
!
!! BLEND_R_0DN extends vector data at endpoints into a line.
!
!
!  Diagram:
!
!    0-----r-----1
!
!  Note:
!
!    This is simply linear interpolation.  BLEND_R_0DN is provided
!    mainly as a "base routine" which can be compared to its 
!    generalizations, such as BLEND_RS_0DN.
!
!  Reference:
!
!    William Gordon,
!    Blending-Function Methods of Bivariate and Multivariate Interpolation
!      and Approximation,
!    SIAM Journal on Numerical Analysis,
!    Volume 8, Number 1, March 1971, pages 158-177.
!
!    William Gordon and Charles Hall,
!    Transfinite Element Methods: Blending-Function Interpolation over
!      Arbitrary Curved Element Domains,
!    Numerische Mathematik,
!    Volume 21, Number 1, 1973, pages 109-129.
!
!    William Gordon and Charles Hall,
!    Construction of Curvilinear Coordinate Systems and Application to
!      Mesh Generation,
!    International Journal of Numerical Methods in Engineering,
!    Volume 7, 1973, pages 461-477.
!
!    Joe Thompson, Bharat Soni, Nigel Weatherill,
!    Handbook of Grid Generation,
!    CRC Press, 1999.
!
!  Modified:
!
!    15 December 1998
!
!  Author:
!
!    John Burkardt
!
!  Parameters:
!
!    Input, real R, the (R) coordinate of the point to be evaluated.
!
!    Output, real X(N), the interpolated value at the point (R).
!
!    Input, integer N, the dimension of the vector space.
!
!    External, BOUND_R, is a subroutine which is given (R) coordinates
!    and an component value I, and returns XI, the value of the I-th 
!    component of the N-vector at that point.  BOUND_R will only be 
!    called for "corners", that is, for values (R) where R is either 
!    0.0E+00 or 1.0.  BOUND_R has the form:
!
!    subroutine bound_r ( r, i, xi )
!
  implicit none
!
  integer n
!
  integer i
  real r
  real x(n)
  real x0
  real x1
!
  external bound_r
!
  do i = 1, n
!
!  Get the I-th coordinate component at the two corners.
!
    call bound_r ( 0.0E+00, i, x0 )
    call bound_r ( 1.0E+00, i, x1 )
!
!  Interpolate the I-th coordinate component of the interior point.
!
    call blend_101 ( r, x0, x1, x(i) )

  end do

  return
end
subroutine blend_rs_0dn ( r, s, x, n, bound_rs )
!
!*******************************************************************************
!
!! BLEND_RS_0DN extends vector data at corners into a square.
!
!
!  Diagram:
!
!    01-----r1-----11
!     |      .      |
!     |      .      |
!    0s.....rs.....1s
!     |      .      |
!     |      .      |
!    00-----r0-----10
!
!  Note:
!
!    BLEND_RS_0DN should be equivalent to the use of a bilinear finite 
!    element method.
!
!  Reference:
!
!    William Gordon,
!    Blending-Function Methods of Bivariate and Multivariate Interpolation
!      and Approximation,
!    SIAM Journal on Numerical Analysis,
!    Volume 8, Number 1, March 1971, pages 158-177.
!
!    William Gordon and Charles Hall,
!    Transfinite Element Methods: Blending-Function Interpolation over
!      Arbitrary Curved Element Domains,
!    Numerische Mathematik,
!    Volume 21, Number 1, 1973, pages 109-129.
!
!    William Gordon and Charles Hall,
!    Construction of Curvilinear Coordinate Systems and Application to
!      Mesh Generation,
!    International Journal of Numerical Methods in Engineering,
!    Volume 7, 1973, pages 461-477.
!
!    Joe Thompson, Bharat Soni, Nigel Weatherill,
!    Handbook of Grid Generation,
!    CRC Press, 1999.
!
!  Modified:
!
!    14 December 1998
!
!  Author:
!
!    John Burkardt
!
!  Parameters:
!
!    Input, real R, S, the (R,S) coordinates of the point to be 
!    evaluated.
!
!    Output, real X(N), the interpolated value at the point (R,S).
!
!    Input, integer N, the dimension of the vector space.
!
!    External, BOUND_RS, is a subroutine which is given (R,S) 
!    coordinates and an component value I, and returns XI, the value 
!    of the I-th component of the N-vector at that point.  BOUND_RS 
!    will only be called for "corners", that is, for values (R,S) where 
!    R and S are either 0.0E+00 or 1.0.  BOUND_RS has the form:
!
!    subroutine bound_rs ( r, s, i, xi )
!
  implicit none
!
  integer n
!
  integer i
  real r
  real s
  real x(n)
  real x00
  real x01
  real x10
  real x11
  real xr0
  real xr1
  real x0s
  real x1s
!
  external bound_rs
!
  do i = 1, n
!
!  Get the I-th coordinate component at the four corners.
!
    call bound_rs ( 0.0E+00, 0.0E+00, i, x00 )
    call bound_rs ( 0.0E+00, 1.0E+00, i, x01 )
    call bound_rs ( 1.0E+00, 0.0E+00, i, x10 )
    call bound_rs ( 1.0E+00, 1.0E+00, i, x11 )
!
!  Interpolate the I-th coordinate component at the sides.
!
    call blend_101 ( r, x00, x10, xr0 )
    call blend_101 ( r, x01, x11, xr1 )
    call blend_101 ( s, x00, x01, x0s )
    call blend_101 ( s, x10, x11, x1s )
!
!  Interpolate the I-th coordinate component of the interior point.
!
    call blend_112 ( r, s, x00, x01, x10, x11, xr0, xr1, x0s, x1s, x(i) )

  end do

  return
end
subroutine blend_rs_1dn ( r, s, x, n, bound_rs )
!
!*******************************************************************************
!
!! BLEND_RS_1DN extends vector data along sides into a square.
!
!
!  Diagram:
!
!    01-----r1-----11
!     |      .      |
!     |      .      |
!    0s.....rs.....1s
!     |      .      |
!     |      .      |
!    00-----r0-----10
!
!  Note:
!
!    BLEND_RS_1DN is NOT equivalent to a bilinear finite element method,
!    since the data is sampled everywhere along the boundary lines,
!    rather than at a finite number of nodes.
!
!  Reference:
!
!    William Gordon,
!    Blending-Function Methods of Bivariate and Multivariate Interpolation
!      and Approximation,
!    SIAM Journal on Numerical Analysis,
!    Volume 8, Number 1, March 1971, pages 158-177.
!
!    William Gordon and Charles Hall,
!    Transfinite Element Methods: Blending-Function Interpolation over
!      Arbitrary Curved Element Domains,
!    Numerische Mathematik,
!    Volume 21, Number 1, 1973, pages 109-129.
!
!    William Gordon and Charles Hall,
!    Construction of Curvilinear Coordinate Systems and Application to
!      Mesh Generation,
!    International Journal of Numerical Methods in Engineering,
!    Volume 7, 1973, pages 461-477.
!
!    Joe Thompson, Bharat Soni, Nigel Weatherill,
!    Handbook of Grid Generation,
!    CRC Press, 1999.
!
!  Modified:
!
!    15 December 1998
!
!  Author:
!
!    John Burkardt
!
!  Parameters:
!
!    Input, real R, S, the (R,S) coordinates of the point to be 
!    evaluated.
!
!    Output, real X(N), the interpolated value at the point (R,S).
!
!    Input, integer N, the dimension of the vector space.
!
!    External, BOUND_RS, is a subroutine which is given (R,S) 
!    coordinates and an component value I, and returns XI, the value 
!    of the I-th component of the N-vector at that point.  BOUND_RS 

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -