1/*
    2  BSD 2-Clause License
    3
    4  Copyright (c) 2019, Can Bican
    5  All rights reserved.
    6
    7  Redistribution and use in source and binary forms, with or without
    8  modification, are permitted provided that the following conditions are met:
    9
   10  * Redistributions of source code must retain the above copyright notice, this
   11    list of conditions and the following disclaimer.
   12
   13  * Redistributions in binary form must reproduce the above copyright notice,
   14    this list of conditions and the following disclaimer in the documentation
   15    and/or other materials provided with the distribution.
   16
   17  THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS"
   18  AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
   19  IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
   20  DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE
   21  FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
   22  DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR
   23  SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   24  CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY,
   25  OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
   26  OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
   27*/
   28
   29:- module(ansi_termx, [
   30  clear_all_tabs/0,
   31  clear_screen/0,
   32  clear_tab/0,
   33  color/1,
   34  color/5,
   35  cursor_move/2,
   36  cursor_position/2,
   37  cursor_save/0,
   38  cursor_unsave/0,
   39  reset/0,
   40  screen_size/2,
   41  scroll/2,
   42  set_tab/0,
   43  style/1
   44  ]).

ANSI terminal manipulation predicates

This module provides predicates for manipulating ANSI terminals. It doesn't aim to cover all of the features, focusing on functionality for fancier output. The extra x at the end of the package name aims to disambiguate the SWI-Prolog library library(ansi_term).

author
- Can Bican
See also
- library(ansi_term)
license
- BSD 2-clause */
   57color_code(default, 39, 49).
   58color_code(black, 30, 40).
   59color_code(red, 31, 41).
   60color_code(green, 32, 42).
   61color_code(yellow, 33, 43).
   62color_code(blue, 34, 44).
   63color_code(magenta, 35, 45).
   64color_code(cyan, 36, 46).
   65color_code(white, 37, 47).
   66color_code(bright_black, 90, 100).
   67color_code(bright_red, 91, 101).
   68color_code(bright_green, 92, 102).
   69color_code(bright_yellow, 93, 103).
   70color_code(bright_blue, 94, 104).
   71color_code(bright_magenta, 95, 105).
   72color_code(bright_cyan, 96, 106).
   73color_code(bright_white, 97, 107).
   74
   75style_code(default, 0).
   76style_code(bold, 1).
   77style_code(dim, 2).
   78style_code(italic, 3).
   79style_code(underline, 4).
   80style_code(reverse, 7).
   81style_code(crossed_out, 9).
   82
   83scroll_direction(up, 'S').
   84scroll_direction(down, 'T').
   85
   86cursor_direction(up, 'A').
   87cursor_direction(down, 'B').
   88cursor_direction(forward, 'C').
   89cursor_direction(backward, 'D').
 clear_all_tabs is det
Clear all tabs
   93clear_all_tabs :- out_tty('[3g').
 clear_screen is det
Clear the screen and move cursor to topleft of the screen
   97clear_screen :-
   98  out_tty('[2J'),
   99  goto_position(0, 0).
 clear_tab is det
Clear the tab on the current cursor position
  103clear_tab :- out_tty('[g').
 color(-Color:atom) is multi
Enumerates available colors.
Arguments:
Color- is a valid color
  110color(Color) :-
  111  color_code(Color, _, _).
 color(+Color:atom, +Background:atom, +Styles:list(atom), +Input:any, -Output:string) is semidet
Generates text of input with a style.
Arguments:
Color- is one of default, black, red, green, yellow, blue, magenta, cyan, white, bright_black, bright_red, bright_green, bright_yellow, bright_blue, bright_magenta, bright_cyan or bright_white.
Background- is one of default, black, red, green, yellow, blue, magenta, cyan, white, bright_black, bright_red, bright_green, bright_yellow, bright_blue, bright_magenta, bright_cyan or bright_white.
Styles- is one or more of default, bold, dim, italic, underline, reverse or crossed_out.
Input- is any kind of variable that can be fed to ~w modifier of format/3.
Output- is the resulting string that can be printed by printing predicate.
  131color(Color, Background, Styles, Input, Output) :-
  132  color_code(Color, ColorCode, _),
  133  color_code(Background, _, BackgroundCode),
  134  maplist(style_code, Styles, StyleCodes),
  135  atomic_list_concat(StyleCodes, ';', StyleCode),
  136  format(atom(Output), '\033[~w;~w;~wm~w\033[0m',[StyleCode, ColorCode, BackgroundCode, Input]).
 cursor_move(+Count:int, +Direction:atom) is semidet
