program contour !*****************************************************************************80 ! !! MAIN is the main program for CONTOUR. ! ! Discussion: ! ! CONTOUR organizes data on a rectangular grid into finite element data. ! ! This version of the program has been revised to work with DISPLAY5 ! (which doesn't work yet!). The idea is to allow the user to specify ! any number of node quantities. Names of the quantities are included ! in the data file, transferred to DISPLAY5, and accessed by the user. ! ! This replaces the old concept of having a fixed number of items ! whose meaning never changes. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 23 June 2001 ! ! Author: ! ! John Burkardt ! implicit none character ( len = 80 ), parameter :: element_file_name = 'element.txt' integer i integer iarg integer iargc integer ierror integer ihi integer ilen integer ilo integer, allocatable, dimension ( : ) :: indx integer ios integer ipxfargc character ( len = 256 ) :: names integer nelem integer nelemx integer nelemy integer, allocatable, dimension ( :, : ) :: node character ( len = 80 ), parameter :: node_file_name = 'node.txt' integer np integer np2 integer npe integer nq integer num_arg integer nx integer ny real, allocatable, dimension (:,:) :: v character ( len = 80 ) :: v_file_name call timestamp ( ) write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'CONTOUR' write ( *, '(a)' ) ' FORTRAN90 version' write ( *, '(a)' ) ' Reads a simple data file, of the form' write ( *, '(a)' ) ' X, Y, V1(X,Y), V2(X,Y)...,' write ( *, '(a)' ) ' and constructs node and element data files' write ( *, '(a)' ) ' suitable for use with the DISPLAY graphics program.' write ( *, '(a)' ) ' ' write ( *, '(a)' ) ' Last modified on 22 June 2001.' ! ! Get the number of command line arguments. ! ! Old style: ! num_arg = iargc ( ) ! ! New style: ! ! num_arg = ipxfargc ( ) ! ! If at least one command line argument, it's the input file name. ! if ( num_arg < 1 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'Enter the input file name:' read ( *, '(a)', iostat = ios ) v_file_name if ( ios /= 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'CONTOUR - Fatal error!' write ( *, '(a)' ) ' Unexpected read error!' stop end if else iarg = 1 ! ! Old style: ! call getarg ( iarg, v_file_name ) ! ! New style: ! ! call pxfgetarg ( iarg, v_file_name, ilen, ierror ) ! ! if ( ierror /= 0 ) then ! write ( *, '(a)' ) ' ' ! write ( *, '(a)' ) 'CONTOUR - Fatal error!' ! write ( *, '(a)' ) ' Could not read command line argument.' ! stop ! end if end if ! ! Now we know what to do. ! write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'CONTOUR' write ( *, '(a)' ) ' Read input file: "' // trim ( v_file_name ) // '".' ! ! Estimate the value of NP by counting the lines in the file. ! call file_line_count ( v_file_name, np ) write ( *, '(a)' ) ' ' write ( *, '(a,i6)' ) ' The number of nodes in the properties file is ', np ! ! Estimate the value of NQ by counting the columns in the file. ! call file_column_count ( v_file_name, nq ) write ( *, '(a)' ) ' ' write ( *, '(a,i6)' ) ' The number of columns in the properties file is ', nq ! ! Set up the arrays. ! allocate ( indx(1:np) ) allocate ( v(1:np,1:nq) ) ! ! Set the names. ! do i = 1, nq ilo = 14*(i-1)+1 ihi = 14*i if ( i == 1 ) then write ( names(ilo:ihi), '(a1,13x)' ) 'X' else if ( i == 2 ) then write ( names(ilo:ihi), '(a1,13x)' ) 'Y' else write ( names(ilo:ihi), '(a1,i2.2,11x)' ) 'V', i-2 end if end do ! ! Read the data. ! call r4mat_read ( v_file_name, np, nq, v ) ! ! Determine a lexicographic ordering for X and Y. ! call r4vec2_sort_heap_index_a ( np, v(1:np,2), v(1:np,1), indx ) ! ! Reorder V. ! call r4mat_permute ( np, nq, v, indx ) ! ! Discard any duplicate data. ! call r4vec2_unique_index ( np, v(1:np,1), v(1:np,2), np2, indx ) v(1:np2,1:nq) = v(indx(1:np2),1:nq) write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'CONTOUR:' write ( *, '(a,i6)' ) ' Number of nodes NP = ', np2 write ( *, '(a,i6)' ) ' Duplicate nodes discarded: ', np - np2 np = np2 ! ! Assuming X, Y form a rectangular mesh, determine NELEMX and NELEMY. ! call grid_shape_2d ( np, v(1:np,2), ny, nx ) write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'CONTOUR' write ( *, '(a)' ) ' Estimate of grid shape NX by NY:' write ( *, '(a,i6)' ) ' NX = ', nx write ( *, '(a,i6)' ) ' NY = ', ny ! ! Construct the element data. ! if ( mod ( nx, 2 ) == 1 .and. mod ( ny, 2 ) == 1 ) then npe = 6 nelemx = ( nx - 1 ) / 2 nelemy = ( ny - 1 ) / 2 nelem = 2 * nelemx * nelemy else if ( .false. ) then npe = 4 nelemx = nx - 1 nelemy = ny - 1 nelem = nelemx * nelemy else npe = 3 nelemx = nx - 1 nelemy = ny - 1 nelem = 2 * nelemx * nelemy end if allocate ( node(1:npe,1:nelem) ) if ( mod ( nx, 2 ) == 1 .and. mod ( ny, 2 ) == 1 ) then call grid_t6 ( nelemx, nelemy, npe, nelem, node ) else if ( .false. ) then call grid_q4 ( nelemx, nelemy, npe, nelem, node ) else call grid_t3 ( nelemx, nelemy, npe, nelem, node ) end if write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'CONTOUR:' write ( *, '(a,i6)' ) ' Number of elements in X direction, NELEMX = ', nelemx write ( *, '(a,i6)' ) ' Number of elements in Y direction, NELEMY = ', nelemy write ( *, '(a,i6)' ) ' Number of nodes per elements is NPE = ', npe write ( *, '(a,i6)' ) ' Number of elements is NELEM = ', nelem ! ! Write the element information to a file. ! call write_element ( element_file_name, nelem, node, npe ) ! ! Write the node information to a file. ! call write_node ( node_file_name, np, nq, v(1:np,1:nq), names ) write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'CONTOUR' write ( *, '(a)' ) ' Normal end of execution.' stop end subroutine ch_cap ( c ) !*****************************************************************************80 ! !! CH_CAP capitalizes a single character. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 19 July 1998 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input/output, character C, the character to capitalize. ! implicit none character c integer itemp itemp = ichar ( c ) if ( 97 <= itemp .and. itemp <= 122 ) then c = char ( itemp - 32 ) end if return end function ch_eqi ( c1, c2 ) !*****************************************************************************80 ! !! CH_EQI is a case insensitive comparison of two characters for equality. ! ! Example: ! ! CH_EQI ( 'A', 'a' ) is .TRUE. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 28 July 2000 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, character C1, C2, the characters to compare. ! ! Output, logical CH_EQI, the result of the comparison. ! implicit none logical ch_eqi character c1 character c1_cap character c2 character c2_cap c1_cap = c1 c2_cap = c2 call ch_cap ( c1_cap ) call ch_cap ( c2_cap ) if ( c1_cap == c2_cap ) then ch_eqi = .true. else ch_eqi = .false. end if return end subroutine ch_to_digit ( c, digit ) !*****************************************************************************80 ! !! CH_TO_DIGIT returns the integer value of a base 10 digit. ! ! Example: ! ! C DIGIT ! --- ----- ! '0' 0 ! '1' 1 ! ... ... ! '9' 9 ! ' ' 0 ! 'X' -1 ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 04 August 1999 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, character C, the decimal digit, '0' through '9' or blank ! are legal. ! ! Output, integer DIGIT, the corresponding integer value. If C was ! 'illegal', then DIGIT is -1. ! implicit none character c integer digit if ( lge ( c, '0' ) .and. lle ( c, '9' ) ) then digit = ichar ( c ) - 48 else if ( c == ' ' ) then digit = 0 else digit = -1 end if return end subroutine file_column_count ( file_name, ncolumn ) !*****************************************************************************80 ! !! FILE_COLUMN_COUNT counts the number of columns in the first line of a file. ! ! Discussion: ! ! The file is assumed to be a simple text file. ! ! Most lines of the file is presumed to consist of NCOLUMN words, separated ! by spaces. There may also be some blank lines, and some comment lines, ! which have a "#" in column 1. ! ! The routine tries to find the first non-comment non-blank line and ! counts the number of words in that line. ! ! If all lines are blanks or comments, it goes back and tries to analyze ! a comment line. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 21 June 2001 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, character ( len = * ) FILE_NAME, the name of the file. ! ! Output, integer NCOLUMN, the number of columns assumed to be in the file. ! implicit none character ( len = * ) file_name logical got_one integer ios integer iunit character ( len = 256 ) line integer ncolumn ! ! Open the file. ! call get_unit ( iunit ) open ( unit = iunit, file = file_name, status = 'old', form = 'formatted', & access = 'sequential', iostat = ios ) if ( ios /= 0 ) then ncolumn = - 1 write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'FILE_COLUMN_COUNT - Fatal error!' write ( *, '(a)' ) ' Could not open the file:' write ( *, '(a)' ) ' ' // trim ( file_name ) return end if ! ! Read one line, but skip blank lines and comment lines. ! got_one = .false. do read ( iunit, '(a)', iostat = ios ) line if ( ios /= 0 ) then exit end if if ( len_trim ( line ) == 0 ) then cycle end if if ( line(1:1) == '#' ) then cycle end if got_one = .true. exit end do if ( .not. got_one ) then rewind ( iunit ) do read ( iunit, '(a)', iostat = ios ) line if ( ios /= 0 ) then exit end if if ( len_trim ( line ) == 0 ) then cycle end if got_one = .true. exit end do end if close ( unit = iunit ) if ( .not. got_one ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'FILE_COLUMN_COUNT - Warning!' write ( *, '(a)' ) ' The file does not seem to contain any data.' ncolumn = 0 return end if call word_count ( line, ncolumn ) return end subroutine file_line_count ( file_name, nline ) !*****************************************************************************80 ! !! FILE_LINE_COUNT counts the number of lines in a file. ! ! Discussion: ! ! The file is assumed to be a simple text file. ! ! Blank lines and comment lines, which begin with '#', are not counted. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 21 June 2001 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, character ( len = * ) FILE_NAME, the name of the file. ! ! Output, integer NLINE, the number of lines found in the file. ! implicit none character ( len = * ) file_name integer ios integer iunit character ( len = 256 ) line integer nline nline = 0 ! ! Open the file. ! call get_unit ( iunit ) open ( unit = iunit, file = file_name, status = 'old', form = 'formatted', & access = 'sequential', iostat = ios ) if ( ios /= 0 ) then nline = - 1 write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'FILE_LINE_COUNT - Fatal error!' write ( *, '(a)' ) ' Could not open the file:' // trim ( file_name ) return end if ! ! Count the lines. ! do read ( iunit, '(a)', iostat = ios ) line if ( ios /= 0 ) then exit end if if ( len_trim ( line ) == 0 ) then cycle end if if ( line(1:1) == '#' ) then cycle end if nline = nline + 1 end do close ( unit = iunit ) return end subroutine get_unit ( iunit ) !*****************************************************************************80 ! !! GET_UNIT returns a free FORTRAN unit number. ! ! Discussion: ! ! A "free" FORTRAN unit number is an integer between 1 and 99 which ! is not currently associated with an I/O device. A free FORTRAN unit ! number is needed in order to open a file with the OPEN command. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 02 March 1999 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Output, integer IUNIT. ! ! If IUNIT = 0, then no free FORTRAN unit could be found, although ! all 99 units were checked (except for units 5 and 6). ! ! Otherwise, IUNIT is an integer between 1 and 99, representing a ! free FORTRAN unit. Note that GET_UNIT assumes that units 5 and 6 ! are special, and will never return those values. ! implicit none integer i integer ios integer iunit logical lopen iunit = 0 do i = 1, 99 if ( i /= 5 .and. i /= 6 ) then inquire ( unit = i, opened = lopen, iostat = ios ) if ( ios == 0 ) then if ( .not. lopen ) then iunit = i return end if end if end if end do return end subroutine grid_q4 ( nelemx, nelemy, npe, nelem, nodes ) !*****************************************************************************80 ! !! GRID_Q4 produces a grid of 4 node quadrilaterals. ! ! Example: ! ! Input: ! ! NELEMX = 3, NELEMY = 2 ! ! Output: ! ! NODES = ! 1, 2, 5, 6; ! 2, 3, 6, 7; ! 3, 4, 7, 8; ! 5, 6, 9, 10; ! 6, 7, 10, 11; ! 7, 8, 11, 12. ! ! Diagram: ! ! 9---10---11---12 ! | | | | ! | | | | ! | 4 | 5 | 6 | ! | | | | ! 5----6----7----8 ! | | | | ! | | | | ! | 1 | 2 | 3 | ! | | | | ! 1----2----3----4 ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 22 June 2001 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer NELEMX, NELEMY, the number of quadrilaterals along the ! X and Y directions. The number of elements generated will be ! NELEMX * NELEMY. ! ! Input, integer NPE, the number of nodes per element. ! ! Input, integer NELEM, the number of elements. ! ! Output, integer NODES(NPE,NELEM); NODES(I,J) contains the index ! of the I-th node of the J-th element. ! implicit none integer nelem integer npe integer ielem integer i integer j integer nelemx integer nelemy integer nodes(npe,nelem) ielem = 0 do j = 1, nelemy do i = 1, nelemx ielem = ielem + 1 nodes(1,ielem) = ( j - 1 ) * ( nelemx + 1 ) + i nodes(2,ielem) = ( j - 1 ) * ( nelemx + 1 ) + i + 1 nodes(3,ielem) = j * ( nelemx + 1 ) + i nodes(4,ielem) = j * ( nelemx + 1 ) + i + 1 end do end do return end subroutine grid_shape_2d ( n, a, n1, n2 ) !*****************************************************************************80 ! !! GRID_SHAPE_2D guesses the shape N1 by N2 of a vector of data. ! ! Discussion: ! ! The data vector A is assumed to contain N1 * N2 values, with ! where each of N2 values is repeated N1 times. ! ! Example: ! ! Input: ! ! A = ( 2, 2, 2, 7, 7, 7 ) ! ! Output: ! ! N1 = 3, N2 = 2 ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 19 September 2000 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer N, the number of data values. ! ! Input, real A(N), the data, which should have the properties ! described above. ! ! Output, integer N1, N2, the "shape" of the data in the array. ! implicit none integer n real a(n) integer i integer n1 integer n2 real small small = 0.001E+00 * ( maxval ( a(1:n) ) - minval ( a(1:n) ) ) & / sqrt ( real ( n ) ) ! ! Make a guess for N2. ! i = 1 n2 = 1 do i = 2, n if ( abs ( a(i) - a(1) ) > small ) then exit end if n2 = n2 + 1 end do ! ! Guess that N1 = N / N2. ! n1 = n / n2 return end subroutine grid_t3 ( nelemx, nelemy, npe, nelem, nodes ) !*****************************************************************************80 ! !! GRID_T3 produces a grid of pairs of 3 node triangles. ! ! Example: ! ! Input: ! ! NELEMX = 3, NELEMY = 2 ! ! Output: ! ! NODES = ! 1, 2, 5; ! 6, 5, 2; ! 2, 3, 6; ! 7, 6, 3; ! 3, 4, 7; ! 8, 7, 4; ! 5, 6, 9; ! 10, 9, 6; ! 6, 7, 10; ! 11, 10, 7; ! 7, 8, 11; ! 12, 11, 8. ! ! Diagram: ! ! 9---10---11---12 ! |\ 8 |\10 |\12 | ! | \ | \ | \ | ! | \ | \ | \ | ! | 7\| 9\| 11\| ! 5----6----7----8 ! |\ 2 |\ 4 |\ 6 | ! | \ | \ | \ | ! | \ | \ | \ | ! | 1\| 3\| 5\| ! 1----2----3----4 ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 22 June 2001 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer NELEMX, NELEMY, the number of triangles along the ! X and Y directions. The number of elements generated will be ! 2 * NELEMX * NELEMY. ! ! Input, integer NPE, the number of nodes per element. ! ! Input, integer NELEM, the number of elements. ! ! Output, integer NODES(NPE,NELEM); NODES(I,J) contains the index ! of the I-th node of the J-th element. ! implicit none integer nelem integer npe integer ielem integer i integer j integer nelemx integer nelemy integer nodes(npe,nelem) ielem = 0 do j = 1, nelemy do i = 1, nelemx ielem = ielem + 1 nodes(1,ielem) = ( j - 1 ) * ( nelemx + 1 ) + i nodes(2,ielem) = ( j - 1 ) * ( nelemx + 1 ) + i + 1 nodes(3,ielem) = j * ( nelemx + 1 ) + i ielem = ielem + 1 nodes(1,ielem) = j * ( nelemx + 1 ) + i + 1 nodes(2,ielem) = j * ( nelemx + 1 ) + i nodes(3,ielem) = ( j - 1 ) * ( nelemx + 1 ) + i + 1 end do end do return end subroutine grid_t6 ( nelemx, nelemy, npe, nelem, nodes ) !*****************************************************************************80 ! !! GRID_T6 produces a grid of pairs of 6 node triangles. ! ! Example: ! ! Input: ! ! NELEMX = 3, NELEMY = 2 ! ! Output: ! ! 3, 15, 1, 2, 9, 8; ! 15, 3, 17, 16, 9, 10; ! 5, 17, 3 4, 11, 10; ! 17, 5, 19, 18, 11, 12; ! 7, 19, 5, 6, 13, 12; ! 19, 7, 21, 20, 13, 14; ! 17, 29, 15, 16, 23, 22; ! 29, 17, 31, 30, 23, 24; ! 19, 31, 17, 18, 25, 24; ! 31, 19, 33, 32, 25, 26; ! 21, 33, 19, 20, 27, 26; ! 33, 21, 35, 34, 27, 28. ! ! Diagram: ! ! 29-30-31-32-33-34-35 ! |\ 8 |\10 |\12 | ! | \ | \ | \ | ! 22 23 24 25 26 27 28 ! | \ | \ | \ | ! | 7 \| 9 \| 11 \| ! 15-16-17-18-19-20-21 ! |\ 2 |\ 4 |\ 6 | ! | \ | \ | \ | ! 8 9 10 11 12 13 14 ! | \ | \ | \ | ! | 1 \| 3 \| 5 \| ! 1--2--3--4--5--6--7 ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 22 June 2001 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer NELEMX, NELEMY, the number of triangles along the ! X and Y directions. The number of elements generated will be ! 2 * NELEMX * NELEMY. ! ! Input, integer NPE, the number of nodes per element. ! ! Input, integer NELEM, the number of elements. ! ! Output, integer NODES(NPE,NELEM); NODES(I,J) contains the index ! of the I-th node of the J-th element. ! implicit none integer nelem integer npe integer base integer ielem integer i integer j integer nelemx integer nelemy integer nodes(npe,nelem) ielem = 0 do j = 1, nelemy do i = 1, nelemx base = ( j - 1 ) * 2 * ( 2 * nelemx + 1 ) + 2 * i - 1 ielem = ielem + 1 nodes(1,ielem) = base + 2 nodes(2,ielem) = base + 2 * ( 2 * nelemx + 1 ) nodes(3,ielem) = base nodes(4,ielem) = base + 1 nodes(5,ielem) = base + ( 2 * nelemx + 1 ) + 1 nodes(6,ielem) = base + ( 2 * nelemx + 1 ) ielem = ielem + 1 nodes(1,ielem) = base + 2 * ( 2 * nelemx + 1 ) nodes(2,ielem) = base + 2 nodes(3,ielem) = base + 2 * ( 2 * nelemx + 1 ) + 2 nodes(4,ielem) = base + 2 * ( 2 * nelemx + 1 ) + 1 nodes(5,ielem) = base + ( 2 * nelemx + 1 ) + 1 nodes(6,ielem) = base + ( 2 * nelemx + 1 ) + 2 end do end do return end subroutine perm_check ( n, p, ierror ) !*****************************************************************************80 ! !! PERM_CHECK checks that a vector represents a permutation. ! ! Discussion: ! ! The routine verifies that each of the integers from 1 ! to N occurs among the N entries of the permutation. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 01 February 2001 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer N, the number of entries. ! ! Input, integer P(N), the array to check. ! ! Output, integer IERROR, error flag. ! 0, the array represents a permutation. ! nonzero, the array does not represent a permutation. The smallest ! missing value is equal to IERROR. ! implicit none integer n integer ierror integer ifind integer iseek integer p(n) ierror = 0 do iseek = 1, n ierror = iseek do ifind = 1, n if ( p(ifind) == iseek ) then ierror = 0 exit end if end do if ( ierror /= 0 ) then return end if end do return end subroutine r4_next ( s, r, done ) !*****************************************************************************80 ! !! R4_NEXT "reads" real numbers from a string, one at a time. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 14 April 1999 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, character ( len = * ) S, a string, presumably containing real ! numbers. These may be separated by spaces or commas. ! ! Output, real R. If DONE is FALSE, then R contains the ! "next" real value read from the string. If DONE is TRUE, then ! R is zero. ! ! Input/output, logical DONE. ! On input with a fresh string, the user should set DONE to TRUE. ! On output, the routine sets DONE to FALSE if another real ! value was read, or TRUE if no more reals could be read. ! implicit none logical done integer ierror integer lchar integer, save :: next = 1 real r character ( len = * ) s r = 0.0E+00 if ( done ) then next = 1 done = .false. end if if ( next > len ( s ) ) then done = .true. return end if call s_to_r4 ( s(next:), r, ierror, lchar ) if ( ierror /= 0 .or. lchar == 0 ) then done = .true. next = 1 else done = .false. next = next + lchar end if return end subroutine r4mat_permute ( np, nq, a, p ) !*****************************************************************************80 ! !! R4MAT_PERMUTE permutes a real matrix in place. ! ! Discussion: ! ! This routine permutes an array of real "objects", but the same ! logic can be used to permute an array of objects of any arithmetic ! type, or an array of objects of any complexity. The only temporary ! storage required is enough to store a single row. The number ! of data movements made is N + the number of cycles of order 2 or more, ! which is never more than N + N/2. ! ! Example: ! ! Input: ! ! NP = 5 ! NQ = 2 ! P = ( 2, 4, 5, 1, 3 ) ! A = ! 11.0, 12.0, ! 21.0, 22.0, ! 31.0, 32.0, ! 41.0, 42.0, ! 51.0, 52.0 ! ! Output: ! ! A = ! 21.0, 22.0, ! 41.0, 42.0, ! 51.0, 52.0, ! 11.0, 12.0, ! 31.0, 32.0 ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 22 June 2001 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer NP, NQ, the number of rows and columns in A. ! ! Input/output, real A(NP,NQ), the array to be permuted. ! ! Input, integer P(NP), the permutation. P(I) = J means ! that the I-th row of the output array should be the J-th ! row of the input array. P must be a legal permutation ! of the integers from 1 to N, otherwise the algorithm will ! fail catastrophically. ! implicit none integer np integer nq real a(np,nq) integer i integer ierror integer iget integer iput integer istart integer p(np) real spare_row(nq) call perm_check ( np, p, ierror ) if ( ierror /= 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'R4MAT_PERMUTE - Fatal error!' write ( *, '(a)' ) ' The input array does not represent' write ( *, '(a)' ) ' a proper permutation. In particular, the' write ( *, '(a,i6)' ) ' array is missing the value ', ierror stop end if ! ! Search for the next element of the permutation that has not been used. ! do istart = 1, np if ( p(istart) < 0 ) then cycle else if ( p(istart) == istart ) then p(istart) = - p(istart) cycle else spare_row(1:nq) = a(istart,1:nq) iget = istart ! ! Copy the new value into the vacated entry. ! do iput = iget iget = p(iget) p(iput) = - p(iput) if ( iget < 1 .or. iget > np ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'R4MAT_PERMUTE - Fatal error!' stop end if if ( iget == istart ) then a(iput,1:nq) = spare_row(1:nq) exit end if a(iput,1:nq) = a(iget,1:nq) end do end if end do ! ! Restore the signs of the entries. ! p(1:np) = - p(1:np) return end subroutine r4mat_print ( lda, m, n, a, title ) !*****************************************************************************80 ! !! R4MAT_PRINT prints a real matrix. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 24 March 2000 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer LDA, the leading dimension of A. ! ! Input, integer M, the number of rows in A. ! ! Input, integer N, the number of columns in A. ! ! Input, real A(LDA,N), the matrix to be printed. ! ! Input, character ( len = * ) TITLE, a title to be printed first. ! TITLE may be blank. ! implicit none integer lda integer n real a(lda,n) integer i integer j integer jhi integer jlo integer m character ( len = * ) title if ( title /= ' ' ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) trim ( title ) end if do jlo = 1, n, 5 jhi = min ( jlo + 4, n ) write ( *, '(a)' ) ' ' write ( *, '(6x,5(i7,7x))' ) ( j, j = jlo, jhi ) write ( *, '(a)' ) ' ' do i = 1, m write ( *, '(i6,5g14.6)' ) i, a(i,jlo:jhi) end do end do return end subroutine r4mat_read ( file_name, np, nq, v ) !*****************************************************************************80 ! !! R4MAT_READ reads a matrix of real data from a file. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 21 June 2001 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, character ( len = * ) FILE_NAME, the name of the file to read. ! ! Input, integer NP, NQ, the number of rows and columns of data to read. ! ! Output, real V(NP,NQ), the data values read from the file. ! implicit none integer np integer nq logical done character ( len = * ) file_name integer i integer ios integer iunit integer j character ( len = 256 ) line real v(np,nq) call get_unit ( iunit ) open ( unit = iunit, file = file_name, status = 'old', iostat = ios ) if ( ios /= 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'R4MAT_READ - Fatal error!' write ( *, '(a)' ) ' Could not open the file ' // trim ( file_name ) stop end if i = 0 do if ( i + 1 > np ) then exit end if i = i + 1 do read ( iunit, '(a)', iostat = ios ) line if ( ios /= 0 ) then exit end if if ( len_trim ( line ) == 0 ) then cycle end if if ( line(1:1) == '#' ) then cycle end if done = .true. do j = 1, nq call r4_next ( line, v(i,j), done ) end do exit end do if ( ios /= 0 ) then exit end if end do close ( unit = iunit ) return end subroutine r4vec2_sort_heap_index_a ( n, x, y, indx ) !*****************************************************************************80 ! !! R4VEC2_SORT_HEAP_INDEX_A does an indexed heap ascending sort of a set of (X,Y) data. ! ! Discussion: ! ! 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. ! ! ( X(I), Y(I) ) < ( X(J), Y(J) ) if: ! ! * X(I) < X(J), or ! ! * X(I) = X(J), and Y(I) < Y(J). ! ! Once the index array is computed, the sorting can be carried out ! "implicitly: ! ! ( X(INDX(I)), Y(INDX(I) ), for I = 1 to N is sorted, ! ! or explicitly, by the call ! ! call R4VEC_PERMUTE ( N, X, INDX ) ! call R4VEC_PERMUTE ( N, Y, INDX ) ! ! after which ( X(I), Y(I) ), I = 1 to N is sorted. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 21 July 2000 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer N, the number of entries in the array. ! ! Input, real X(N),Y(N), pairs of X, Y coordinates of points. ! ! Output, integer INDX(N), contains the sort index. The ! I-th element of the sorted array has coordinates ( X(INDX(I)), Y(INDX(I) ). ! implicit none integer n integer i integer indx(n) integer indxt integer ir integer j integer l real x(n) real xval real y(n) real yval do i = 1, n indx(i) = i end do l = n / 2 + 1 ir = n do if ( l > 1 ) then l = l - 1 indxt = indx(l) xval = x(indxt) yval = y(indxt) else indxt = indx(ir) xval = x(indxt) yval = y(indxt) 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 if ( x(indx(j)) < x(indx(j+1)) .or. & ( x(indx(j)) == x(indx(j+1)) .and. y(indx(j)) < y(indx(j+1)) ) ) then j = j + 1 end if end if if ( xval < x(indx(j)) .or. & ( xval == x(indx(j)) .and. yval < y(indx(j)) ) ) 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 r4vec2_unique_index ( n, a1, a2, nuniq, indx ) !*****************************************************************************80 ! !! R4VEC2_UNIQUE_INDEX indexes unique elements in a sorted array of pairs of reals. ! ! Discussion: ! ! Item I is stored as the pair A1(I), A2(I). ! ! The items must have been sorted, or at least it should be the ! case that equal items are stored in adjacent vector locations. ! ! If the items are not sorted, then this routine will only ! replace a string of equal values by a single representative. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 21 June 2001 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer N, the number of items. ! ! Input/output, real A1(N), A2(N). ! On input, the array of N items. ! On output, an array of NUNIQ unique items. ! ! Output, integer NUNIQ, the number of unique items. ! ! Output, integer INDX(N), contains in entries 1 through NUNIQ an index ! array of the unique items. To build new arrays with no repeated elements: ! B1(1:NUNIQ) = A1(INDX(1:NUNIQ)) ! implicit none integer n real a1(n) real a2(n) integer indx(n) integer itest integer nuniq nuniq = 0 if ( n <= 0 ) then return end if nuniq = 1 indx(1) = 1 do itest = 2, n if ( a1(itest-1) /= a1(itest) .or. a2(itest-1) /= a2(itest) ) then nuniq = nuniq + 1 indx(nuniq) = itest end if end do indx(nuniq+1:n) = 0 return end subroutine r4vec_read ( file_name, np, a ) !*****************************************************************************80 ! !! R4VEC_READ reads a vector of real data from a file. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 21 June 2001 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, character ( len = * ) FILE_NAME, the name of the file to read. ! ! Input, integer NP, the number of data values to read. ! ! Output, real A(NP), the data values read from the file. ! implicit none integer np real a(np) character ( len = * ) file_name integer i integer ios integer iunit call get_unit ( iunit ) open ( unit = iunit, file = file_name, status = 'old', iostat = ios ) if ( ios /= 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'R4VEC_READ - Fatal error!' write ( *, '(a)' ) ' Could not open the file ' // trim ( file_name ) stop end if i = 0 do if ( i + 1 > np ) then exit end if i = i + 1 read ( iunit, *, iostat = ios ) a(i) if ( ios /= 0 ) then exit end if end do close ( unit = iunit ) return end subroutine s_to_r4 ( s, r, ierror, lchar ) !*****************************************************************************80 ! !! S_TO_R4 reads a real number from a string. ! ! Discussion: ! ! This routine will read as many characters as possible until it reaches ! the end of the string, or encounters a character which cannot be ! part of the real number. ! ! Legal input is: ! ! 1 blanks, ! 2 '+' or '-' sign, ! 2.5 spaces ! 3 integer part, ! 4 decimal point, ! 5 fraction part, ! 6 'E' or 'e' or 'D' or 'd', exponent marker, ! 7 exponent sign, ! 8 exponent integer part, ! 9 exponent decimal point, ! 10 exponent fraction part, ! 11 blanks, ! 12 final comma or semicolon. ! ! with most quantities optional. ! ! Example: ! ! S R ! ! '1' 1.0 ! ' 1 ' 1.0 ! '1A' 1.0 ! '12,34,56' 12.0 ! ' 34 7' 34.0 ! '-1E2ABCD' -100.0 ! '-1X2ABCD' -1.0 ! ' 2E-1' 0.2 ! '23.45' 23.45 ! '-4.2E+2' -420.0 ! '17d2' 1700.0 ! '-14e-2' -0.14 ! 'e2' 100.0 ! '-12.73e-9.23' -12.73 * 10.0**(-9.23) ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 12 February 2001 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, character ( len = * ) S, the string containing the ! data to be read. Reading will begin at position 1 and ! terminate at the end of the string, or when no more ! characters can be read to form a legal real. Blanks, ! commas, or other nonnumeric data will, in particular, ! cause the conversion to halt. ! ! Output, real R, the real value that was read from the string. ! ! Output, integer IERROR, error flag. ! ! 0, no errors occurred. ! ! 1, 2, 6 or 7, the input number was garbled. The ! value of IERROR is the last type of input successfully ! read. For instance, 1 means initial blanks, 2 means ! a plus or minus sign, and so on. ! ! Output, integer LCHAR, the number of characters read from ! the string to form the number, including any terminating ! characters such as a trailing comma or blanks. ! implicit none logical ch_eqi character c integer ierror integer ihave integer isgn integer iterm integer jbot integer jsgn integer jtop integer lchar integer nchar integer ndig real r real rbot real rexp real rtop character ( len = * ) s character, parameter :: TAB = char ( 9 ) nchar = len_trim ( s ) ierror = 0 r = 0.0E+00 lchar = - 1 isgn = 1 rtop = 0.0E+00 rbot = 1.0E+00 jsgn = 1 jtop = 0 jbot = 1 ihave = 1 iterm = 0 do lchar = lchar + 1 c = s(lchar+1:lchar+1) ! ! Blank or TAB character. ! if ( c == ' ' .or. c == TAB ) then if ( ihave == 2 ) then else if ( ihave == 6 .or. ihave == 7 ) then iterm = 1 else if ( ihave > 1 ) then ihave = 11 end if ! ! Comma. ! else if ( c == ',' .or. c == ';' ) then if ( ihave /= 1 ) then iterm = 1 ihave = 12 lchar = lchar + 1 end if ! ! Minus sign. ! else if ( c == '-' ) then if ( ihave == 1 ) then ihave = 2 isgn = - 1 else if ( ihave == 6 ) then ihave = 7 jsgn = - 1 else iterm = 1 end if ! ! Plus sign. ! else if ( c == '+' ) then if ( ihave == 1 ) then ihave = 2 else if ( ihave == 6 ) then ihave = 7 else iterm = 1 end if ! ! Decimal point. ! else if ( c == '.' ) then if ( ihave < 4 ) then ihave = 4 else if ( ihave >= 6 .and. ihave <= 8 ) then ihave = 9 else iterm = 1 end if ! ! Exponent marker. ! else if ( ch_eqi ( c, 'E' ) .or. ch_eqi ( c, 'D' ) ) then if ( ihave < 6 ) then ihave = 6 else iterm = 1 end if ! ! Digit. ! else if ( ihave < 11 .and. lge ( c, '0' ) .and. lle ( c, '9' ) ) then if ( ihave <= 2 ) then ihave = 3 else if ( ihave == 4 ) then ihave = 5 else if ( ihave == 6 .or. ihave == 7 ) then ihave = 8 else if ( ihave == 9 ) then ihave = 10 end if call ch_to_digit ( c, ndig ) if ( ihave == 3 ) then rtop = 10.0E+00 * rtop + real ( ndig ) else if ( ihave == 5 ) then rtop = 10.0E+00 * rtop + real ( ndig ) rbot = 10.0E+00 * rbot else if ( ihave == 8 ) then jtop = 10 * jtop + ndig else if ( ihave == 10 ) then jtop = 10 * jtop + ndig jbot = 10 * jbot end if ! ! Anything else is regarded as a terminator. ! else iterm = 1 end if ! ! If we haven't seen a terminator, and we haven't examined the ! entire string, go get the next character. ! if ( iterm == 1 .or. lchar+1 >= nchar ) then exit end if end do ! ! If we haven't seen a terminator, and we have examined the ! entire string, then we're done, and LCHAR is equal to NCHAR. ! if ( iterm /= 1 .and. lchar+1 == nchar ) then lchar = nchar end if ! ! Number seems to have terminated. Have we got a legal number? ! Not if we terminated in states 1, 2, 6 or 7! ! if ( ihave == 1 .or. ihave == 2 .or. ihave == 6 .or. ihave == 7 ) then ierror = ihave return end if ! ! Number seems OK. Form it. ! if ( jtop == 0 ) then rexp = 1.0E+00 else if ( jbot == 1 ) then rexp = 10.0E+00**( jsgn * jtop ) else rexp = jsgn * jtop rexp = rexp / jbot rexp = 10.0E+00**rexp end if end if r = isgn * rexp * rtop / rbot return end subroutine timestamp ( ) !*****************************************************************************80 ! !! TIMESTAMP prints the current YMDHMS date as a time stamp. ! ! Example: ! ! May 31 2001 9:45:54.872 AM ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 31 May 2001 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! None ! implicit none character ( len = 8 ) ampm integer d character ( len = 8 ) date 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 character ( len = 10 ) time integer values(8) integer y character ( len = 5 ) zone call date_and_time ( date, time, zone, 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 ( *, '(a,1x,i2,1x,i4,2x,i2,a1,i2.2,a1,i2.2,a1,i3.3,1x,a)' ) & trim ( month(m) ), d, y, h, ':', n, ':', s, '.', mm, trim ( ampm ) return end subroutine word_count ( s, nword ) !*****************************************************************************80 ! !! WORD_COUNT counts the number of "words" in a string. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 14 April 1999 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, character ( len = * ) S, the string to be examined. ! ! Output, integer NWORD, the number of "words" in the string. ! Words are presumed to be separated by one or more blanks. ! implicit none logical blank integer i integer lens integer nword character ( len = * ) s nword = 0 lens = len ( s ) if ( lens <= 0 ) then return end if blank = .true. do i = 1, lens if ( s(i:i) == ' ' ) then blank = .true. else if ( blank ) then nword = nword + 1 blank = .false. end if end do return end subroutine write_element ( element_file, nelem, node, npe ) !*****************************************************************************80 ! !! WRITE_ELEMENT writes an element data file. ! ! Discussion: ! ! The element file contains information about the organization of ! the nodes into elements. The format is as follows: ! ! Line 1: NELEM, the number of elements ! Line 2: NPE, the number of nodes per element. ! Line 3 through NELEM+2: the node list for each element. ! ! Blank lines, and comments lines, which begin with a "#", may ! occur anywhere. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 22 June 2001 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, character ( len = * ) ELEMENT_FILE, the name of the element file. ! ! Input, integer NELEM, the number of elements. ! ! Input, integer NODE(NPE,NELEM), the global node numbers in each element. ! ! Input, integer NPE, the number of nodes per element. ! implicit none integer nelem integer npe character ( len = * ) element_file integer ielem integer ierror integer ios integer node(npe,nelem) integer output_unit ierror = 0 call get_unit ( output_unit ) ! ! Open the data file. ! open ( unit = output_unit, file = element_file, status = 'replace', & iostat = ios ) if ( ios /= 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'WRITE_ELEMENT - Fatal error!' write ( *, '(a)' ) ' Could not open the element file: ' & // trim ( element_file ) return end if ! ! Header. ! write ( output_unit, '(a)' ) '# ' // trim ( element_file ) write ( output_unit, '(a)' ) '# created by routine WRITE_ELEMENT,' write ( output_unit, '(a)' ) '# program CONTOUR, for input to DISPLAY.' write ( output_unit, '(a)' ) '#' write ( output_unit, '(a)' ) '# Line 1 is number of elements.' write ( output_unit, '(a)' ) '# Line 2 is number of nodes per element.' write ( output_unit, '(a)' ) '# Subsequent lines are node lists for elements.' write ( output_unit, '(a)' ) '#' ! ! Number of elements. ! write ( output_unit, '(i6)' ) nelem ! ! Number of nodes per element. ! write ( output_unit, '(i6)' ) npe ! ! Node numbers associated with each element. ! do ielem = 1, nelem write ( output_unit, '(6i6)' ) node(1:npe,ielem) end do close ( unit = output_unit ) write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'WRITE_ELEMENT:' write ( *, '(a)' ) ' The element data was written to the file: ' // & trim ( element_file ) return end subroutine write_node ( node_file, np, nq, v, names ) !*****************************************************************************80 ! !! WRITE_NODE writes a node data file. ! ! Discussion: ! ! The node file contains the value of various quantities at the nodes. ! The format is: ! ! Line 1: NP, the number of nodes ! Line 2: NQ, the number of values per node, (X, Y and the quantities). ! Line 3: NAMES, the names of X, Y, and the quantities ! Lines 4 through NP+3: X, Y, and the quantities for each node. ! ! Blanks and comment lines, which have a "#" in column 1, may occur anywhere. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 22 June 2001 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, character ( len = * ) NODE_FILE, the node file. ! ! Input, integer NP, the number of nodes. ! ! Input, integer NQ, the number of quantities (including X and Y). ! ! Input, real V(NP,NQ), X, Y, and various quantities associated with ! the nodes. ! ! Input, character ( len = 14 * NQ ) NAMES, names for the quantities. ! implicit none integer np integer nq integer i integer ios character ( len = * ) names character ( len = * ) node_file integer output_unit real v(np,nq) call get_unit ( output_unit ) open ( unit = output_unit, file = node_file, status = 'replace', & iostat = ios ) if ( ios /= 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'WRITE_NODE - Fatal error!' write ( *, '(a)' ) ' Could not open the node data file:' & // trim ( node_file ) return end if write ( output_unit, '(a)' ) '# ' // trim ( node_file ) write ( output_unit, '(a)' ) '# created by routine WRITE_NODE,' write ( output_unit, '(a)' ) '# program CONTOUR, for input to DISPLAY.' write ( output_unit, '(a)' ) '#' write ( output_unit, '(a)' ) '# Line 1 is number of nodes.' write ( output_unit, '(a)' ) '# Line 2 is number of properties per node.' write ( output_unit, '(a)' ) '# Line 3 is property names.' write ( output_unit, '(a)' ) '# Subsequent lines are X, Y and properties for each node.' write ( output_unit, '(a)' ) '#' write ( output_unit, '(i6)' ) np write ( output_unit, '(i6)' ) nq write ( output_unit, '(5x,a)' ) names(1:14*nq) do i = 1, np write ( output_unit, '(12g14.6)' ) v(i,1:nq) end do close ( unit = output_unit ) write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'WRITE_NODE:' write ( *, '(a)' ) ' The node data was written to the file: ' & // trim ( node_file ) return end