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

📄 blend.f90

📁 FORTRAN程序 共有8个插值程序 希望能帮到大家
💻 F90
📖 第 1 页 / 共 5 页
字号:
!    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 October 2001
!
!  Author:
!
!    John Burkardt
!
!  Parameters:
!
!    Input, real R, S, T, the coordinates where an interpolated value
!    is desired.
!
!    Input, real X000, X001, X010, X011, X100, X101, X110, X111, the
!    data values at the corners.
!
!    Input, real XR00, XR01, XR10, XR11, X0S0, X0S1, X1S0, X1S1, X00T,
!    X01T, X10T, X11T, the data values at points along the edges.
!
!    Output, real X, the interpolated data value at (R,S,T).
!
  implicit none
!
  real r
  real s
  real t
  real x
  real x000
  real x001
  real x010
  real x011
  real x100
  real x101
  real x110
  real x111
  real xr00
  real xr01
  real xr0t
  real xr10
  real xr11
  real xr1t
  real xrs0
  real xrs1
  real x0s0
  real x0s1
  real x0st
  real x1s0
  real x1s1
  real x1st
  real x00t
  real x01t
  real x10t
  real x11t
!
!  Interpolate the points in the centers of the faces.
!
  call blend_112 ( s, t, x000, x001, x010, x011, x0s0, x0s1, x00t, x01t, x0st )
  call blend_112 ( s, t, x100, x101, x110, x111, x1s0, x1s1, x10t, x11t, x1st )
  call blend_112 ( r, t, x000, x001, x100, x101, xr00, xr01, x00t, x10t, xr0t )
  call blend_112 ( r, t, x010, x011, x110, x111, xr10, xr11, x01t, x11t, xr1t )
  call blend_112 ( r, s, x000, x010, x100, x110, xr00, xr10, x0s0, x1s0, xrs0 )
  call blend_112 ( r, s, x001, x011, x101, x111, xr01, xr11, x0s1, x1s1, xrs1 )
!
!  Interpolate the I-th coordinate component of the interior point.
!
  call blend_123 ( r, s, t, x000, x001, x010, x011, x100, x101, x110, x111, &
    xr00, xr01, xr10, xr11, x0s0, x0s1, x1s0, x1s1, x00t, x01t, x10t, x11t, &
    x0st, x1st, xr0t, xr1t, xrs0, xrs1, x )

  return
end
subroutine blend_123 ( r, s, t, x000, x001, x010, x011, x100, x101, x110, &
  x111, xr00, xr01, xr10, xr11, x0s0, x0s1, x1s0, x1s1, x00t, x01t, x10t, &
  x11t, x0st, x1st, xr0t, xr1t, xrs0, xrs1, x )
!
!*******************************************************************************
!
!! BLEND_123 extends scalar face data into a cube.
!
!
!  Diagram:
!
!    010-----r10-----110        011-----r11-----111
!      |       .       |          |       .       |  
!      |       .       |          |       .       |
!    0s0.....rs0.....1s0        0s1.....rs1.....1s1     S
!      |       .       |          |       .       |     |
!      |       .       |          |       .       |     |
!    000-----r00-----100        001-----r01-----101     +----R
!           BOTTOM                      TOP
!
!    011-----0s1-----001        111-----1s1-----101
!      |       .       |          |       .       |  
!      |       .       |          |       .       |
!    01t.....0st.....00t        11t.....1st.....10t          T
!      |       .       |          |       .       |          |
!      |       .       |          |       .       |          |
!    010-----0s0-----000        110-----1s0-----100     S----+
!           LEFT                       RIGHT
!
!    001-----r01-----101        011-----r11-----111
!      |       .       |          |       .       |  
!      |       .       |          |       .       |
!    00t.....r0t.....100        01t.....r1t.....11t     T
!      |       .       |          |       .       |     |
!      |       .       |          |       .       |     |
!    000-----r00-----100        010-----r10-----110     +----R
!           FRONT                       BACK
!
!  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, T, the coordinates where an interpolated value 
!    is desired.  
!
!    Input, real X000, X001, X010, X011, X100, X101, X110, X111, the 
!    data values at the corners.
!
!    Input, real XR00, XR01, XR10, XR11, X0S0, X0S1, X1S0, X1S1, X00T, 
!    X01T, X10T, X11T, the data values at points along the edges.
!
!    Input, real X0ST, X1ST, XR0T, XR1T, XRS0, XRS1, the data values 
!    at points on the faces.
!
!    Output, real X, the interpolated data value at (R,S,T).
!
  implicit none
!
  real r
  real s
  real t
  real x
  real x000
  real x001
  real x010
  real x011
  real x100
  real x101
  real x110
  real x111
  real xr00
  real xr01
  real xr10
  real xr11
  real x0s0
  real x0s1
  real x1s0
  real x1s1
  real x00t
  real x01t
  real x10t
  real x11t
  real x0st
  real x1st
  real xr0t
  real xr1t
  real xrs0
  real xrs1
