Using Box drawing characters

Hello everyone,

I recently found out that the UTF-8 character set has a nice set of characters for drawing boxes on the terminal. I thought these would be nice for creating simple text-based interfaces for my programs.

However, the box drawing characters don’t seem to work very well with ordinary Fortran character strings. I tried them with following program. It should print a square on the terminal.

program main
    implicit none
    
    integer, parameter :: NW = 1
    integer, parameter :: SW = 3
    integer, parameter :: NE = 2
    integer, parameter :: SE = 4
    character(len=*), parameter :: hline = '─'
    character(len=*), parameter :: vline = '│'
    character(len=*), parameter :: corners = '┌┐└┘'
    
    integer :: box_size
    integer :: line
    
    write(*, '(a)', advance='no') 'Enter box size: '
    read (*, '(i3)') box_size
    
    print '(a,i0,a)', 'Printing a box of size ', box_size, '.'
    
    do line = 1, box_size
        if (line == 1) then
            write(*,'(a)',advance='no') corners(NW:NW)
            write(*,'(a)',advance='no') repeat(hline, box_size - 2)
            write(*,'(a)',advance='yes') corners(NE:NE)
        end if
        
        if ((line > 1) .and. (line < box_size)) then
            write(*,'(a,a,a)') vline, repeat(' ', box_size - 2), vline
        end if
        
        if (line == box_size) then
            write(*,'(a)',advance='no') corners(SW:SW)
            write(*,'(a)',advance='no') repeat(hline, box_size - 2)
            write(*,'(a)',advance='yes') corners(SE:SE)
        end if
    end do
end program main

This is the output:
Kuvakaappaus 2021-01-31 16-26-34

As can be seen, the “corner” characters are not printed correctly. Is there any way to use these characters with Fortran? Thanks in advance!

GFortran version: GNU Fortran (GCC) 10.2.1 20201125 (Red Hat 10.2.1-9)

2 Likes

Your characters need to be of kind ISO 10646 (UCS-4), and the default output unit has to be opened with UTF-8 encoding first:

program main
    use, intrinsic :: iso_fortran_env, only: output_unit
    implicit none
    integer, parameter :: ucs4 = selected_char_kind('ISO_10646')
    character(kind=ucs4, len=:), allocatable :: str

    str = ucs4_'Unicode Box Drawing: ' // &
          char(int(z'250C'), kind=ucs4) // &
          char(int(z'2510'), kind=ucs4) // &
          char(int(z'2514'), kind=ucs4) // &
          char(int(z'2518'), kind=ucs4)

    open (output_unit, encoding='utf-8')
    print '(a)', str
end program main

Make sure your terminal emulator can display the printed UTF-8 code points.

3 Likes

Yes, indeed - that is the Fortran standard supported way.

But the standard does not require a processor to support ISO_10646 character set, it leaves it as processor-dependent. Unfortunately compiler support for ISO_10646 set is limited and some compilers only support one character set, ASCII.

The code shown can then fail to compile on account of a negative value for ucs4 constant for that character kind.

1 Like

The character kind is part of iso_fortran_env and should be available if the compiler supports the module. [Edit: nope, you’re right, ISO_10646 depends on the compiler] Certainly, as you said, not every compiler does so, like Flang, for instance:

$ flang -o ucs4 ucs4.f90                                                       
F90-F-0004-Unable to open MODULE file iso_fortran_env.mod (ucs4.f90: 2)
F90/x86-64 FreeBSD Flang - 1.5 2017-05-01: compilation aborted

Might it be that the problem is the font used by your terminal window? Not all fonts have these characters.

Alternatives also have their limitations as to what terminal emulators and fonts are required, but many emulators support the DEC extended character set which only requires ANSI characters (but requires exiting and entering the graphics character “mode”). If your terminal+font supports it:

program decsg
DEC Special Graphics
!            mt           
!  tl #hhhhhhh#hhhhhhh# tr 
!     v       v       v
!     v       v       v
!     v       v       v
!  ml #hhhhhhhmhhhhhhh# mr  
!     v       v       v
!     v       v       v
!     v       v       v
!  bl #hhhhhhh#hhhhhhh# br 
!             mb
character(len=1),parameter :: esc=char(27), &
 & tl=char(108),  tr=char(107),  bl=char(109),  br=char(106), &
 & h=char(113),   v=char(120),   m=char(110),   b=' ',        &
 & mt=char(119),  mb=char(118),  ml=char(116),  mr=char(117) 

   write(*,*)esc,'(0',tl,h,h,h,h,h,mt,h,h,h,h,h,tr,esc,'(B'
   write(*,*)esc,'(0',v ,b,b,b,b,b, v,b,b,b,b,b, v,esc,'(B'
   write(*,*)esc,'(0',v ,b,b,b,b,b, v,b,b,b,b,b, v,esc,'(B'
   write(*,*)esc,'(0',v ,b,b,b,b,b, v,b,b,b,b,b, v,esc,'(B'
   write(*,*)esc,'(0',v ,b,b,b,b,b, v,b,b,b,b,b, v,esc,'(B'
   write(*,*)esc,'(0',ml,h,h,h,h,h, m,h,h,h,h,h,mr,esc,'(B'
   write(*,*)esc,'(0',v ,b,b,b,b,b, v,b,b,b,b,b, v,esc,'(B'
   write(*,*)esc,'(0',v ,b,b,b,b,b, v,b,b,b,b,b, v,esc,'(B'
   write(*,*)esc,'(0',v ,b,b,b,b,b, v,b,b,b,b,b, v,esc,'(B'
   write(*,*)esc,'(0',v ,b,b,b,b,b, v,b,b,b,b,b, v,esc,'(B'
   write(*,*)esc,'(0',bl,h,h,h,h,h,mb,h,h,h,h,h,br,esc,'(B'

