function i4_log_10 ( i ) !*****************************************************************************80 ! !! I4_LOG_10 returns the integer part of the logarithm base 10 of an I4. ! ! Discussion: ! ! I4_LOG_10 ( I ) + 1 is the number of decimal digits in I. ! ! An I4 is an integer value. ! ! Example: ! ! I I4_LOG_10 ! ----- -------- ! 0 0 ! 1 0 ! 2 0 ! 9 0 ! 10 1 ! 11 1 ! 99 1 ! 100 2 ! 101 2 ! 999 2 ! 1000 3 ! 1001 3 ! 9999 3 ! 10000 4 ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 08 June 2003 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer I, the number whose logarithm base 10 ! is desired. ! ! Output, integer I4_LOG_10, the integer part of the ! logarithm base 10 of the absolute value of X. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer i integer i_abs integer i4_log_10 integer ten_pow if ( i == 0 ) then i4_log_10 = 0 else i4_log_10 = 0 ten_pow = 10 i_abs = abs ( i ) do while ( ten_pow <= i_abs ) i4_log_10 = i4_log_10 + 1 ten_pow = ten_pow * 10 end do end if return end subroutine i4mat_print ( m, n, a, title ) !*****************************************************************************80 ! !! I4MAT_PRINT prints an I4MAT. ! ! Discussion: ! ! An I4MAT is a rectangular array of I4's. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 30 June 2003 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, the number of rows in A. ! ! Input, integer N, the number of columns in A. ! ! Input, integer A(M,N), the matrix to be printed. ! ! Input, character ( len = * ) TITLE, a title. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer n integer a(m,n) integer ihi integer ilo integer jhi integer jlo character ( len = * ) title ilo = 1 ihi = m jlo = 1 jhi = n call i4mat_print_some ( m, n, a, ilo, jlo, ihi, jhi, title ) return end subroutine i4mat_print_some ( m, n, a, ilo, jlo, ihi, jhi, title ) !*****************************************************************************80 ! !! I4MAT_PRINT_SOME prints some of an I4MAT. ! ! Discussion: ! ! An I4MAT is a rectangular array of I4's. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 10 September 2009 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, N, the number of rows and columns. ! ! Input, integer A(M,N), an M by N matrix to be printed. ! ! Input, integer ILO, JLO, the first row and column to print. ! ! Input, integer IHI, JHI, the last row and column to print. ! ! Input, character ( len = * ) TITLE, a title. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer, parameter :: incx = 10 integer m integer n integer a(m,n) character ( len = 8 ) ctemp(incx) integer i integer i2hi integer i2lo integer ihi integer ilo integer inc integer j integer j2 integer j2hi integer j2lo integer jhi integer jlo character ( len = * ) title if ( 0 < len_trim ( title ) ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) trim ( title ) end if if ( m <= 0 .or. n <= 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) ' (None)' return end if do j2lo = max ( jlo, 1 ), min ( jhi, n ), incx j2hi = j2lo + incx - 1 j2hi = min ( j2hi, n ) j2hi = min ( j2hi, jhi ) inc = j2hi + 1 - j2lo write ( *, '(a)' ) ' ' do j = j2lo, j2hi j2 = j + 1 - j2lo write ( ctemp(j2), '(i8)' ) j end do write ( *, '('' Col '',10a8)' ) ctemp(1:inc) write ( *, '(a)' ) ' Row' write ( *, '(a)' ) ' ' i2lo = max ( ilo, 1 ) i2hi = min ( ihi, m ) do i = i2lo, i2hi do j2 = 1, inc j = j2lo - 1 + j2 write ( ctemp(j2), '(i8)' ) a(i,j) end do write ( *, '(i5,a,10a8)' ) i, ':', ( ctemp(j), j = 1, inc ) end do end do return end subroutine i4vec_print ( n, a, title ) !*****************************************************************************80 ! !! I4VEC_PRINT prints an I4VEC. ! ! Discussion: ! ! An I4VEC is a vector of I4's. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 02 May 2010 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer N, the number of components of the vector. ! ! Input, integer A(N), the vector to be printed. ! ! Input, character ( len = * ) TITLE, a title. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer n integer a(n) integer i character ( len = * ) title write ( *, '(a)' ) ' ' write ( *, '(a)' ) trim ( title ) write ( *, '(a)' ) ' ' do i = 1, n write ( *, '(2x,i8,a,2x,i12)' ) i, ':', a(i) end do return end subroutine r8row_compare ( m, n, a, i, j, value ) !*****************************************************************************80 ! !! R8ROW_COMPARE compares rows in an R8ROW. ! ! Discussion: ! ! An R8ROW is an M by N array of R8's, regarded as an array of M rows, ! each of length N. ! ! Example: ! ! Input: ! ! M = 4, N = 3, I = 2, J = 4 ! ! A = ( ! 1 5 9 ! 2 6 10 ! 3 7 11 ! 4 8 12 ) ! ! Output: ! ! VALUE = -1 ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 21 May 2012 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, N, the number of rows and columns. ! ! Input, real ( kind = rk ) A(M,N), the M by N array. ! ! Input, integer I, J, the rows to be compared. ! I and J must be between 1 and M. ! ! Output, integer VALUE, the results of the comparison: ! -1, row I < row J, ! 0, row I = row J, ! +1, row J < row I. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer n real ( kind = rk ) a(m,n) integer i integer j integer k integer value ! ! Check. ! if ( i < 1 .or. m < i ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'R8ROW_COMPARE - Fatal error!' write ( *, '(a)' ) ' Row index I is out of bounds.' write ( *, '(a,i8)' ) ' I = ', i stop 1 end if if ( j < 1 .or. m < j ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'R8ROW_COMPARE - Fatal error!' write ( *, '(a)' ) ' Row index J is out of bounds.' write ( *, '(a,i8)' ) ' J = ', j stop 1 end if value = 0 if ( i == j ) then return end if k = 1 do while ( k <= n ) if ( a(i,k) < a(j,k) ) then value = -1 return else if ( a(j,k) < a(i,k) ) then value = +1 return end if k = k + 1 end do return end subroutine r8row_indicator ( m, n, a ) !*****************************************************************************80 ! !! R8ROW_INDICATOR sets up an "indicator" R8ROW. ! ! Discussion: ! ! An R8ROW is an M by N array of R8's, regarded as an array of M rows, ! each of length N. ! ! The value of each entry suggests its location, as in: ! ! 11 12 13 14 ! 21 22 23 24 ! 31 32 33 34 ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 28 February 2016 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, the number of rows of the matrix. ! M must be positive. ! ! Input, integer N, the number of columns of the matrix. ! N must be positive. ! ! Output, real ( kind = rk ) A(M,N), the matrix. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer n real ( kind = rk ) a(m,n) integer fac integer i integer i4_log_10 integer j fac = 10 ** ( i4_log_10 ( n ) + 1 ) do i = 1, m do j = 1, n a(i,j) = real ( fac * i + j, kind = rk ) end do end do return end subroutine r8row_max ( m, n, a, amax ) !*****************************************************************************80 ! !! R8ROW_MAX returns the maximums of an R8ROW. ! ! Discussion: ! ! An R8ROW is an M by N array of R8 values, regarded ! as an array of M rows of length N. ! ! Example: ! ! A = ! 1 2 3 ! 2 6 7 ! ! MAX = ! 3 ! 7 ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 10 October 2004 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, N, the number of rows and columns ! in the array. ! ! Input, real ( kind = rk ) A(M,N), the array to be examined. ! ! Output, real ( kind = rk ) AMAX(M), the maximums of the rows. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer n real ( kind = rk ) a(m,n) real ( kind = rk ) amax(m) integer i integer j do i = 1, m amax(i) = a(i,1) do j = 2, n if ( amax(i) < a(i,j) ) then amax(i) = a(i,j) end if end do end do return end subroutine r8row_mean ( m, n, a, mean ) !*****************************************************************************80 ! !! R8ROW_MEAN returns the means of an R8ROW. ! ! Discussion: ! ! An R8ROW is an M by N array of R8 values, regarded ! as an array of M rows of length N. ! ! Example: ! ! A = ! 1 2 3 ! 2 6 7 ! ! MEAN = ! 2 ! 5 ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 10 October 2004 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, N, the number of rows and columns. ! ! Input, real ( kind = rk ) A(M,N), the array to be examined. ! ! Output, real ( kind = rk ) MEAN(M), the means, or averages, of the rows. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer n real ( kind = rk ) a(m,n) integer i real ( kind = rk ) mean(m) do i = 1, m mean(i) = sum ( a(i,1:n) ) / real ( n, kind = rk ) end do return end subroutine r8row_min ( m, n, a, amin ) !*****************************************************************************80 ! !! R8ROW_MIN returns the minimums of an R8ROW. ! ! Discussion: ! ! An R8ROW is an M by N array of R8 values, regarded ! as an array of M rows of length N. ! ! Example: ! ! A = ! 1 2 3 ! 2 6 7 ! ! MIN = ! 1 ! 2 ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 10 October 2004 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, N, the number of rows and columns ! in the array. ! ! Input, real ( kind = rk ) A(M,N), the array to be examined. ! ! Output, real ( kind = rk ) AMIN(M), the minimums of the rows. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer n real ( kind = rk ) a(m,n) real ( kind = rk ) amin(m) integer i integer j do i = 1, m amin(i) = a(i,1) do j = 2, n if ( a(i,j) < amin(i) ) then amin(i) = a(i,j) end if end do end do return end subroutine r8row_part_quick_a ( m, n, a, l, r ) !*****************************************************************************80 ! !! R8ROW_PART_QUICK_A reorders the rows of an R8ROW. ! ! Discussion: ! ! An R8ROW is an M by N array of R8's, regarded as an array of M rows, ! each of length N. ! ! The routine reorders the rows of A. Using A(1,1:N) as a ! key, all entries of A that are less than or equal to the key will ! precede the key, which precedes all entries that are greater than the key. ! ! Example: ! ! Input: ! ! M = 8, N = 2 ! A = ( 2 4 ! 8 8 ! 6 2 ! 0 2 ! 10 6 ! 10 0 ! 0 6 ! 5 8 ) ! ! Output: ! ! L = 2, R = 4 ! ! A = ( 0 2 LEFT ! 0 6 ! ---- ! 2 4 KEY ! ---- ! 8 8 RIGHT ! 6 2 ! 10 6 ! 10 0 ! 5 8 ) ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 21 May 2012 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, the row dimension of A. ! ! Input, integer N, the column dimension of A, and the ! length of a row. ! ! Input/output, real ( kind = rk ) A(M,N). On input, the array to be checked. ! On output, A has been reordered as described above. ! ! Output, integer L, R, the indices of A that define the three ! segments. Let KEY = the input value of A(1,1:N). Then ! I <= L A(I,1:N) < KEY; ! L < I < R A(I,1:N) = KEY; ! R <= I KEY < A(I,1:N). ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer n real ( kind = rk ) a(m,n) integer j integer k real ( kind = rk ) key(n) integer l integer r logical ( kind = 4 ) r8vec_eq logical ( kind = 4 ) r8vec_gt logical ( kind = 4 ) r8vec_lt if ( m < 1 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'R8ROW_PART_QUICK_A - Fatal error!' write ( *, '(a)' ) ' M < 1.' return end if if ( m == 1 ) then l = 0 r = 2 return end if key(1:n) = a(1,1:n) k = 1 ! ! The elements of unknown size have indices between L+1 and R-1. ! l = 1 r = m + 1 do j = 2, m if ( r8vec_gt ( n, a(l+1,1:n), key(1:n) ) ) then r = r - 1 call r8vec_swap ( n, a(r,1:n), a(l+1,1:n) ) else if ( r8vec_eq ( n, a(l+1,1:n), key(1:n) ) ) then k = k + 1 call r8vec_swap ( n, a(k,1:n), a(l+1,1:n) ) l = l + 1 else if ( r8vec_lt ( n, a(l+1,1:n), key(1:n) ) ) then l = l + 1 end if end do ! ! Shift small elements to the left. ! do j = 1, l - k a(j,1:n) = a(j+k,1:n) end do ! ! Shift KEY elements to center. ! do j = l - k + 1, l a(j,1:n) = key(1:n) end do ! ! Update L. ! l = l - k return end subroutine r8row_print ( m, n, a, title ) !*****************************************************************************80 ! !! R8ROW_PRINT prints an R8ROW. ! ! Discussion: ! ! An R8ROW is an M by N array of R8's, regarded as an array of M rows, ! each of length N. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 12 September 2004 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, the number of rows in A. ! ! Input, integer N, the number of columns in A. ! ! Input, real ( kind = rk ) A(M,N), the matrix. ! ! Input, character ( len = * ) TITLE, a title. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer n real ( kind = rk ) a(m,n) character ( len = * ) title call r8row_print_some ( m, n, a, 1, 1, m, n, title ) return end subroutine r8row_print_some ( m, n, a, ilo, jlo, ihi, jhi, title ) !*****************************************************************************80 ! !! R8ROW_PRINT_SOME prints some of an R8ROW. ! ! Discussion: ! ! An R8ROW is an M by N array of R8's, regarded as an array of M rows, ! each of length N. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 10 September 2009 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, N, the number of rows and columns. ! ! Input, real ( kind = rk ) A(M,N), an M by N matrix to be printed. ! ! Input, integer ILO, JLO, the first row and column to print. ! ! Input, integer IHI, JHI, the last row and column to print. ! ! Input, character ( len = * ) TITLE, a title. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer, parameter :: incx = 5 integer m integer n real ( kind = rk ) a(m,n) character ( len = 14 ) ctemp(incx) integer i integer i2hi integer i2lo integer ihi integer ilo integer inc integer j integer j2 integer j2hi integer j2lo integer jhi integer jlo character ( len = * ) title write ( *, '(a)' ) ' ' write ( *, '(a)' ) trim ( title ) if ( m <= 0 .or. n <= 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) ' (None)' return end if do j2lo = max ( jlo, 1 ), min ( jhi, n ), incx j2hi = j2lo + incx - 1 j2hi = min ( j2hi, n ) j2hi = min ( j2hi, jhi ) inc = j2hi + 1 - j2lo write ( *, '(a)' ) ' ' do j = j2lo, j2hi j2 = j + 1 - j2lo write ( ctemp(j2), '(i8,6x)' ) j end do write ( *, '('' Col '',5a14)' ) ctemp(1:inc) write ( *, '(a)' ) ' Row' write ( *, '(a)' ) ' ' i2lo = max ( ilo, 1 ) i2hi = min ( ihi, m ) do i = i2lo, i2hi do j2 = 1, inc j = j2lo - 1 + j2 if ( a(i,j) == real ( int ( a(i,j) ), kind = rk ) ) then write ( ctemp(j2), '(f8.0,6x)' ) a(i,j) else write ( ctemp(j2), '(g14.6)' ) a(i,j) end if end do write ( *, '(i5,a,5a14)' ) i, ':', ( ctemp(j), j = 1, inc ) end do end do return end subroutine r8row_reverse ( m, n, a ) !****************************************************************************80 ! !! R8ROW_REVERSE reverses the order of the rows of an R8ROW. ! ! Discussion: ! ! An R8ROW is an M by N array of R8's, regarded as an array of M rows, ! each of length N. ! ! To reverse the rows is to start with something like ! ! 11 12 13 14 15 ! 21 22 23 24 25 ! 31 32 33 34 35 ! 41 42 43 44 45 ! 51 52 53 54 55 ! ! and return ! ! 51 52 53 54 55 ! 41 42 43 44 45 ! 31 32 33 34 35 ! 21 22 23 24 25 ! 11 12 13 14 15 ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 06 May 2013 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, N, the number of rows and columns. ! ! Input/output, real ( kind = rk ) A(M,N), the matrix. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer n real ( kind = rk ) a(m,n) integer i integer ihi real ( kind = rk ) t(n) ihi = m / 2 do i = 1, ihi t(1:n) = a(i,1:n) a(i,1:n) = a(m+1-i,1:n) a(m+1-i,1:n) = t(1:n) end do return end subroutine r8row_running_average ( m, n, v, a ) !*****************************************************************************80 ! !! R8ROW_RUNNING_AVERAGE computes the running averages of an R8ROW. ! ! Discussion: ! ! An R8ROW is an M by N array of R8's, regarded as an array of M rows, ! each of length N. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 24 February 2016 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, the number of rows. ! ! Input, integer N, the number of items in each row. ! ! Input, real ( kind = rk ) V(M,N), the data. ! ! Output, real ( kind = rk ) A(M,N+1), the running average. A(I,J) is the ! average value of V(I,1:J-1). ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer n real ( kind = rk ) a(m,n+1) integer j real ( kind = rk ) v(m,n) ! ! Sum. ! a(1:m,1) = 0.0D+00 do j = 2, n + 1 a(1:m,j) = a(1:m,j-1) + v(1:m,j-1) end do ! ! Average. ! do j = 2, n + 1 a(1:m,j) = a(1:m,j) / real ( j - 1, kind = rk ) end do return end subroutine r8row_running_sum ( m, n, v, s ) !*****************************************************************************80 ! !! R8ROW_RUNNING_SUM computes the running sum of an R8ROW. ! ! Discussion: ! ! An R8ROW is an M by N array of R8's, regarded as an array of M rows, ! each of length N. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 24 February 2016 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, the number of rows. ! ! Input, integer N, the number of items in each row. ! ! Input, real ( kind = rk ) V(M,N), the data. ! ! Output, real ( kind = rk ) S(M,N+1), the running sums. S(I,J) is the sum ! of V(i,1:J-1). ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer n integer j real ( kind = rk ) s(m,n+1) real ( kind = rk ) v(m,n) ! ! Sum. ! s(1:m,1) = 0.0D+00 do j = 2, n + 1 s(1:m,j) = s(1:m,j-1) + v(1:m,j-1) end do return end subroutine r8row_sort_heap_a ( m, n, a ) !*****************************************************************************80 ! !! R8ROW_SORT_HEAP_A ascending heapsorts an R8ROW. ! ! Discussion: ! ! An R8ROW is an M by N array of R8's, regarded as an array of M rows, ! each of length N. ! ! In lexicographic order, the statement "X < Y", applied to two real ! vectors X and Y of length M, means that there is some index I, with ! 1 <= I <= M, with the property that ! ! X(J) = Y(J) for J < I, ! and ! X(I) < Y(I). ! ! In other words, the first time they differ, X is smaller. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 21 May 2012 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, N, the number of rows and columns. ! ! Input/output, real ( kind = rk ) A(M,N). ! On input, the array of M rows of N-vectors. ! On output, the rows of A have been sorted in lexicographic order. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer n real ( kind = rk ) a(m,n) integer i integer indx integer isgn integer j if ( m <= 0 ) then return end if if ( m <= 1 ) then return end if ! ! Initialize. ! i = 0 indx = 0 isgn = 0 j = 0 ! ! Call the external heap sorter. ! do call sort_heap_external ( m, indx, i, j, isgn ) ! ! Interchange the I and J objects. ! if ( 0 < indx ) then call r8row_swap ( m, n, a, i, j ) ! ! Compare the I and J objects. ! else if ( indx < 0 ) then call r8row_compare ( m, n, a, i, j, isgn ) else if ( indx == 0 ) then exit end if end do return end subroutine r8row_sort_heap_index_a ( m, n, a, indx ) !*****************************************************************************80 ! !! R8ROW_SORT_HEAP_INDEX_A does an indexed heap ascending sort of an R8ROW. ! ! Discussion: ! ! An R8ROW is an M by N array of R8's, regarded as an array of M rows, ! each of length N. ! ! The sorting is not actually carried out. Rather an index array is ! created which defines the sorting. This array may be used to sort ! or index the array, or to sort or index related arrays keyed on the ! original array. ! ! A(I1,*) < A(I1,*) if the first nonzero entry of A(I1,*)-A(I2,*) ! is negative. ! ! Once the index array is computed, the sorting can be carried out ! "implicitly: ! ! A(INDX(1:M),1:N) is sorted. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 21 May 2012 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, the number of rows in each column of A. ! ! Input, integer N, the number of columns in A. ! ! Input, real ( kind = rk ) A(M,N), the array. ! ! Output, integer INDX(M), the sort index. The I-th element ! of the sorted array is row INDX(I). ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer n real ( kind = rk ) a(m,n) integer i integer indx(m) integer indxt integer ir integer isgn integer j integer l real ( kind = rk ) row(n) if ( n < 1 ) then return end if do i = 1, m indx(i) = i end do if ( m == 1 ) then return end if l = ( m / 2 ) + 1 ir = m do if ( 1 < l ) then l = l - 1 indxt = indx(l) row(1:n) = a(indxt,1:n) else indxt = indx(ir) row(1:n) = a(indxt,1:n) indx(ir) = indx(1) ir = ir - 1 if ( ir == 1 ) then indx(1) = indxt exit end if end if i = l j = l + l do while ( j <= ir ) if ( j < ir ) then call r8row_compare ( m, n, a, indx(j), indx(j+1), isgn ) if ( isgn < 0 ) then j = j + 1 end if end if call r8vec_compare ( n, row, a(indx(j),1:n), isgn ) if ( isgn < 0 ) then indx(i) = indx(j) i = j j = j + j else j = ir + 1 end if end do indx(i) = indxt end do return end subroutine r8row_sort_quick_a ( m, n, a ) !*****************************************************************************80 ! !! R8ROW_SORT_QUICK_A ascending quick sorts an R8ROW. ! ! Discussion: ! ! An R8ROW is an M by N array of R8's, regarded as an array of M rows, ! each of length N. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 21 May 2012 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, the number of rows of A. ! ! Input, integer N, the number of columns of A, ! and the length of a row. ! ! Input/output, real ( kind = rk ) A(M,N). ! On input, the array to be sorted. ! On output, the array has been sorted. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer, parameter :: level_max = 30 integer m integer n real ( kind = rk ) a(m,n) integer base integer l_segment integer level integer m_segment integer rsave(level_max) integer r_segment if ( n <= 0 ) then return end if if ( m < 1 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'R8ROW_SORT_QUICK_A - Fatal error!' write ( *, '(a)' ) ' M < 1.' write ( *, '(a,i8)' ) ' M = ', m stop 1 end if if ( m == 1 ) then return end if level = 1 rsave(level) = m + 1 base = 1 m_segment = m do ! ! Partition the segment. ! call r8row_part_quick_a ( m_segment, n, a(base:base+m_segment-1,1:n), & l_segment, r_segment ) ! ! If the left segment has more than one element, we need to partition it. ! if ( 1 < l_segment ) then if ( level_max < level ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'R8ROW_SORT_QUICK_A - Fatal error!' write ( *, '(a,i8)' ) ' Exceeding recursion maximum of ', level_max stop 1 end if level = level + 1 m_segment = l_segment rsave(level) = r_segment + base - 1 ! ! The left segment and the middle segment are sorted. ! Must the right segment be partitioned? ! else if ( r_segment < m_segment ) then m_segment = m_segment + 1 - r_segment base = base + r_segment - 1 ! ! Otherwise, we back up a level if there is an earlier one. ! else do if ( level <= 1 ) then return end if base = rsave(level) m_segment = rsave(level-1) - rsave(level) level = level - 1 if ( 0 < m_segment ) then exit end if end do end if end do return end subroutine r8row_sorted_unique_count ( m, n, a, unique_num ) !*****************************************************************************80 ! !! R8ROW_SORTED_UNIQUE_COUNT counts unique elements in an R8ROW. ! ! Discussion: ! ! An R8ROW is an M by N array of R8 values, regarded ! as an array of M rows of length N. ! ! The rows of the array may be ascending or descending sorted. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 17 February 2005 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, N, the number of rows and columns. ! ! Input, real ( kind = rk ) A(M,N), a sorted array, containing ! M rows of data. ! ! Output, integer UNIQUE_NUM, the number of unique rows. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer n real ( kind = rk ) a(m,n) integer i1 integer i2 integer unique_num if ( n <= 0 ) then unique_num = 0 return end if unique_num = 1 i1 = 1 do i2 = 2, m if ( any ( a(i1,1:n) /= a(i2,1:n) ) ) then unique_num = unique_num + 1 i1 = i2 end if end do return end subroutine r8row_sum ( m, n, a, rowsum ) !*****************************************************************************80 ! !! R8ROW_SUM returns the sums of the rows of an R8ROW. ! ! Discussion: ! ! An R8ROW is an M by N array of R8 values, regarded ! as an array of M rows of length N. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 06 December 2004 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, N, the number of rows and columns. ! ! Input, real ( kind = rk ) A(M,N), the M by N array. ! ! Output, real ( kind = rk ) ROWSUM(M), the sum of the entries of ! each row. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer n real ( kind = rk ) a(m,n) integer i real ( kind = rk ) rowsum(m) do i = 1, m rowsum(i) = sum ( a(i,1:n) ) end do return end subroutine r8row_swap ( m, n, a, i1, i2 ) !*****************************************************************************80 ! !! R8ROW_SWAP swaps two rows of an R8ROW. ! ! Discussion: ! ! An R8ROW is an M by N array of R8 values, regarded ! as an array of M rows of length N. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 05 December 2004 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, N, the number of rows and columns. ! ! Input/output, real ( kind = rk ) A(M,N), the M by N array. ! ! Input, integer I1, I2, the two rows to swap. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer n real ( kind = rk ) a(m,n) integer i1 integer i2 real ( kind = rk ) row(n) if ( i1 < 1 .or. m < i1 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'R8ROW_SWAP - Fatal error!' write ( *, '(a)' ) ' I1 is out of range.' write ( *, '(a,i8)' ) ' I1 = ', i1 stop 1 end if if ( i2 < 1 .or. m < i2 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'R8ROW_SWAP - Fatal error!' write ( *, '(a)' ) ' I2 is out of range.' write ( *, '(a,i8)' ) ' I2 = ', i2 stop 1 end if if ( i1 == i2 ) then return end if row(1:n) = a(i1,1:n) a(i1,1:n) = a(i2,1:n) a(i2,1:n) = row(1:n) return end subroutine r8row_to_r8vec ( m, n, a, x ) !*****************************************************************************80 ! !! R8ROW_TO_R8VEC converts an R8ROW into an R8VEC. ! ! Discussion: ! ! An R8ROW is an M by N array of R8 values, regarded ! as an array of M rows of length N. ! ! Example: ! ! M = 3, N = 4 ! ! A = ! 11 12 13 14 ! 21 22 23 24 ! 31 32 33 34 ! ! X = ( 11, 12, 13, 14, 21, 22, 23, 24, 31, 32, 33, 34 ) ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 13 July 2000 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, N, the number of rows and columns. ! ! Input, real ( kind = rk ) A(M,N), the M by N array. ! ! Output, real ( kind = rk ) X(M*N), a vector containing the M rows of A. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer n real ( kind = rk ) a(m,n) integer i integer j real ( kind = rk ) x(m*n) j = 1 do i = 1, m x(j:j+n-1) = a(i,1:n) j = j + n end do return end subroutine r8row_transpose_print ( m, n, a, title ) !*****************************************************************************80 ! !! R8ROW_TRANSPOSE_PRINT prints an R8ROW, transposed. ! ! Discussion: ! ! An R8ROW is an M by N array of R8 values, regarded ! as an array of M rows of length N. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 14 June 2004 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, N, the number of rows and columns. ! ! Input, real ( kind = rk ) A(M,N), an M by N matrix to be printed. ! ! Input, character ( len = * ) TITLE, a title. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer n real ( kind = rk ) a(m,n) character ( len = * ) title call r8row_transpose_print_some ( m, n, a, 1, 1, m, n, title ) return end subroutine r8row_transpose_print_some ( m, n, a, ilo, jlo, ihi, jhi, title ) !*****************************************************************************80 ! !! R8ROW_TRANSPOSE_PRINT_SOME prints some of an R8ROW, transposed. ! ! Discussion: ! ! An R8ROW is an M by N array of R8 values, regarded ! as an array of M rows of length N. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 10 September 2009 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, N, the number of rows and columns. ! ! Input, real ( kind = rk ) A(M,N), an M by N matrix to be printed. ! ! Input, integer ILO, JLO, the first row and column to print. ! ! Input, integer IHI, JHI, the last row and column to print. ! ! Input, character ( len = * ) TITLE, a title. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer, parameter :: incx = 5 integer m integer n real ( kind = rk ) a(m,n) character ( len = 14 ) ctemp(incx) integer i integer i2 integer i2hi integer i2lo integer ihi integer ilo integer inc integer j integer j2hi integer j2lo integer jhi integer jlo character ( len = * ) title write ( *, '(a)' ) ' ' write ( *, '(a)' ) trim ( title ) if ( m <= 0 .or. n <= 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) ' (None)' return end if do i2lo = max ( ilo, 1 ), min ( ihi, m ), incx i2hi = i2lo + incx - 1 i2hi = min ( i2hi, m ) i2hi = min ( i2hi, ihi ) inc = i2hi + 1 - i2lo write ( *, '(a)' ) ' ' do i = i2lo, i2hi i2 = i + 1 - i2lo write ( ctemp(i2), '(i8,6x)' ) i end do write ( *, '('' Row '',5a14)' ) ctemp(1:inc) write ( *, '(a)' ) ' Col' write ( *, '(a)' ) ' ' j2lo = max ( jlo, 1 ) j2hi = min ( jhi, n ) do j = j2lo, j2hi do i2 = 1, inc i = i2lo - 1 + i2 write ( ctemp(i2), '(g14.6)' ) a(i,j) end do write ( *, '(i5,a,5a14)' ) j, ':', ( ctemp(i), i = 1, inc ) end do end do return end subroutine r8row_uniform_ab ( m, n, a, b, r ) !*****************************************************************************80 ! !! R8ROW_UNIFORM_AB returns a scaled pseudorandom R8ROW. ! ! Discussion: ! ! An R8ROW is an M by N array of R8 values, regarded ! as an array of M rows of length N. ! ! A <= R(I,J) <= B. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 31 May 2007 ! ! Author: ! ! John Burkardt ! ! Reference: ! ! Paul Bratley, Bennett Fox, Linus Schrage, ! A Guide to Simulation, ! Second Edition, ! Springer, 1987, ! ISBN: 0387964673, ! LC: QA76.9.C65.B73. ! ! Bennett Fox, ! Algorithm 647: ! Implementation and Relative Efficiency of Quasirandom ! Sequence Generators, ! ACM Transactions on Mathematical Software, ! Volume 12, Number 4, December 1986, pages 362-376. ! ! Pierre L'Ecuyer, ! Random Number Generation, ! in Handbook of Simulation, ! edited by Jerry Banks, ! Wiley, 1998, ! ISBN: 0471134031, ! LC: T57.62.H37. ! ! Peter Lewis, Allen Goodman, James Miller, ! A Pseudo-Random Number Generator for the System/360, ! IBM Systems Journal, ! Volume 8, Number 2, 1969, pages 136-143. ! ! Parameters: ! ! Input, integer M, N, the number of rows and columns ! in the array. ! ! Input, real ( kind = rk ) A, B, the lower and upper limits. ! ! Output, real ( kind = rk ) R(M,N), the array of pseudorandom values. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer n real ( kind = rk ) a real ( kind = rk ) b real ( kind = rk ) r(m,n) call random_number ( harvest = r(1:m,1:n) ) r(1:m,1:n) = a + ( b - a ) * r(1:m,1:n) return end subroutine r8row_variance ( m, n, a, variance ) !*****************************************************************************80 ! !! R8ROW_VARIANCE returns the variances of an R8ROW. ! ! Discussion: ! ! An R8ROW is an M by N array of R8 values, regarded ! as an array of M rows of length N. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 10 October 2004 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer M, N, the number of rows and columns ! in the array. ! ! Input, real ( kind = rk ) A(M,N), the array whose variances are desired. ! ! Output, real ( kind = rk ) VARIANCE(M), the variances of the rows. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer m integer n real ( kind = rk ) a(m,n) integer i integer j real ( kind = rk ) mean real ( kind = rk ) variance(m) do i = 1, m mean = sum ( a(i,1:n) ) / real ( n, kind = rk ) variance(i) = 0.0D+00 do j = 1, n variance(i) = variance(i) + ( a(i,j) - mean )**2 end do if ( 1 < n ) then variance(i) = variance(i) / real ( n - 1, kind = rk ) else variance(i) = 0.0D+00 end if end do return end subroutine r8vec_compare ( n, a1, a2, isgn ) !*****************************************************************************80 ! !! R8VEC_COMPARE compares two R8VEC's. ! ! Discussion: ! ! An R8VEC is a vector of R8's. ! ! The lexicographic ordering is used. ! ! Example: ! ! Input: ! ! A1 = ( 2.0, 6.0, 2.0 ) ! A2 = ( 2.0, 8.0, 12.0 ) ! ! Output: ! ! ISGN = -1 ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 23 February 1999 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer N, the number of entries in the vectors. ! ! Input, real ( kind = rk ) A1(N), A2(N), the vectors to be compared. ! ! Output, integer ISGN, the results of the comparison: ! -1, A1 < A2, ! 0, A1 = A2, ! +1, A1 > A2. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer n real ( kind = rk ) a1(n) real ( kind = rk ) a2(n) integer isgn integer k isgn = 0 k = 1 do while ( k <= n ) if ( a1(k) < a2(k) ) then isgn = -1 return else if ( a2(k) < a1(k) ) then isgn = + 1 return end if k = k + 1 end do return end function r8vec_eq ( n, a1, a2 ) !*****************************************************************************80 ! !! R8VEC_EQ is true if two R8VECs are equal. ! ! Discussion: ! ! An R8VEC is a vector of R8's. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 05 December 2004 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer N, the number of entries in the vectors. ! ! Input, real ( kind = rk ) A1(N), A2(N), two vectors to compare. ! ! Output, logical ( kind = 4 ) R8VEC_EQ, is TRUE if every pair of elements ! A1(I) and A2(I) are equal, and FALSE otherwise. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer n real ( kind = rk ) a1(n) real ( kind = rk ) a2(n) logical ( kind = 4 ) r8vec_eq r8vec_eq = ( all ( a1(1:n) == a2(1:n) ) ) return end function r8vec_gt ( n, a1, a2 ) !*****************************************************************************80 ! !! R8VEC_GT == ( A1 > A2 ) for R8VEC's. ! ! Discussion: ! ! An R8VEC is a vector of R8's. ! ! The comparison is lexicographic. ! ! A1 > A2 <=> A1(1) > A2(1) or ! ( A1(1) == A2(1) and A1(2) > A2(2) ) or ! ... ! ( A1(1:N-1) == A2(1:N-1) and A1(N) > A2(N) ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 05 December 2004 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer N, the dimension of the vectors. ! ! Input, real ( kind = rk ) A1(N), A2(N), the vectors to be compared. ! ! Output, logical ( kind = 4 ) R8VEC_GT, is TRUE if and only if A1 > A2. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer n real ( kind = rk ) a1(n) real ( kind = rk ) a2(n) integer i logical ( kind = 4 ) r8vec_gt r8vec_gt = .false. do i = 1, n if ( a2(i) < a1(i) ) then r8vec_gt = .true. exit else if ( a1(i) < a2(i) ) then r8vec_gt = .false. exit end if end do return end function r8vec_lt ( n, a1, a2 ) !*****************************************************************************80 ! !! R8VEC_LT == ( A1 < A2 ) for R8VEC's. ! ! Discussion: ! ! An R8VEC is a vector of R8's. ! ! The comparison is lexicographic. ! ! A1 < A2 <=> A1(1) < A2(1) or ! ( A1(1) == A2(1) and A1(2) < A2(2) ) or ! ... ! ( A1(1:N-1) == A2(1:N-1) and A1(N) < A2(N) ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 05 December 2004 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer N, the dimension of the vectors. ! ! Input, real ( kind = rk ) A1(N), A2(N), the vectors to be compared. ! ! Output, logical ( kind = 4 ) R8VEC_LT, is TRUE if and only if A1 < A2. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer n real ( kind = rk ) a1(n) real ( kind = rk ) a2(n) logical ( kind = 4 ) r8vec_lt integer i r8vec_lt = .false. do i = 1, n if ( a1(i) < a2(i) ) then r8vec_lt = .true. exit else if ( a2(i) < a1(i) ) then r8vec_lt = .false. exit end if end do return end subroutine r8vec_print ( n, a, title ) !*****************************************************************************80 ! !! R8VEC_PRINT prints an R8VEC. ! ! Discussion: ! ! An R8VEC is a vector of R8's. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 22 August 2000 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer N, the number of components of the vector. ! ! Input, real ( kind = rk ) A(N), the vector to be printed. ! ! Input, character ( len = * ) TITLE, a title. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer n real ( kind = rk ) a(n) integer i character ( len = * ) title write ( *, '(a)' ) ' ' write ( *, '(a)' ) trim ( title ) write ( *, '(a)' ) ' ' do i = 1, n write ( *, '(2x,i8,a,1x,g16.8)' ) i, ':', a(i) end do return end subroutine r8vec_swap ( n, a1, a2 ) !*****************************************************************************80 ! !! R8VEC_SWAP swaps the entries of two R8VECs. ! ! Discussion: ! ! An R8VEC is a vector of R8's. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 04 December 2004 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer N, the number of entries in the arrays. ! ! Input/output, real ( kind = rk ) A1(N), A2(N), the vectors to swap. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer n real ( kind = rk ) a1(n) real ( kind = rk ) a2(n) real ( kind = rk ) a3(n) a3(1:n) = a1(1:n) a1(1:n) = a2(1:n) a2(1:n) = a3(1:n) return end subroutine sort_heap_external ( n, indx, i, j, isgn ) !*****************************************************************************80 ! !! SORT_HEAP_EXTERNAL externally sorts a list of items into ascending order. ! ! Discussion: ! ! The actual list of data is not passed to the routine. Hence this ! routine may be used to sort integers, reals, numbers, names, ! dates, shoe sizes, and so on. After each call, the routine asks ! the user to compare or interchange two items, until a special ! return value signals that the sorting is completed. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 05 February 2004 ! ! Author: ! ! Original FORTRAN77 version by Albert Nijenhuis, Herbert Wilf. ! FORTRAN90 version by John Burkardt. ! ! Reference: ! ! Albert Nijenhuis, Herbert Wilf, ! Combinatorial Algorithms for Computers and Calculators, ! Academic Press, 1978, ! ISBN: 0-12-519260-6, ! LC: QA164.N54. ! ! Parameters: ! ! Input, integer N, the number of items to be sorted. ! ! Input/output, integer INDX, the main communication signal. ! The user must set INDX to 0 before the first call. ! Thereafter, the user should not change the value of INDX until ! the sorting is done. ! On return, if INDX is ! * greater than 0, ! > interchange items I and J; ! > call again. ! * less than 0, ! > compare items I and J; ! > set ISGN = -1 if I < J, ISGN = +1 if J < I; ! > call again. ! * equal to 0, the sorting is done. ! ! Output, integer I, J, the indices of two items. ! On return with INDX positive, elements I and J should be interchanged. ! On return with INDX negative, elements I and J should be compared, and ! the result reported in ISGN on the next call. ! ! Input, integer ISGN, results of comparison of elements ! I and J. (Used only when the previous call returned INDX less than 0). ! ISGN <= 0 means I is less than or equal to J; ! 0 <= ISGN means I is greater than or equal to J. ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) integer i integer, save :: i_save = 0 integer indx integer isgn integer j integer, save :: j_save = 0 integer, save :: k = 0 integer, save :: k1 = 0 integer n integer, save :: n1 = 0 ! ! INDX = 0: This is the first call. ! if ( indx == 0 ) then i_save = 0 j_save = 0 k = n / 2 k1 = k n1 = n ! ! INDX < 0: The user is returning the results of a comparison. ! else if ( indx < 0 ) then if ( indx == -2 ) then if ( isgn < 0 ) then i_save = i_save + 1 end if j_save = k1 k1 = i_save indx = -1 i = i_save j = j_save return end if if ( 0 < isgn ) then indx = 2 i = i_save j = j_save return end if if ( k <= 1 ) then if ( n1 == 1 ) then i_save = 0 j_save = 0 indx = 0 else i_save = n1 n1 = n1 - 1 j_save = 1 indx = 1 end if i = i_save j = j_save return end if k = k - 1 k1 = k ! ! 0 < INDX, the user was asked to make an interchange. ! else if ( indx == 1 ) then k1 = k end if do i_save = 2 * k1 if ( i_save == n1 ) then j_save = k1 k1 = i_save indx = -1 i = i_save j = j_save return else if ( i_save <= n1 ) then j_save = i_save + 1 indx = -2 i = i_save j = j_save return end if if ( k <= 1 ) then exit end if k = k - 1 k1 = k end do if ( n1 == 1 ) then i_save = 0 j_save = 0 indx = 0 i = i_save j = j_save else i_save = n1 n1 = n1 - 1 j_save = 1 indx = 1 i = i_save j = j_save end if return end subroutine timestamp ( ) !*****************************************************************************80 ! !! TIMESTAMP prints the current YMDHMS date as a time stamp. ! ! Example: ! ! 31 May 2001 9:45:54.872 AM ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 18 May 2013 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! None ! implicit none integer, parameter :: rk = kind ( 1.0D+00 ) character ( len = 8 ) ampm integer d integer h integer m integer mm character ( len = 9 ), parameter, dimension(12) :: month = (/ & 'January ', 'February ', 'March ', 'April ', & 'May ', 'June ', 'July ', 'August ', & 'September', 'October ', 'November ', 'December ' /) integer n integer s integer values(8) integer y call date_and_time ( values = values ) y = values(1) m = values(2) d = values(3) h = values(5) n = values(6) s = values(7) mm = values(8) if ( h < 12 ) then ampm = 'AM' else if ( h == 12 ) then if ( n == 0 .and. s == 0 ) then ampm = 'Noon' else ampm = 'PM' end if else h = h - 12 if ( h < 12 ) then ampm = 'PM' else if ( h == 12 ) then if ( n == 0 .and. s == 0 ) then ampm = 'Midnight' else ampm = 'AM' end if end if end if write ( *, '(i2,1x,a,1x,i4,2x,i2,a1,i2.2,a1,i2.2,a1,i3.3,1x,a)' ) & d, trim ( month(m) ), y, h, ':', n, ':', s, '.', mm, trim ( ampm ) return end