program main !*****************************************************************************80 ! !! MAIN is the main program for SMDLIB_FONTS. ! ! Discussion: ! ! SMDLIB_FONTS creates a binary font database for SMDLIB. ! ! Discussion: ! ! SMDLIB_FONTS reads one or more text files, containing information ! defining various fonts, and generates a direct access file ! for use by SMDLIB. ! ! Modified: ! ! 07 September 2008 ! implicit none integer, parameter :: maxtot = 22 integer, parameter :: mxstrk = 12000 integer, parameter :: maxrec = maxtot*(mxstrk+511)/512 integer bwidth(95) integer bx(150) integer bxy(mxstrk) integer by(150) integer height integer i integer ibias(maxtot) integer ibxy integer icmax integer icmin integer ie integer ifill(512) integer ileft integer indx(96) character ( len = 80 ) inpfil integer ios integer iright integer is integer j integer jchar integer jst character ( len = 80 ) kode integer load integer luni integer luno integer nmchar integer nrec integer nst integer nstrok integer, parameter :: numbyt = 4 character ( len = 80 ) :: outfil = 'smdlib_fonts.dat' call timestamp ( ) write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'SMDLIB_FONTS' write ( *, '(a)' ) ' FORTRAN90 version.' write ( *, '(a)' ) ' ' write ( *, '(a)' ) ' Create the single SMDLIB binary font database' write ( *, '(a)' ) ' from a collection of ASCII font files.' write ( *, '(a)' ) ' ' write ( *, '(a)' ) ' SMDLIB_FONTS incorporates all the fonts into ' write ( *, '(a)' ) ' one direct access file.' ! ! Open the direct access output file. ! ! The RECL parameter is specified in bytes. ! call get_unit ( luno ) open ( unit = luno, file = outfil, status = 'replace', access = 'direct', & form = 'unformatted', recl = 512*numbyt, iostat = ios ) if ( ios /= 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'SMDLIB_FONTS - Fatal error!' write ( *, '(a)' ) ' An error occurred while opening the' write ( *, '(a)' ) ' output file ' // trim ( outfil ) stop end if write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'SMDLIB_FONTS:' write ( *, '(a)' ) ' Enter:' write ( *, '(a)' ) ' * the name of the next ASCII font file to process,' write ( *, '(a)' ) ' or' write ( *, '(a)' ) ' * RETURN if done.' write ( *, '(a)' ) ' ' load = 2 ibias(1) = 0 ibias(2) = 1 nrec = 0 do read ( *, '(a)', iostat = ios ) inpfil if ( len_trim ( inpfil ) .le. 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'SMDLIB_FONTS:' write ( *, '(a)' ) ' End of input.' exit end if write ( *, '(a)' ) ' Reading "' // trim ( inpfil ) // '".' if ( ios /= 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'SMDLIB_FONTS - Fatal error!' write ( *, '(a)' ) ' Input error reading input file name.' stop end if call get_unit ( luni ) open ( unit = luni, file = inpfil, status = 'old', iostat = ios ) if ( ios /= 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'SMDLIB_FONTS - Fatal error!' write ( *, '(a)' ) ' An error occurred while opening the' write ( *, '(a)' ) ' input file ' // trim ( inpfil ) stop end if ibxy = 0 ! ! Read in a character from the sequential file and calculate the width. ! indx(1) = 1 rewind ( unit = luni ) do read ( luni, '(18i4)', iostat = ios ) jchar, nstrok, ileft, iright, & ( bx(i), by(i), i=1,7 ) if ( ios /= 0 ) then exit end if if ( jchar <= 32 .or. jchar >= 128 ) then cycle end if jchar = jchar - 32 bwidth(jchar) = iright - ileft nst = nstrok / 2 if ( nstrok > 16 ) then read ( luni, '(18i4)', iostat = ios ) ( bx(i), by(i), i = 8, nst-1 ) if ( ios /= 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'SMDLIB_FONTS - Error!' write ( *, '(a)' ) ' An input error occurred while processing' write ( *, '(a)' ) ' the font file: ' // trim ( inpfil ) stop end if end if nstrok = ( nstrok - 4 ) / 2 do i = 1, nstrok if ( bx(i) == -999 ) then ibxy = ibxy + 1 bxy(ibxy) = -64 else ibxy = ibxy + 2 bxy(ibxy-1) = bx(i) - ileft bxy(ibxy) = by(i) end if end do indx(jchar+1) = ibxy + 1 end do ! ! Calculate the height based on a capital A. ! is = indx(33) ie = indx(34) - 1 icmax = bxy(is+1) icmin = bxy(is+1) if ( icmax == -64 ) then icmin = bxy(is+2) icmax = bxy(is+2) end if i = is - 2 do i = i + 2 if ( i >= ie ) then exit end if if ( bxy(i) /= -64 ) then icmax = max ( icmax, bxy(i+1) ) icmin = min ( icmin, bxy(i+1) ) else i = i - 1 end if end do height = icmax - icmin ! ! Subtract the Y bias from the Y values in BXY to make zero the base ! of all capital letters. ! nmchar = ibxy i = -1 do i = i + 2 if ( nmchar <= i ) then exit end if if ( bxy(i) /= -64 ) then bxy(i+1) = bxy(i+1) - icmin else i = i - 1 end if end do ! ! Initialize the IFILL array. ! ifill(1:512) = 0 ! ! Write the header record. ! nrec = 1 + ( nmchar + 511 ) / 512 write ( luno, rec = 1, iostat = ios ) load, ibias(2:load), & ifill(load+1:512) if ( ios /= 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'SMDLIB_FONTS - Error!' write ( *, '(a)' ) ' An error occurred while writing record 1' write ( *, '(a)' ) ' of the output file.' write ( *, '(a,i6)' ) ' The value of IOSTAT was ', ios stop end if write ( luno, rec = 1+ibias(load), iostat = ios ) nmchar, height, & indx(1:96), bwidth(1:95), ifill(1:319) if ( ios /= 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'SMDLIB_FONTS - Error!' write ( *, '(a)' ) ' An error occurred while writing the output file.' write ( *, '(a,i6)' ) ' The value of IOSTAT was ', ios stop end if ! ! Write out the strokes. ! jst = 1 do i = 1, nrec-1 write ( luno, rec = i+1+ibias(load), iostat = ios ) bxy(jst:jst+511) if ( ios /= 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'SMDLIB_FONTS - Error!' write ( *, '(a)' ) ' An error occurred while operating on the' write ( *, '(a)' ) ' output file ' // trim ( outfil ) stop end if jst = jst + 512 end do if ( jst <= nmchar ) then write ( luno, rec = nrec+1+ibias(load), iostat = ios ) bxy(jst:nmchar) if ( ios /= 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'SMDLIB_FONTS - Error!' write ( *, '(a)' ) ' An error occurred while operating on the' write ( *, '(a)' ) ' output file ' // trim ( outfil ) stop end if end if load = load + 1 if ( maxtot < load ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'SMDLIB_FONTS - Warning!' write ( *, '(a)' ) ' No more fonts can be processed.' write ( *, '(a)' ) ' The output file is being closed now.' exit end if ibias(load) = ibias(load-1) + nrec + 1 end do load = load - 1 close ( unit = luno ) close ( unit = luni ) write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'SMDLIB_FONTS:' write ( *, '(a)' ) ' The file "' // trim ( outfil ) // '" was created.' write ( *, '(a)' ) ' This direct access font file fonts 2 through ', load write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'SMDLIB_FONTS:' write ( *, '(a)' ) ' Normal end of execution.' write ( *, '(a)' ) ' ' call timestamp ( ) stop 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 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