program main !*****************************************************************************80 ! !! MAIN is the main program for TEC_TO_UCD. ! ! Discussion: ! ! TEC_TO_UCD copies information from a TECPLOT ASCII file to a UCD file. ! ! A TECPLOT ASCII file contains information to be processed and displayed ! by the TECPLOT graphics program. ! ! A UCD file is an AVS "Unstructured Cell Data" format. ! ! This program can read a TECPLOT ASCII file and write an equivalent UCD ! file, assuming that the TECPLOT file is of the special format used ! for finite element data. This should be OK as long as the third ! line of the TECPLOT file looks something like ! ! ZONE N = ###, E = ###, DATAPACKING = POINT, ZONETYPE = FETRIANGLE ! ! The "ZONETYPE" argument could also be 'FEQUADRILATERAL', or ! 'FETETRATHEDRON' or 'FEBRICK'. ! ! Usage: ! ! tec_to_ucd file.dat file.ucd ! ! reads the information in "file.dat", and writes an ! equivalent copy into "file.ucd". ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 20 February 2006 ! ! Author: ! ! John Burkardt ! ! Parameters: ! implicit none integer arg_num logical, parameter :: debug = .true. integer dim_num integer, allocatable, dimension ( :, : ) :: element_node integer element_num integer element_order integer iarg integer iargc real ( kind = 8 ), allocatable, dimension ( :, : ) :: node_coord real ( kind = 8 ), allocatable, dimension ( :, : ) :: node_data integer node_data_num integer node_num character ( len = 255 ) tec_file_name integer tec_file_unit character ( len = 255 ) title character ( len = 255 ) ucd_file_name integer ucd_file_unit character ( len = 255 ) variables character ( len = 255 ) zone call timestamp ( ) write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'TEC_TO_UCD' write ( *, '(a)' ) ' FORTRAN90 version:' write ( *, '(a)' ) ' Read finite element information in a TEC file.' write ( *, '(a)' ) ' Write the equivalent information to a UCD file.' ! ! Get the number of command line arguments. ! arg_num = iargc ( ) ! ! If at least one command line argument, it's the TEC name. ! if ( 1 <= arg_num ) then iarg = 1 call getarg ( iarg, tec_file_name ) else write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'TEC_TO_UCD:' write ( *, '(a)' ) ' Please enter the name of the TECPLOT ASCII file.' read ( *, '(a)' ) tec_file_name end if ! ! If at least two command line arguments, the second is the UCD file. ! if ( 2 <= arg_num ) then iarg = 2 call getarg ( iarg, ucd_file_name ) else write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'TEC_TO_UCD:' write ( *, '(a)' ) ' Please enter the name of the UCD file.' read ( *, '(a)' ) ucd_file_name end if ! ! Read the data from the TECPLOT ASCII file. ! write ( *, '(a)' ) ' ' write ( *, '(a)' ) ' Reading "' // trim ( tec_file_name ) // '".' ! ! Open the file. ! call get_unit ( tec_file_unit ) open ( unit = tec_file_unit, file = tec_file_name, status = 'old' ) ! ! Read the header, which tells us how big things are. ! call tec_header_read ( tec_file_name, tec_file_unit, dim_num, node_num, & element_num, element_order, node_data_num ) call tec_header_print ( dim_num, node_num, element_num, & element_order, node_data_num ) ! ! Allocate space for the data, and read the data. ! allocate ( node_coord(1:dim_num,1:node_num) ) allocate ( node_data(1:node_data_num,1:node_num) ) allocate ( element_node(1:element_order,1:element_num) ) call tec_data_read ( tec_file_name, tec_file_unit, dim_num, & node_num, element_num, element_order, node_data_num, node_coord, & element_node, node_data ) close ( unit = tec_file_unit ) write ( *, '(a)' ) ' ' write ( *, '(a)' ) ' The data has been read from "' & // trim ( tec_file_name ) // '"' ! ! Write the data to the UCD file. ! write ( *, '(a)' ) ' ' write ( *, '(a)' ) ' Writing "' // trim ( ucd_file_name ) // '".' call get_unit ( ucd_file_unit ) open ( unit = ucd_file_unit, file = ucd_file_name, status = 'replace' ) call ucd_write ( node_num, dim_num, node_data_num, element_num, & element_order, node_coord, node_data, element_node, & ucd_file_unit, ucd_file_name ) close ( unit = ucd_file_unit ) write ( *, '(a)' ) ' ' write ( *, '(a)' ) ' The data has been written to "' & // trim ( ucd_file_name ) // '".' ! ! Free memory. ! deallocate ( node_coord ) deallocate ( node_data ) deallocate ( element_node ) ! ! Terminate. ! write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'TEC_TO_UCD:' write ( *, '(a)' ) ' Normal end of execution.' write ( *, '(a)' ) ' ' call timestamp ( ) 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 character c1 character c1_cap character c2 character c2_cap logical ch_eqi 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 file_name_inc ( file_name ) !*****************************************************************************80 ! !! FILE_NAME_INC increments a partially numeric filename. ! ! Discussion: ! ! It is assumed that the digits in the name, whether scattered or ! connected, represent a number that is to be increased by 1 on ! each call. If this number is all 9's on input, the output number ! is all 0's. Non-numeric letters of the name are unaffected. ! ! If the name is empty, then the routine stops. ! ! If the name contains no digits, the empty string is returned. ! ! Example: ! ! Input Output ! ----- ------ ! 'a7to11.txt' 'a7to12.txt' ! 'a7to99.txt' 'a8to00.txt' ! 'a9to99.txt' 'a0to00.txt' ! 'cat.txt' ' ' ! ' ' STOP! ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 14 September 2005 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input/output, character ( len = * ) FILE_NAME. ! On input, a character string to be incremented. ! On output, the incremented string. ! implicit none character c integer change integer digit character ( len = * ) file_name integer i integer lens lens = len_trim ( file_name ) if ( lens <= 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'FILE_NAME_INC - Fatal error!' write ( *, '(a)' ) ' The input string is empty.' stop end if change = 0 do i = lens, 1, -1 c = file_name(i:i) if ( lge ( c, '0' ) .and. lle ( c, '9' ) ) then change = change + 1 digit = ichar ( c ) - 48 digit = digit + 1 if ( digit == 10 ) then digit = 0 end if c = char ( digit + 48 ) file_name(i:i) = c if ( c /= '0' ) then return end if end if end do if ( change == 0 ) then file_name = ' ' return end if 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. ! ! If IUNIT = 0, then no free FORTRAN unit could be found, although ! all 99 units were checked (except for units 5, 6 and 9, which ! are commonly reserved for console I/O). ! ! 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. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 18 September 2005 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Output, integer IUNIT, the free unit number. ! implicit none integer i integer ios integer iunit logical lopen iunit = 0 do i = 1, 99 if ( i /= 5 .and. i /= 6 .and. i /= 9 ) 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 function s_begin ( s1, s2 ) !*****************************************************************************80 ! !! S_BEGIN is TRUE if one string matches the beginning of the other. ! ! Discussion: ! ! The strings are compared, ignoring blanks, spaces and capitalization. ! ! Example: ! ! S1 S2 S_BEGIN ! ! 'Bob' 'BOB' TRUE ! ' B o b ' ' bo b' TRUE ! 'Bob' 'Bobby' TRUE ! 'Bobo' 'Bobb' FALSE ! ' ' 'Bob' FALSE (Do not allow a blank to match ! anything but another blank string.) ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 20 January 2000 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, character ( len = * ) S1, S2, the strings to be compared. ! ! Output, logical S_BEGIN, is TRUE if the strings match up to ! the end of the shorter string, ignoring case. ! implicit none logical ch_eqi integer i1 integer i2 integer len1 integer len2 logical s_begin character ( len = * ) s1 character ( len = * ) s2 len1 = len_trim ( s1 ) len2 = len_trim ( s2 ) ! ! If either string is blank, then both must be blank to match. ! Otherwise, a blank string matches anything, which is not ! what most people want. ! if ( len1 == 0 .or. len2 == 0 ) then if ( len1 == 0 .and. len2 == 0 ) then s_begin = .true. else s_begin = .false. end if return end if i1 = 0 i2 = 0 ! ! Find the next nonblank in S1. ! do do i1 = i1 + 1 if ( len1 < i1 ) then s_begin = .true. return end if if ( s1(i1:i1) /= ' ' ) then exit end if end do ! ! Find the next nonblank in S2. ! do i2 = i2 + 1 if ( len2 < i2 ) then s_begin = .true. return end if if ( s2(i2:i2) /= ' ' ) then exit end if end do ! ! If the characters match, get the next pair. ! if ( .not. ch_eqi ( s1(i1:i1), s2(i2:i2) ) ) then exit end if end do s_begin = .false. return end subroutine s_behead_substring ( s, sub ) !*****************************************************************************80 ! !! S_BEHEAD_SUBSTRING "beheads" a string, removing a given substring. ! ! Discussion: ! ! Initial blanks in the string are removed first. ! ! Then, if the initial part of the string matches the substring, ! that part is removed and the remainder shifted left. ! ! Initial blanks in the substring are NOT ignored. ! ! Capitalization is ignored. ! ! If the substring is equal to the string, then the resultant ! string is returned as a single blank. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 30 January 2006 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input/output, character ( len = * ) S, the string to be transformed. ! ! Input, character ( len = * ) SUB, the substring to be removed from ! the beginning of the string. ! implicit none character ( len = * ) s logical s_eqi integer s_len character ( len = * ) sub integer sub_len ! ! Remove leading blanks from the string. ! s = adjustl ( s ) ! ! Get lengths. ! s_len = len_trim ( s ) sub_len = len_trim ( sub ) if ( s_len < sub_len ) then return end if ! ! If the string begins with the substring, chop it off. ! if ( s_eqi ( s(1:sub_len), sub(1:sub_len) ) ) then if ( sub_len < s_len ) then s = s(sub_len+1:s_len) s = adjustl ( s ) else s = ' ' end if end if return end function s_eqi ( s1, s2 ) !*****************************************************************************80 ! !! S_EQI is a case insensitive comparison of two strings for equality. ! ! Example: ! ! S_EQI ( 'Anjana', 'ANJANA' ) is TRUE. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 14 April 1999 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, character ( len = * ) S1, S2, the strings to compare. ! ! Output, logical S_EQI, the result of the comparison. ! implicit none character c1 character c2 integer i integer len1 integer len2 integer lenc logical s_eqi character ( len = * ) s1 character ( len = * ) s2 len1 = len ( s1 ) len2 = len ( s2 ) lenc = min ( len1, len2 ) s_eqi = .false. do i = 1, lenc c1 = s1(i:i) c2 = s2(i:i) call ch_cap ( c1 ) call ch_cap ( c2 ) if ( c1 /= c2 ) then return end if end do do i = lenc + 1, len1 if ( s1(i:i) /= ' ' ) then return end if end do do i = lenc + 1, len2 if ( s2(i:i) /= ' ' ) then return end if end do s_eqi = .true. return end subroutine s_replace_ch ( s, c1, c2 ) !*****************************************************************************80 ! !! S_REPLACE_CH replaces all occurrences of one character by another. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 27 March 2002 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input/output, character ( len = * ) S, the string. ! ! Input, character C1, C2, the character to be replaced, and the ! replacement character. ! implicit none character c1 character c2 integer i character ( len = * ) s do i = 1, len ( s ) if ( s(i:i) == c1 ) then s(i:i) = c2 end if end do return end subroutine s_to_i4 ( s, value, ierror, length ) !*****************************************************************************80 ! !! S_TO_I4 reads an I4 from a string. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 13 January 2006 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, character ( len = * ) S, a string to be examined. ! ! Output, integer VALUE, the integer value read from the string. ! If the string is blank, then VALUE will be returned 0. ! ! Output, integer IERROR, an error flag. ! 0, no error. ! 1, an error occurred. ! ! Output, integer LENGTH, the number of characters of S used to make ! the integer. ! implicit none character c integer i integer ierror integer isgn integer length character ( len = * ) s integer state integer value value = 0 ierror = 0 length = 0 state = 0 isgn = 1 do i = 1, len_trim ( s ) c = s(i:i) ! ! STATE = 0, haven't read anything. ! if ( state == 0 ) then if ( c == ' ' ) then else if ( c == '-' ) then state = 1 isgn = -1 else if ( c == '+' ) then state = 1 isgn = +1 else if ( lle ( '0', c ) .and. lle ( c, '9' ) ) then state = 2 value = ichar ( c ) - ichar ( '0' ) else ierror = 1 return end if ! ! STATE = 1, have read the sign, expecting digits or spaces. ! else if ( state == 1 ) then if ( c == ' ' ) then else if ( lle ( '0', c ) .and. lle ( c, '9' ) ) then state = 2 value = ichar ( c ) - ichar ( '0' ) else ierror = 1 return end if ! ! STATE = 2, have read at least one digit, expecting more. ! else if ( state == 2 ) then if ( lle ( '0', c ) .and. lle ( c, '9' ) ) then value = 10 * value + ichar ( c ) - ichar ( '0' ) else value = isgn * value ierror = 0 length = i - 1 return end if end if end do ! ! If we read all the characters in the string, see if we're OK. ! if ( state == 2 ) then value = isgn * value ierror = 0 length = len_trim ( s ) else value = 0 ierror = 1 length = 0 end if return end subroutine s_word_count ( s, word_num ) !*****************************************************************************80 ! !! S_WORD_COUNT counts the number of "words" in a string. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 05 October 2003 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, character ( len = * ) S, the string to be examined. ! ! Output, integer WORD_NUM, the number of "words" in the string. ! Words are presumed to be separated by one or more blanks. ! implicit none logical blank integer i character ( len = * ) s integer s_len integer word_num word_num = 0 s_len = len ( s ) if ( s_len <= 0 ) then return end if blank = .true. do i = 1, s_len if ( s(i:i) == ' ' ) then blank = .true. else if ( blank ) then word_num = word_num + 1 blank = .false. end if end do return end subroutine s_word_extract ( s, w ) !*****************************************************************************80 ! !! S_WORD_EXTRACT extracts the next word from a string. ! ! Discussion: ! ! A "word" is a string of characters terminated by a blank or ! the end of the string. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 31 January 2006 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input/output, character ( len = * ) S, the string. On output, the first ! word has been removed, and the remaining string has been shifted left. ! ! Output, character ( len = * ) W, the leading word of the string. ! implicit none integer get1 integer get2 character ( len = * ) s integer s_len character ( len = * ) w w = ' ' s_len = len_trim ( s ) if ( s_len < 1 ) then return end if ! ! Find the first nonblank. ! get1 = 0 do get1 = get1 + 1 if ( s_len < get1 ) then return end if if ( s(get1:get1) /= ' ' ) then exit end if end do ! ! Look for the last contiguous nonblank. ! get2 = get1 do if ( s_len <= get2 ) then exit end if if ( s(get2+1:get2+1) == ' ' ) then exit end if get2 = get2 + 1 end do ! ! Copy the word. ! w = s(get1:get2) ! ! Shift the string. ! s(1:get2) = ' ' s = adjustl ( s(get2+1:) ) return end subroutine tec_data_read ( tec_file_name, tec_file_unit, dim_num, & node_num, element_num, element_order, node_data_num, node_coord, & element_node, node_data ) !*****************************************************************************80 ! !! TEC_DATA_READ reads the data from a TEC file. ! ! Discussion: ! ! This routine assumes that the TEC file has already been opened, ! and that the optional TITLE record, VARIABLES record and ZONE ! record have been read, so that the file is positioned at the ! next record (the first data record). ! ! After this call, the user may close the file. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 04 February 2006 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, character ( len = * ) TEC_FILE_NAME, the name of the file. ! ! Input, integer TEC_FILE_UNIT, the unit associated with the file. ! ! Input, integer DIM_NUM, the spatial dimension. ! ! Input, integer NODE_NUM, the number of nodes. ! ! Input, integer ELEMENT_NUM, the number of elements. ! ! Input, integer ELEMENT_ORDER, the order of the elements. ! ! Input, integer NODE_DATA_NUM, the number of data items per node. ! ! Output, real ( kind = 8 ) NODE_COORD(DIM_NUM,NODE_NUM), the coordinates ! of nodes. ! ! Output, integer ELEMENT_NODE(ELEMENT_ORDER,ELEMENT_NUM); ! the global index of local node I in element J. ! ! Output, real ( kind = 8 ) NODE_DATA(NODE_DATA_NUM,NODE_NUM), the ! data values associated with each node. ! implicit none integer dim_num integer element_num integer element_order integer node_data_num integer node_num integer element integer element_node(element_order,element_num) integer node real ( kind = 8 ) node_coord(dim_num,node_num) real ( kind = 8 ) node_data(node_data_num,node_num) character ( len = * ) tec_file_name integer tec_file_unit ! ! Read the node coordinates and node data. ! do node = 1, node_num read ( tec_file_unit, * ) & node_coord(1:dim_num,node), node_data(1:node_data_num,node) end do ! ! Read the element-node connectivity. ! do element = 1, element_num read ( tec_file_unit, * ) element_node(1:element_order,element) end do return end subroutine tec_header_print ( dim_num, node_num, element_num, & element_order, node_data_num ) !*****************************************************************************80 ! !! TEC_HEADER_PRINT prints the header to a TEC file. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 04 February 2006 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer DIM_NUM, the spatial dimension. ! ! Input, integer NODE_NUM, the number of nodes. ! ! Input, integer ELEMENT_NUM, the number of elements. ! ! Input, integer ELEMENT_ORDER, the order of the elements. ! ! Input, integer NODE_DATA_NUM, the number of data items per node. ! implicit none integer dim_num integer element_num integer element_order integer node_data_num integer node_num write ( *, '(a)' ) ' ' write ( *, '(a,i8)' ) ' Spatial dimension = ', dim_num write ( *, '(a,i8)' ) ' Number of nodes = ', node_num write ( *, '(a,i8)' ) ' Number of elements = ', element_num write ( *, '(a,i8)' ) ' Element order = ', element_order write ( *, '(a,i8)' ) ' Number of node data items = ', node_data_num return end subroutine tec_header_read ( tec_file_name, tec_file_unit, dim_num, node_num, & element_num, element_order, node_data_num ) !*****************************************************************************80 ! !! TEC_HEADER_READ reads the header from a TEC file. ! ! Discussion: ! ! This routine assumes that the TEC file has already been opened on ! unit TEC_FILE_UNIT, and that it contains finite element data. ! ! The routine reads the optional TITLE record, the VARIABLES line ! and the ZONE line. It leaves the file open, positioned at the next ! record, which begins the data section. The user may either close ! the file, or call TEC_DATA_READ to read the data. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 18 February 2006 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, character TEC_FILE_NAME(*), the name of the TEC file. ! ! Input, integer TEC_FILE_UNIT, the unit number associated with the TEC file. ! ! Output, integer DIM_NUM, the spatial dimension, inferred from the ! names of the variables. ! ! Output, integer NODE_NUM, the number of nodes, determined by the ! "N=" argument. ! ! Output, integer ELEMENT_NUM, the number of elements, inferred from the ! "E=" argument. ! ! Output, integer ELEMENT_ORDER, the order of the elements, inferred from ! the "ZONETYPE=" argument. ! ! Output, integer NODE_DATA_NUM, the number of data items per node, ! inferred from the the number of node data items, minus those which are ! inferred to be spatial coordinates. ! ! Output, real ( kind = 8 ) NODE_COORD(DIM_NUM,NODE_NUM), the coordinates ! of nodes. ! implicit none integer begin logical ch_eqi integer dim_num integer element_num integer element_order character ( len = 80 ) element_type character ( len = 255 ) line character ( len = 20 ) name integer name_len integer node_data_num integer node_num logical s_begin logical s_eqi character ( len = * ) tec_file_name integer tec_file_status integer tec_file_unit integer variable character ( len = 255 ) variable_name integer, allocatable, dimension ( : ) :: variable_name_length integer variable_num ! ! Read and parse the TITLE line. ! But it is optional, so you may have just read the VARIABLES line instead! ! line = ' ' do while ( len_trim ( line ) <= 0 ) read ( tec_file_unit, '(a)', iostat = tec_file_status ) line if ( tec_file_status /= 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'TEC_FILE_HEADER_READ - Fatal error!' write ( *, '(a)' ) ' Error while reading the file,' write ( *, '(a)' ) ' searching for TITLE line.' stop end if end do ! ! Read the VARIABLES line. ! ! Because the TITLE line is apparently optional, we may have already ! read the VARIABLES line! ! if ( .not. s_begin ( line, 'VARIABLES=' ) ) then line = ' ' do while ( len_trim ( line ) == 0 ) read ( tec_file_unit, '(a)', iostat = tec_file_status ) line if ( tec_file_status /= 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'TEC_FILE_HEADER_READ - Fatal error!' write ( *, '(a)' ) ' Error while reading the file,' write ( *, '(a)' ) ' searching for VARIABLES line.' stop end if end do end if if ( .not. s_begin ( line, 'VARIABLES=' ) ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'TEC_HEADER_READ - Fatal error!' write ( *, '(a)' ) ' The VARIABLES = line is missing in the file.' stop end if ! ! Parse the VARIABLES line. ! VARIABLES = name1 name2 name3... ! The names may be quoted, and are separated by quotes, commas or spaces. ! ! Remove the initial "VARIABLES=" ! call s_behead_substring ( line, 'VARIABLES' ) call s_behead_substring ( line, '=' ) ! ! Replace single quotes, double quotes, commas and periods by blanks. ! call s_replace_ch ( line, '''', ' ' ) call s_replace_ch ( line, '"', ' ' ) call s_replace_ch ( line, ',', ' ' ) call s_replace_ch ( line, '.', ' ' ) ! ! Count the words. ! call s_word_count ( line, variable_num ) allocate ( variable_name_length(variable_num) ) ! ! Extract the words. ! begin = 0 do variable = 1, variable_num call s_word_extract ( line, name ) name_len = len_trim ( name ) variable_name_length(variable) = name_len variable_name(begin+1:begin+name_len) = name(1:name_len) begin = begin + name_len end do ! ! Based on the variable names, determine the spatial dimension and the number ! of node data items. ! ! For now, we SIMPLY ASSUME that the spatial coordinates are listed first. ! Hence, when we read the node data, we assume that the first DIM_NUM values ! represent X, Y and possibly Z. ! dim_num = 0 node_data_num = variable_num begin = 0 do variable = 1, variable_num if ( variable_name_length(variable) == 1 ) then name = variable_name(begin+1:begin+1) if ( ch_eqi ( name, 'X' ) .or. & ch_eqi ( name, 'Y' ) .or. & ch_eqi ( name, 'Z' ) ) then dim_num = dim_num + 1 node_data_num = node_data_num - 1 end if end if begin = begin + variable_name_length(variable) end do ! ! Read and parse the ZONE line. ! line = ' ' do while ( len_trim ( line ) == 0 ) read ( tec_file_unit, '(a)' ) line end do if ( .not. s_begin ( line, 'ZONE' ) ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'TEC_READ - Fatal error!' write ( *, '(a)' ) ' The ZONE = line is missing in the file.' stop end if call tec_zone_line_parse ( line, node_num, element_num, element_type ) ! ! Based on ELEMENT_TYPE, determine the element order. ! if ( s_eqi ( element_type, 'FETRIANGLE' ) ) then element_order = 3 elseif ( s_eqi ( element_type, 'FEQUADRILATERAL' ) ) then element_order = 4 elseif ( s_eqi ( element_type, 'FETETRAHEDRON' ) ) then element_order = 4 elseif ( s_eqi ( element_type, 'FEBRICK' ) ) then element_order = 8 else element_order = -1 end if deallocate ( variable_name_length ) return end subroutine tec_zone_line_parse ( line, node_num, element_num, element_type ) !*****************************************************************************80 ! !! TEC_ZONE_LINE_PARSE parses the "ZONE" line of a TEC file. ! ! Discussion: ! ! The string begins with the substring "ZONE" and is followed by ! a sequence of keywords and values joined by an equals sign. ! ! We expect the following, but in arbitrary order, separated ! by spaces or commas: ! ! N = number of nodes ! E = number of elements ! T = optional zone title (we can't handle this field right now) ! PACKING = POINT ! ZONETYPE = FETRIANGLE or FEQUADRILATERAL or FETETRAHEDRON or FEBRICK. ! ! Other arguments that may appear on this line will be ignore. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 20 February 2006 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, character ( len = * ) LINE, a string of characters, representing the ! "VARIABLES=" line of the file. ! ! Output, integer NODE_NUM, the number of nodes. ! ! Output, integer ELEMENT_NUM, the number of elements. ! ! Output, character ( len = * ) ELEMENT_TYPE, the element type: ! FETRIANGLE or FEQUADRILATERAL or FETETRAHEDRON or FEBRICK. ! implicit none logical ch_eqi integer element_num character ( len = * ) element_type integer found_num integer ierror integer length character ( len = * ) line character ( len = 80 ) name integer node_num logical s_eqi character ( len = 80 ) value ! ! Remove the initial "ZONE" ! call s_behead_substring ( line, 'ZONE' ) ! ! Replace each EQUALS sign by a space. ! Also get rid of commas and periods. ! Do single and double quotes have to go, also? ! call s_replace_ch ( line, '=', ' ' ) call s_replace_ch ( line, ',', ' ' ) call s_replace_ch ( line, '.', ' ' ) ! ! Now each pair of words represents a name and a value. ! node_num = -1 element_num = -1 element_type = ' ' found_num = 0 do call s_word_extract ( line, name ) if ( len_trim ( name ) == 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'TEC_ZONE_LINE_PARSE - Fatal error!' write ( *, '(a)' ) ' Unexpected End of input.' stop end if call s_word_extract ( line, value ) if ( len_trim ( value ) == 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'TEC_ZONE_LINE_PARSE - Fatal error!' write ( *, '(a)' ) ' Unexpected End of input.' stop end if if ( ch_eqi ( name(1:1), 'N' ) .and. node_num == -1 ) then call s_to_i4 ( value, node_num, ierror, length ) found_num = found_num + 1 elseif ( ch_eqi ( name(1:1), 'E' ) .and. element_num == -1 ) then call s_to_i4 ( value, element_num, ierror, length ) found_num = found_num + 1 elseif ( s_eqi ( name, 'DATAPACKING' ) ) then if ( .not. s_eqi ( value, 'POINT' ) ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'TEC_ZONE_LINE_PARSE - Fatal error!' write ( *, '(a)' ) ' Value of DATAPACKING argument must be POINT.' stop end if elseif ( s_eqi ( name, 'ZONETYPE' ) .and. & len_trim ( element_type ) == 0 ) then found_num = found_num + 1 element_type = value else write ( *, '(a)' ) ' ' write ( *, '(a)' ) ' Ignoring "' // trim ( name ) & // '" = "' // trim ( value ) // '".' end if if ( found_num == 3 ) then exit end if end do 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 GNU LGPL license. ! ! Modified: ! ! 06 August 2005 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! None ! implicit none 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 subroutine ucd_write ( node_num, dim_num, node_data_num, cell_num, & cell_order, node_coord, node_data, cell_node, output_file_unit, & output_file_name ) !*****************************************************************************80 ! !! UCD_WRITE writes graphics data to an AVS UCD file. ! ! Discussion: ! ! We include dummy variables for cell data, including ! CELL_DATA_NUM and CELL_DATA, but for now, we do not intend ! to handle cell data. ! ! Licensing: ! ! This code is distributed under the GNU LGPL license. ! ! Modified: ! ! 01 February 2006 ! ! Author: ! ! John Burkardt ! ! Parameters: ! ! Input, integer NODE_NUM, the number of nodes. ! ! Input, integer DIM_NUM, the spatial dimension of the nodes. ! ! Input, integer NODE_DATA_NUM, the number of non-coordinate data items ! associated with each node. ! ! Input, integer CELL_NUM, the number of cells. ! ! Input, integer CELL_ORDER, the order of the cells. ! ! Input, real ( kind = 8 ) NODE_COORD(DIM_NUM,NODE_NUM), the node ! coordinates. ! ! Input, real ( kind = 8 ) NODE_DATA(NODE_DATA_NUM,NODE_NUM), the data ! associated with each node. ! ! Input, integer CELL_NODE(CELL_ORDER,CELL_NUM), the nodes ! associated with each cell. ! ! Input, integer OUTPUT_FILE_UNIT, the unit number associated with ! the output file. ! ! Input, character ( len = * ) OUTPUT_FILE_NAME, the name of the ! output file. ! implicit none integer, parameter :: cell_data_num = 0 integer cell_num integer cell_order integer dim_num integer node_data_num integer node_num integer cell integer cell_data(1,1) integer cell_material integer cell_node(cell_order,cell_num) character ( len = 5 ) cell_type character ( len = 80 ) format_string integer i integer node real ( kind = 8 ) node_coord(dim_num,node_num) real ( kind = 8 ) node_data(node_data_num,node_num) character ( len = * ) output_file_name integer output_file_unit character ( len = 80 ) text write ( output_file_unit, '(a)' ) '# ' // trim ( output_file_name ) write ( output_file_unit, '(a)' ) '# AVS UCD structure.' write ( output_file_unit, '(a)' ) '#' write ( output_file_unit, '(a)' ) '# 1) node_num, cell_num, ' // & ' node_data_num, cell_data_num, model_num' write ( output_file_unit, '(a)' ) '# 2) node, node_coords' write ( output_file_unit, '(a)' ) '# 3) cell, cell_mat, cell_type, ' // & ' cell_nodes' write ( output_file_unit, '(a)' ) '# 4) node_data components, ' // & ' node data dimensions.' write ( output_file_unit, '(a)' ) '# 5) node component label, units' write ( output_file_unit, '(a)' ) '# 6) node_data for each node' write ( output_file_unit, '(a)' ) '# 7) cell data components, ' // & ' cell data dimensions' write ( output_file_unit, '(a)' ) '# 8) cell component label, units' write ( output_file_unit, '(a)' ) '# 9) cell_data for each cell' write ( output_file_unit, '(a)' ) '#' ! ! 1) node_num, cell_num, node_data_num, cell_data_num, model_num ! write ( output_file_unit, '(2x,i8,2x,i8,2x,i8,2x,i8,2x,i8)' ) & node_num, cell_num, node_data_num, 0, 0 ! ! 2) node, node_coordinates. ! do node = 1, node_num write ( output_file_unit, '(2x,i8,2x,f14.6,2x,f14.6,2x,f14.6)' ) & node, node_coord(1:dim_num,node) end do ! ! 3) cell, cell_mat, cell_type, cell_nodes' ! cell_material = 0 if ( cell_order == 1 ) then cell_type = 'pt ' else if ( cell_order == 2 ) then cell_type = 'line ' else if ( cell_order == 3 ) then cell_type = 'tri ' else if ( cell_order .eq. 4 ) then cell_type = 'quad' ! cell_type = 'tet ' else if ( cell_order .eq. 5 ) then cell_type = 'pyr ' else if ( cell_order .eq. 6 ) then cell_type = 'prism' else if ( cell_order .eq. 8 ) then cell_type = 'hex ' else cell_type = '?????' end if do cell = 1, cell_num write ( output_file_unit, '(2x,i8,2x,i8,2x,a5,2x,8i8)' ) & cell, cell_material, cell_type, cell_node(1:cell_order,cell) end do ! ! 4) number of node data components, component dimensions. ! ???Are we counting (X,Y,Z)? ! ! write ( output_file_unit, '(2x,i8,2x,i8)' ) 1, node_data_num ! write ( output_file_unit, '(2x,i8,2x,i8)' ) 3, 1, 1, 3 write ( output_file_unit, '(2x,i8,2x,i8)' ) 3, 3, 3, 1 ! ! 5) node component label, units ! ! text = 'node_data_00, units' ! do i = 1, node_data_num ! call file_name_inc ( text ) ! write ( output_file_unit, '(a)' ) trim ( text ) ! end do write ( output_file_unit, '(a)' ) 'P, units' write ( output_file_unit, '(a)' ) 'S, units' write ( output_file_unit, '(a)' ) 'SxSySz, units' ! ! 6) node_data for each node ! if ( 0 < node_data_num ) then write ( format_string, '(a,i8,a)' ) & '(2x,i8,2x', node_data_num, '(2x,f14.6))' do node = 1, node_num write ( output_file_unit, format_string ) & node, node_data(1:node_data_num,node) end do end if ! ! 7) cell_data components, cell data dimensions. ! write ( output_file_unit, '(2x,i8,2x,i8)' ) cell_data_num, cell_data_num ! ! 8) cell component label, units ! text = 'cell_data_00, units' do i = 1, cell_data_num call file_name_inc ( text ) write ( output_file_unit, '(a)' ) trim ( text ) end do ! ! 9) cell_data for each cell ! if ( 0 < cell_data_num ) then do cell = 1, cell_num write ( output_file_unit, format_string ) cell_data(1:cell_data_num,cell) end do end if return end