Relative cursor movement.
Arguments:
Count- is number of steps to move in Direction.
Direction- is one of up, down, forward or backward.
  144cursor_move(Count, Direction) :-
  145  number(Count),
  146  cursor_direction(Direction, D),
  147  format(atom(Out),'[~w~w', [Count, D]),
  148  out_tty(Out).
 cursor_position(?Row:int, ?Column:int) is det
Queries and sets the cursor position.
Arguments:
Row- is the row of the screen. It can be queried or set.
Column- is the column of the screen. It can be queried or set.
  156cursor_position(Row, Column) :-
  157  \+ ground(Row),
  158  \+ ground(Column),
  159  !,
  160  read_screen_position_response(Row, Column).
  161
  162cursor_position(NewRow, Column) :-
  163  ground(NewRow),
  164  \+ ground(Column),
  165  !,
  166  read_screen_position_response(_, Column),
  167  goto_position(NewRow, Column).
  168
  169cursor_position(Row, NewColumn) :-
  170  ground(NewColumn),
  171  \+ ground(Row),
  172  !,
  173  read_screen_position_response(Row, _),
  174  goto_position(Row, NewColumn).
  175
  176cursor_position(Row, Column) :-
  177  goto_position(Row, Column).
 cursor_save is det
Saves the current position of the cursor, to be retrieved later by cursor_unsave/0.
  181cursor_save :- out_tty('[s').
 cursor_unsave is det
Restores the current position of the cursor, previously saved by cursor_save/0.
  185cursor_unsave :- out_tty('[u').
 reset is det
Resets the terminal
  189reset :- out_tty('c').
 screen_size(-Rows:int, -Columns:int) is det
Determines the screen size.
Arguments:
Rows- is the height of the current terminal.
Columns- is the width of the current terminal.
  197screen_size(Rows, Columns) :-
  198  cursor_position(OR, OC),
  199  cursor_position(9999, 9999),
  200  cursor_position(Rows, Columns),
  201  cursor_position(OR, OC).
 scroll(+Lines:int, +Direction:atom) is semidet
Scrolls the screen up or down, depending on the direction.
Arguments:
Lines- number of lines to scroll
Direction- up or down
  209scroll(Count, Direction) :-
  210  number(Count),
  211  scroll_direction(Direction, D),
  212  format(atom(Out),'[~w~w', [Count, D]),
  213  out_tty(Out).
 set_tab is det
Set a tab on the current cursor position
  217set_tab :- out_tty('H').
 style(-Style:atom) is multi
Enumerates all styles.
Arguments:
Style- is a valid style
  224style(Style) :-
  225  style_code(Style, _).
  226 
  227goto_position(Row, Column) :-
  228  format(atom(Out), '[~w;~wH', [Row, Column]),
  229  out_tty(Out).
  230
  231read_screen_position_response(Row, Column) :-
  232  out_tty('[6n'),
  233  read_input_upto(82, [27, 91|ResponseCodes]),
  234  !,
  235  string_codes(ResponseString, ResponseCodes),
  236  split_string(ResponseString, ';', "", [RowString, ColumnString]),
  237  number_codes(Row, RowString),
  238  number_codes(Column, ColumnString).
  239read_screen_position_response(0, 0).
  240
  241read_input_upto(S, Result) :-
  242  read_tty_char(Char),
  243  (  Char=S
  244  -> Result=[]
  245  ;  read_input_upto(S, SubResult),
  246     Result=[Char|SubResult]
  247  ).
  248
  249read_tty_char(Char) :-
  250  is_tty,
  251  get_single_char(Char).
  252
  253out_tty(Out) :-
  254  is_tty,
  255  !,
  256  format('\033~w', [Out]).
  257out_tty(_).
  258
  259is_tty :-
  260  stream_property(current_output, tty(true)),
  261  current_prolog_flag(color_term, true)