end program decsg

And there are several Fortran interfaces to the curses/ncurses/pcurses libraries ias alternatives to UTF-8 Many Fortran programs supported boxes
in the past. The best interface for Fortran was called TDU on CDC NOS machines, which easily allowed creating interactive active forms by inputting a simple text template. A non-proprietary demonstration program that is similiar to a subset of TDU is in the fixedform program in the GPF collection, which also includes an ncurses interface.

Thanks a lot @interkosmos. With your modifications, I managed to print my boxes. Additionally, I found I could just directly use the decimal codes instead of int(z’250C’) etc. as parameters for the CHAR() function.

Here’s the functioning test code (for completeness).

program main
    use, intrinsic :: iso_fortran_env, only: output_unit
    implicit none
    
    integer, parameter :: ucs4 = selected_char_kind('ISO_10646')
    
    ! Defining UTF-8 box drawing characters:
    !  char dec  hex
    !  '─'  9472 0x2500
    !  '│'  9474 0x2502
    !  '┌'  9484 0x250C
    !  '┐'  9488 0x2510
    !  '└'  9492 0x2514
    !  '┘'  9496 0x2518
    character(kind=ucs4, len=*), parameter :: hline = char(9472,kind=ucs4)
    character(kind=ucs4, len=*), parameter :: vline = char(9474,kind=ucs4)
    character(kind=ucs4, len=*), parameter :: cornerNW = char(9484,kind=ucs4)
    character(kind=ucs4, len=*), parameter :: cornerNE = char(9488,kind=ucs4)
    character(kind=ucs4, len=*), parameter :: cornerSW = char(9492,kind=ucs4)
    character(kind=ucs4, len=*), parameter :: cornerSE = char(9496,kind=ucs4)
    integer :: box_size
    integer :: line
    
    open(output_unit, encoding='utf-8')
    
    write(*, '(a)', advance='no') 'Enter box size: '
    read (*, '(i3)') box_size
    
    print '(a,i0,a)', 'Printing a box of size ', box_size, '.'
    
    do line = 1, box_size
        if (line == 1) then
            write(*,'(a)',advance='no') cornerNW
            write(*,'(a)',advance='no') repeat(hline, box_size - 2)
            write(*,'(a)',advance='yes') cornerNE
        end if
        
        if ((line > 1) .and. (line < box_size)) then
            write(*,'(a,a,a)') vline, repeat(' ', box_size - 2), vline
        end if
        
        if (line == box_size) then
            write(*,'(a)',advance='no') cornerSW
            write(*,'(a)',advance='no') repeat(hline, box_size - 2)
            write(*,'(a)',advance='yes') cornerSE
        end if
    end do
end program main

@sblionel: That’s a good point. In fact I am using the Gnome Terminal application which has pretty good UTF-8 support. It can even print smiley faces at me.

@urbanjost: Thanks for your information and the link to your ncurses interface. This is definitely something I need experiment with some day. Ncurses seems to offer great possibilities for building text user interfaces.

1 Like
    !  char dec  
    !  '═'  9552 
    !  '║'  9553 
    !  '╔'  9556 
    !  '╗'  9559 
    !  '╚'  9562 
    !  '╝'  9565 
    !  '╠'  9568 
    !  '╣'  9571 
    !  '╦'  9574 
    !  '╩'  9577 
    !  '╬'  9580 

    character(kind=ucs4, len=*), parameter :: dhline = char(9552,kind=ucs4)
    character(kind=ucs4, len=*), parameter :: dvline = char(9553,kind=ucs4)
    character(kind=ucs4, len=*), parameter :: dcornerNW = char(9556,kind=ucs4)
    character(kind=ucs4, len=*), parameter :: dcornerNE = char(9559,kind=ucs4)
    character(kind=ucs4, len=*), parameter :: dcornerSW = char(9562,kind=ucs4)
    character(kind=ucs4, len=*), parameter :: dcornerSE = char(9565,kind=ucs4)

No problem. Thought I would mention the alternatives, as non-ASCII characters are still not supported by a good number of Fortran compilers. Np one mentioned the double-line box characters, which I often prefer, so I thought I would mention those too, for future viewers.

1 Like