!
!  Interpolate the interior point.
!
  x =        ( 1.0E+00 - r ) * ( 1.0E+00 - s ) * ( 1.0E+00 - t ) * x000 &
           - ( 1.0E+00 - r ) * ( 1.0E+00 - s )                   * x00t &
           + ( 1.0E+00 - r ) * ( 1.0E+00 - s ) *             t   * x001 &
           - ( 1.0E+00 - r )                   * ( 1.0E+00 - t ) * x0s0 &
           + ( 1.0E+00 - r )                                     * x0st &
           - ( 1.0E+00 - r )                   *             t   * x0s1 &
           + ( 1.0E+00 - r ) *             s   * ( 1.0E+00 - t ) * x010 &
           - ( 1.0E+00 - r ) *             s                     * x01t &
           + ( 1.0E+00 - r ) *             s   *             t   * x011 &
           -                   ( 1.0E+00 - s ) * ( 1.0E+00 - t ) * xr00 &
           +                   ( 1.0E+00 - s )                   * xr0t &
           -                   ( 1.0E+00 - s ) *             t   * xr01 &
           +                                     ( 1.0E+00 - t ) * xrs0 &
           +                                                 t   * xrs1 &
           -                               s   * ( 1.0E+00 - t ) * xr10 &
           +                               s                     * xr1t &
           -                               s   *             t   * xr11 &
           +             r   * ( 1.0E+00 - s ) * ( 1.0E+00 - t ) * x100 &
           -             r   * ( 1.0E+00 - s )                   * x10t &
           +             r   * ( 1.0E+00 - s ) *             t   * x101 &
           -             r                     * ( 1.0E+00 - t ) * x1s0 &
           +             r                                       * x1st &
           -             r                     *             t   * x1s1 &
           +             r   *             s   * ( 1.0E+00 - t ) * x110 &
           -             r   *             s                     * x11t &
           +             r   *             s   *             t   * x111

  return
end
subroutine blend_i_0d1 ( x, m )
!
!*******************************************************************************
!
!! BLEND_I_0D1 extends indexed scalar data at endpoints along a line.
!
!
!  Diagram:
!
!    ( X1, ..., ..., ..., ..., ..., XM )
!
!  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/output, real X(M).  
!
!    On input, X(1) and X(M) contain scalar values which are to be 
!    interpolated through the entries X(2) through X(M).  It is assumed
!    that the dependence of the data is linear in the vector index I.  
!    
!    On output, X(2) through X(M-1) have been assigned interpolated 
!    values.
!
!    Input, integer M, the number of entries in X.
!
  implicit none
!
  integer m
!
  integer i
  real r
  real x(m)
!
  do i = 2, m - 1

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

    call blend_101 ( r, x(1), x(m), x(i) )

  end do

  return
end
subroutine blend_ij_0d1 ( x, m1, m2 )
!
!*******************************************************************************
!
!! BLEND_IJ_0D1 extends indexed scalar data at corners into a table.
!
!
!  Diagram:
!
!    ( X11,  ..., ..., ..., ..., ..., X1M2  )
!    ( ...,  ..., ..., ..., ..., ..., ...   )
!    ( ...,  ..., ..., ..., ..., ..., ...   )
!    ( ...,  ..., ..., ..., ..., ..., ...   )
!    ( XM11, ..., ..., ..., ..., ..., XM1M2 )
!
!  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).  
!
!    On input, X(1,1), X(1,M2), X(M1,1) and X(M1,M2) contain scalar 
!    values which are to be interpolated throughout the table, using 
!    the table indices I and J as independent variables. 
!    
!    On output, all entries in X have been assigned a value.
!
!    Input, integer M1, M2, the number of rows and columns in X.
!
  implicit none
!
  integer m1
  integer m2
!
  integer i
  integer j
  real r
  real s
  real x(m1,m2)
!
!  Interpolate values along the edges.
!
  do i = 2, m1 - 1

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

    call blend_101 ( r, x(1,1), x(m1,1), x(i,1) )

    call blend_101 ( r, x(1,m2), x(m1,m2), x(i,m2) )

  end do

  do j = 2, m2 - 1

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

    call blend_101 ( s, x(1,1), x(1,m2), x(1,j) )

    call blend_101 ( s, x(m1,1), x(m1,m2), x(m1,j) )

  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 )

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

    end do

  end do

  return
end
subroutine blend_ij_1d1 ( x, m1, m2 )
!
!*******************************************************************************
!
!! BLEND_IJ_1D1 extends indexed scalar data along edges into a table.
!
!
!  Diagram:
!
!    ( X11,  X12,  X13,  X14,  X15,  X16,  X1M2  )
!    ( X21,  ...,  ...,  ...,  ...,  ...,  X2M2  )
!    ( X31,  ...,  ...,  ...,  ...,  ...,  X3M2  )
!    ( X41,  ...,  ...,  ...,  ...,  ...,  X4M2  )
!    ( XM11, XM12, XM13, XM14, XM15, XM16, XM1M2 )
!
!  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,

⌨️ 快捷键说明

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