subroutine i4_fake_use ( n ) !*****************************************************************************80 ! !! i4_fake_use() pretends to use a variable. ! ! Discussion: ! ! Some compilers will issue a warning if a variable is unused. ! Sometimes there's a good reason to include a variable in a program, ! but not to use it. Calling this function with that variable as ! the argument will shut the compiler up. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 21 April 2020 ! ! Author: ! ! John Burkardt ! ! Input: ! ! integer N, the variable to be "used". ! implicit none integer n if ( n /= n ) then write ( *, '(a)' ) ' i4_fake_use(): variable is NAN.' end if return end function index0 ( i_min, i, i_max ) !*****************************************************************************80 ! !! index0() indexes a 1D vector using a zero base. ! ! Discussion: ! ! Index Element ! --------- -------- ! 0 I_MIN ! INDEX0 I ! (INDEX_MAX) I_MAX ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 15 November 2012 ! ! Author: ! ! John Burkardt ! ! Input: ! ! integer I_MIN, I, I_MAX, for the first index, ! the minimum, the index, and the maximum. ! ! Output: ! ! integer INDEX0, the index of element I. ! implicit none integer i integer i_max integer i_min integer, parameter :: index_min = 0 integer index0 call i4_fake_use ( i_max ) index0 = index_min + ( i - i_min ) return end function index01 ( i_min, i, i_max, j_min, j, j_max ) !*****************************************************************************80 ! !! index01() indexes a 2D array by columns, with a zero base. ! ! Discussion: ! ! Entries of the array are indexed starting at entry (I_MIN,J_MIN), ! and increasing the row index first. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 03 April 2010 ! ! Author: ! ! John Burkardt ! ! Input: ! ! integer I_MIN, I, I_MAX, for row indices, ! the minimum, the index, and the maximum. ! ! integer J_MIN, J, J_MAX, for column indices, ! the minimum, the index, and the maximum. ! ! Output: ! ! Output, integer INDEX01, the index of element (I,J). ! implicit none integer i integer i_max integer i_min integer, parameter :: index_min = 0 integer index01 integer j integer j_max integer j_min call i4_fake_use ( j_max ) index01 = & index_min & + ( i - i_min ) & + ( i_max + 1 - i_min ) * ( j - j_min ) return end function index012 ( i_min, i, i_max, j_min, j, j_max, k_min, k, k_max ) !*****************************************************************************80 ! !! index012() indexes a 3D array by columns with zero base. ! ! Discussion: ! ! Entries of the array are indexed starting at entry (I_MIN,J_MIN,K_MIN), ! and increasing the row index first, then the column index. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 03 April 2010 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer I_MIN, I, I_MAX, for row indices, ! the minimum, the index, and the maximum. ! ! Input, integer J_MIN, J, J_MAX, for column indices, ! the minimum, the index, and the maximum. ! ! Input, integer K_MIN, K, K_MAX, for plane indices, ! the minimum, the index, and the maximum. ! ! Output, integer INDEX012, the index of element (I,J,K). ! implicit none integer i integer i_max integer i_min integer, parameter :: index_min = 0 integer index012 integer j integer j_max integer j_min integer k integer k_max integer k_min call i4_fake_use ( k_max ) index012 = & index_min & + ( i - i_min ) & + ( i_max + 1 - i_min ) * ( j - j_min ) * & + ( i_max + 1 - i_min ) * ( j_max + 1 - j_min ) * ( k - k_min ) return end function index0123 ( i1_min, i1, i1_max, i2_min, i2, i2_max, i3_min, i3, & i3_max, i4_min, i4, i4_max ) !*****************************************************************************80 ! !! index0123() indexes a 4D array by columns, with a zero base. ! ! Discussion: ! ! Entries are indexed starting at (I1_MIN,I2_MIN,I3_MIN,I4_MIN), ! and increasing the initial index first, then the second, third and so on. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 16 November 2012 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer I1_MIN, I1, I1_MAX, for index 1, ! the minimum, the index, and the maximum. ! ! Input, integer I2_MIN, I2, I2_MAX, for index 2, ! the minimum, the index, and the maximum. ! ! Input, integer I3_MIN, I3, I3_MAX, for index 3, ! the minimum, the index, and the maximum. ! ! Input, integer I4_MIN, I4, I4_MAX, for index 4, ! the minimum, the index, and the maximum. ! ! Output, integer INDEX0123, the index of (I1,I2,I3,I4). ! implicit none integer i1 integer i1_max integer i1_min integer i2 integer i2_max integer i2_min integer i3 integer i3_max integer i3_min integer i4 integer i4_max integer i4_min integer, parameter :: index_min = 0 integer index0123 call i4_fake_use ( i4_max ) index0123 = & index_min & + ( i1 - i1_min ) & + ( i1_max + 1 - i1_min ) * ( i2 - i2_min ) & + ( i1_max + 1 - i1_min ) * ( i2_max + 1 - i2_min ) & * ( i3 - i3_min ) & + ( i1_max + 1 - i1_min ) * ( i2_max + 1 - i2_min ) & * ( i3_max + 1 - i3_min ) * ( i4 - i4_min ) return end function index0n ( n, i_min, i, i_max ) !*****************************************************************************80 ! !! index0n() indexes an N-dimensional array by columns, with zero base. ! ! Discussion: ! ! Entries of the array are indexed starting at entry ! ( I_MIN(1), I_MIN(2),...,I_MIN(N) ), ! and increasing the first index up to I_MAX(1), ! then the second and so on. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 03 April 2010 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer N, the number of indices. ! ! Input, integer I_MIN(N), the minimum indices. ! ! Input, integer I(N), the indices. ! ! Input, integer I_MAX(N), for maximum indices. ! ! Output, integer INDEX0N, the index of element I. ! implicit none integer n integer i(n) integer i_max(n) integer i_min(n) integer, parameter :: index_min = 0 integer index0n integer j integer value value = ( i(n) - i_min(n) ) do j = n - 1, 1, - 1 value = value * ( i_max(j) + 1 - i_min(j) ) + ( i(j) - i_min(j) ) end do value = value + index_min index0n = value return end function index1 ( i_min, i, i_max ) !*****************************************************************************80 ! !! index1() indexes a 1D vector using a unit base. ! ! Discussion: ! ! Index Element ! --------- -------- ! 1 I_MIN ! INDEX1 I ! (INDEX_MAX) I_MAX ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 15 November 2012 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer I_MIN, I, I_MAX, for the first index, ! the minimum, the index, and the maximum. ! ! Output, integer INDEX1, the index of element I. ! implicit none integer i integer i_max integer i_min integer, parameter :: index_min = 1 integer index1 call i4_fake_use ( i_max ) index1 = index_min + ( i - i_min ) return end function index10 ( i_min, i, i_max, j_min, j, j_max ) !*****************************************************************************80 ! !! index10() indexes a 2D array by rows, with a zero base. ! ! Discussion: ! ! Entries of the array are indexed starting at entry (I_MIN,J_MIN), ! and increasing the column index first. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 15 November 2012 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer I_MIN, I, I_MAX, for row indices, ! the minimum, the index, and the maximum. ! ! Input, integer J_MIN, J, J_MAX, for column indices, ! the minimum, the index, and the maximum. ! ! Output, integer INDEX10, the index of element (I,J). ! implicit none integer i integer i_max integer i_min integer, parameter :: index_min = 0 integer index10 integer j integer j_max integer j_min call i4_fake_use ( i_max ) index10 = index_min & + ( j - j_min ) & + ( i - i_min ) * ( j_max + 1 - j_min ) return end function index12 ( i_min, i, i_max, j_min, j, j_max ) !*****************************************************************************80 ! !! index12() indexes a 2D array by columns, with a unit base. ! ! Discussion: ! ! Entries of the array are indexed starting at entry (I_MIN,J_MIN), ! and increasing the row index first. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 15 November 2012 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer I_MIN, I, I_MAX, for row indices, ! the minimum, the index, and the maximum. ! ! Input, integer J_MIN, J, J_MAX, for column indices, ! the minimum, the index, and the maximum. ! ! Output, integer INDEX12, the index of element (I,J). ! implicit none integer i integer i_max integer i_min integer, parameter :: index_min = 1 integer index12 integer j integer j_max integer j_min call i4_fake_use ( j_max ) index12 = & index_min & + ( i - i_min ) & + ( i_max + 1 - i_min ) * ( j - j_min ) return end function index123 ( i_min, i, i_max, j_min, j, j_max, k_min, k, k_max ) !*****************************************************************************80 ! !! index123() indexes a 3D array by columns with unit base. ! ! Discussion: ! ! Entries of the array are indexed starting at entry (I_MIN,J_MIN,K_MIN), ! and increasing the row index first, then the column index. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 15 November 2012 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer I_MIN, I, I_MAX, for row indices, ! the minimum, the index, and the maximum. ! ! Input, integer J_MIN, J, J_MAX, for column indices, ! the minimum, the index, and the maximum. ! ! Input, integer K_MIN, K, K_MAX, for plane indices, ! the minimum, the index, and the maximum. ! ! Output, integer INDEX123, the index of element (I,J,K). ! implicit none integer i integer i_max integer i_min integer, parameter :: index_min = 1 integer index123 integer j integer j_max integer j_min integer k integer k_max integer k_min call i4_fake_use ( k_max ) index123 = & index_min & + ( i - i_min ) & + ( i_max + 1 - i_min ) * ( j - j_min ) * & + ( i_max + 1 - i_min ) * ( j_max + 1 - j_min ) * ( k - k_min ) return end function index1234 ( i1_min, i1, i1_max, i2_min, i2, i2_max, i3_min, i3, & i3_max, i4_min, i4, i4_max ) !*****************************************************************************80 ! !! index1234() indexes a 4D array by columns, with a unit base. ! ! Discussion: ! ! Entries are indexed starting at (I1_MIN,I2_MIN,I3_MIN,I4_MIN), ! and increasing the initial index first, then the second, third and so on. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 16 November 2012 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer I1_MIN, I1, I1_MAX, for index 1, ! the minimum, the index, and the maximum. ! ! Input, integer I2_MIN, I2, I2_MAX, for index 2, ! the minimum, the index, and the maximum. ! ! Input, integer I3_MIN, I3, I3_MAX, for index 3, ! the minimum, the index, and the maximum. ! ! Input, integer I4_MIN, I4, I4_MAX, for index 4, ! the minimum, the index, and the maximum. ! ! Output, integer INDEX1234, the index of (I1,I2,I3,I4). ! implicit none integer i1 integer i1_max integer i1_min integer i2 integer i2_max integer i2_min integer i3 integer i3_max integer i3_min integer i4 integer i4_max integer i4_min integer, parameter :: index_min = 1 integer index1234 call i4_fake_use ( i4_max ) index1234 = & index_min & + ( i1 - i1_min ) & + ( i1_max + 1 - i1_min ) * ( i2 - i2_min ) & + ( i1_max + 1 - i1_min ) * ( i2_max + 1 - i2_min ) & * ( i3 - i3_min ) & + ( i1_max + 1 - i1_min ) * ( i2_max + 1 - i2_min ) & * ( i3_max + 1 - i3_min ) * ( i4 - i4_min ) return end function index1n ( n, i_min, i, i_max ) !*****************************************************************************80 ! !! index1n() indexes an N-dimensional array by columns, with unit base. ! ! Discussion: ! ! Entries of the array are indexed starting at entry ! ( I_MIN(1), I_MIN(2),...,I_MIN(N) ), ! and increasing the first index up to I_MAX(1), ! then the second and so on. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 03 April 2010 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer N, the number of indices. ! ! Input, integer I_MIN(N), the minimum indices. ! ! Input, integer I(N), the indices. ! ! Input, integer I_MAX(N), for maximum indices. ! ! Output, integer INDEX1N, the index of element I. ! implicit none integer n integer i(n) integer i_max(n) integer i_min(n) integer, parameter :: index_min = 1 integer index1n integer j integer value value = ( i(n) - i_min(n) ) do j = n - 1, 1, - 1 value = value * ( i_max(j) + 1 - i_min(j) ) + ( i(j) - i_min(j) ) end do value = value + index_min index1n = value return end function index21 ( i_min, i, i_max, j_min, j, j_max ) !*****************************************************************************80 ! !! index21() indexes a 2D array by rows, with a unit base. ! ! Discussion: ! ! Entries of the array are indexed starting at entry (I_MIN,J_MIN), ! and increasing the column index first. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 15 November 2012 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer I_MIN, I, I_MAX, for row indices, ! the minimum, the index, and the maximum. ! ! Input, integer J_MIN, J, J_MAX, for column indices, ! the minimum, the index, and the maximum. ! ! Output, integer INDEX21, the index of element (I,J). ! implicit none integer i integer i_max integer i_min integer, parameter :: index_min = 1 integer index21 integer j integer j_max integer j_min call i4_fake_use ( i_max ) index21 = index_min & + ( j - j_min ) & + ( i - i_min ) * ( j_max + 1 - j_min ) return end function index210 ( i_min, i, i_max, j_min, j, j_max, k_min, k, k_max ) !*****************************************************************************80 ! !! index210() indexes a 3D array by rows, with zero base. ! ! Discussion: ! ! When we say "by rows", we really just mean that entries of the array are ! indexed starting at entry (I_MIN,J_MIN,K_MIN), and the increasing the LAST ! index first, then the next-to-the-last, and so on. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 15 November 2012 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer I_MIN, I, I_MAX, for row indices, ! the minimum, the index, and the maximum. ! ! Input, integer J_MIN, J, J_MAX, for column indices, ! the minimum, the index, and the maximum. ! ! Input, integer K_MIN, K, K_MAX, for plane indices, ! the minimum, the index, and the maximum. ! ! Output, integer INDEX210, the index of element (I,J,K). ! implicit none integer i integer i_max integer i_min integer, parameter :: index_min = 0 integer index210 integer j integer j_max integer j_min integer k integer k_max integer k_min call i4_fake_use ( i_max ) index210 = & index_min & + ( k - k_min ) & + ( j - j_min ) * ( k_max + 1 - k_min ) & + ( i - i_min ) * ( j_max + 1 - j_min ) * ( k_max + 1 - k_min ) return end function index321 ( i_min, i, i_max, j_min, j, j_max, k_min, k, k_max ) !*****************************************************************************80 ! !! index321() indexes a 3D array by rows, with zero base. ! ! Discussion: ! ! When we say "by rows", we really just mean that entries of the array are ! indexed starting at entry (I_MIN,J_MIN,K_MIN), and the increasing the LAST ! index first, then the next-to-the-last, and so on. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 15 November 2012 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer I_MIN, I, I_MAX, for row indices, ! the minimum, the index, and the maximum. ! ! Input, integer J_MIN, J, J_MAX, for column indices, ! the minimum, the index, and the maximum. ! ! Input, integer K_MIN, K, K_MAX, for plane indices, ! the minimum, the index, and the maximum. ! ! Output, integer INDEX321, the index of element (I,J,K). ! implicit none integer i integer i_max integer i_min integer, parameter :: index_min = 1 integer index321 integer j integer j_max integer j_min integer k integer k_max integer k_min call i4_fake_use ( i_max ) index321 = & index_min & + ( k - k_min ) & + ( j - j_min ) * ( k_max + 1 - k_min ) & + ( i - i_min ) * ( j_max + 1 - j_min ) * ( k_max + 1 - k_min ) return end function index3210 ( i1_min, i1, i1_max, i2_min, i2, i2_max, i3_min, i3, & i3_max, i4_min, i4, i4_max ) !*****************************************************************************80 ! !! index3210() indexes a 4D array by rows, with zero base. ! ! Discussion: ! ! Entries are indexed starting at (I1_MIN,I2_MIN,I3_MIN,I4_MIN), ! and increasing the last index, then the next to last, and so on. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 16 November 2012 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer I1_MIN, I1, I1_MAX, for index 1, ! the minimum, the index, and the maximum. ! ! Input, integer I2_MIN, I2, I2_MAX, for index 2, ! the minimum, the index, and the maximum. ! ! Input, integer I3_MIN, I3, I3_MAX, for index 3, ! the minimum, the index, and the maximum. ! ! Input, integer I4_MIN, I4, I4_MAX, for index 4, ! the minimum, the index, and the maximum. ! ! Output, integer INDEX3210, the index of (I1,I2,I3,I4). ! implicit none integer i1 integer i1_max integer i1_min integer i2 integer i2_max integer i2_min integer i3 integer i3_max integer i3_min integer i4 integer i4_max integer i4_min integer, parameter :: index_min = 0 integer index3210 call i4_fake_use ( i1_max ) index3210 = & index_min & + ( i4 - i4_min ) & + ( i3 - i3_min ) & * ( i4_max + 1 - i4_min ) & + ( i2 - i2_min ) * ( i3_max + 1 - i3_min ) & * ( i4_max + 1 - i4_min ) & + ( i1 - i1_min ) * ( i2_max + 1 - i2_min ) * ( i3_max + 1 - i3_min ) & * ( i4_max + 1 - i4_min ) return end function index4321 ( i1_min, i1, i1_max, i2_min, i2, i2_max, i3_min, i3, & i3_max, i4_min, i4, i4_max ) !*****************************************************************************80 ! !! index4321() indexes a 4D array by rows, with unit base. ! ! Discussion: ! ! Entries are indexed starting at (I1_MIN,I2_MIN,I3_MIN,I4_MIN), ! and increasing the last index, then the next to last, and so on. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 16 November 2012 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer I1_MIN, I1, I1_MAX, for index 1, ! the minimum, the index, and the maximum. ! ! Input, integer I2_MIN, I2, I2_MAX, for index 2, ! the minimum, the index, and the maximum. ! ! Input, integer I3_MIN, I3, I3_MAX, for index 3, ! the minimum, the index, and the maximum. ! ! Input, integer I4_MIN, I4, I4_MAX, for index 4, ! the minimum, the index, and the maximum. ! ! Output, integer INDEX4321, the index of (I1,I2,I3,I4). ! implicit none integer i1 integer i1_max integer i1_min integer i2 integer i2_max integer i2_min integer i3 integer i3_max integer i3_min integer i4 integer i4_max integer i4_min integer, parameter :: index_min = 1 integer index4321 call i4_fake_use ( i1_max ) index4321 = & index_min & + ( i4 - i4_min ) & + ( i3 - i3_min ) & * ( i4_max + 1 - i4_min ) & + ( i2 - i2_min ) * ( i3_max + 1 - i3_min ) & * ( i4_max + 1 - i4_min ) & + ( i1 - i1_min ) * ( i2_max + 1 - i2_min ) * ( i3_max + 1 - i3_min ) & * ( i4_max + 1 - i4_min ) return end function indexn0 ( n, i_min, i, i_max ) !*****************************************************************************80 ! !! indexn0() indexes an N-dimensional array by rows, with zero base. ! ! Discussion: ! ! Entries of the array are indexed starting at entry ! ( I_MIN(1), I_MIN(2),...,I_MIN(N) ), ! and increasing the last index up to I_MAX(N), ! then the next-to-last and so on. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 16 November 2012 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer N, the number of indices. ! ! Input, integer I_MIN(N), the minimum indices. ! ! Input, integer I(N), the indices. ! ! Input, integer I_MAX(N), for maximum indices. ! ! Output, integer INDEXN0, the index of element I. ! implicit none integer n integer i(n) integer i_max(n) integer i_min(n) integer, parameter :: index_min = 0 integer indexn0 integer j integer value value = ( i(1) - i_min(1) ) do j = 2, n value = value * ( i_max(j) + 1 - i_min(j) ) + ( i(j) - i_min(j) ) end do value = value + index_min indexn0 = value return end function indexn1 ( n, i_min, i, i_max ) !*****************************************************************************80 ! !! indexn1() indexes an N-dimensional array by rows, with unit base. ! ! Discussion: ! ! Entries of the array are indexed starting at entry ! ( I_MIN(1), I_MIN(2),...,I_MIN(N) ), ! and increasing the last index up to I_MAX(N), ! then the next-to-last and so on. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 16 November 2012 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer N, the number of indices. ! ! Input, integer I_MIN(N), the minimum indices. ! ! Input, integer I(N), the indices. ! ! Input, integer I_MAX(N), for maximum indices. ! ! Output, integer INDEXN1, the index of element I. ! implicit none integer n integer i(n) integer i_max(n) integer i_min(n) integer, parameter :: index_min = 1 integer indexn1 integer j integer value value = ( i(1) - i_min(1) ) do j = 2, n value = value * ( i_max(j) + 1 - i_min(j) ) + ( i(j) - i_min(j) ) end do value = value + index_min indexn1 = value return end