aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorLaurence Kedward <laurence.kedward@bristol.ac.uk>2021-11-28 11:43:49 +0000
committerLaurence Kedward <laurence.kedward@bristol.ac.uk>2021-11-29 11:56:10 +0000
commitb0115d1a000ee15d3ca773c3da3300595d805454 (patch)
tree37262d539db79f61093d94195dc94a181e17db01
parent6aba40db1385007e0bf4e9c2b9b4afe8bb105593 (diff)
downloadfpm-b0115d1a000ee15d3ca773c3da3300595d805454.tar.gz
fpm-b0115d1a000ee15d3ca773c3da3300595d805454.zip
Apply suggestion: don't use M_attr, simplify implementation
-rw-r--r--fpm.toml5
-rw-r--r--src/fpm_backend_console.f9059
-rw-r--r--src/fpm_backend_output.f9022
3 files changed, 27 insertions, 59 deletions
diff --git a/fpm.toml b/fpm.toml
index f3a297c..7289c82 100644
--- a/fpm.toml
+++ b/fpm.toml
@@ -14,11 +14,6 @@ rev = "2f5eaba864ff630ba0c3791126a3f811b6e437f3"
git = "https://github.com/urbanjost/M_CLI2.git"
rev = "ea6bbffc1c2fb0885e994d37ccf0029c99b19f24"
-[dependencies.M_attr]
-git = "https://github.com/urbanjost/M_attr.git"
-rev = "608b9d3b40be9ff2590c23d2089781fd4da76344"
-
-
[[test]]
name = "cli-test"
source-dir = "test/cli_test"
diff --git a/src/fpm_backend_console.f90 b/src/fpm_backend_console.f90
index 73bcd5d..014e800 100644
--- a/src/fpm_backend_console.f90
+++ b/src/fpm_backend_console.f90
@@ -14,21 +14,30 @@ implicit none
private
public :: console_t
+public :: LINE_RESET
+public :: COLOR_RED, COLOR_GREEN, COLOR_YELLOW, COLOR_RESET
character(len=*), parameter :: ESC = char(27)
+!> Escape code for erasing current line
+character(len=*), parameter :: LINE_RESET = ESC//"[2K"//ESC//"[1G"
+!> Escape code for moving up one line
+character(len=*), parameter :: LINE_UP = ESC//"[1A"
+!> Escape code for moving down one line
+character(len=*), parameter :: LINE_DOWN = ESC//"[1B"
+!> Escape code for red foreground color
+character(len=*), parameter :: COLOR_RED = ESC//"[31m"
+!> Escape code for green foreground color
+character(len=*), parameter :: COLOR_GREEN = ESC//"[32m"
+!> Escape code for yellow foreground color
+character(len=*), parameter :: COLOR_YELLOW = ESC//"[93m"
+!> Escape code to reset foreground color
+character(len=*), parameter :: COLOR_RESET = ESC//"[0m"
!> Console object
type console_t
!> Number of lines printed
integer :: n_line = 1
- !> 'Plain' output (no escape codes)
- logical :: plain_mode = .false.
- !> Escape code for erasing current line
- character(:), allocatable :: LINE_RESET
- !> Escape code for moving up one line
- character(:), allocatable :: LINE_UP
- !> Escape code for moving down one line
- character(:), allocatable :: LINE_DOWN
+
contains
!> Write a single line to the console
procedure :: write_line => console_write_line
@@ -36,36 +45,8 @@ contains
procedure :: update_line => console_update_line
end type console_t
-!> Constructor for console_t
-interface console_t
- procedure :: new_console
-end interface console_t
-
contains
-!> Initialise a new console object
-function new_console(plain_mode) result(console)
- !> 'Plain' output (no escape codes)
- logical, intent(in), optional :: plain_mode
- !> Console object to initialise
- type(console_t) :: console
-
- if (present(plain_mode)) then
- console%plain_mode = plain_mode
- end if
-
- if (console%plain_mode) then
- console%LINE_RESET = ""
- console%LINE_UP = ""
- console%LINE_DOWN = ""
- else
- console%LINE_RESET = ESC//"[2K"//ESC//"[1G"
- console%LINE_UP = ESC//"[1A"
- console%LINE_DOWN = ESC//"[1B"
- end if
-
-end function new_console
-
!> Write a single line to the standard output
subroutine console_write_line(console,str,line,advance)
!> Console object
@@ -92,7 +73,7 @@ subroutine console_write_line(console,str,line,advance)
line = console%n_line
end if
- write(stdout,'(A)',advance=trim(adv)) console%LINE_RESET//str
+ write(stdout,'(A)',advance=trim(adv)) LINE_RESET//str
if (adv=="yes") then
console%n_line = console%n_line + 1
@@ -118,12 +99,12 @@ subroutine console_update_line(console,line_no,str)
n = console%n_line - line_no !+ 1 !+ 1
! Step back to line
- write(stdout,'(A)',advance="no") repeat(console%LINE_UP,n)//console%LINE_RESET
+ write(stdout,'(A)',advance="no") repeat(LINE_UP,n)//LINE_RESET
write(stdout,*) str
! Step forward to end
- write(stdout,'(A)',advance="no") repeat(console%LINE_DOWN,n)//console%LINE_RESET
+ write(stdout,'(A)',advance="no") repeat(LINE_DOWN,n)//LINE_RESET
!$omp end critical
diff --git a/src/fpm_backend_output.f90 b/src/fpm_backend_output.f90
index 2cc8597..3f297f7 100644
--- a/src/fpm_backend_output.f90
+++ b/src/fpm_backend_output.f90
@@ -13,8 +13,7 @@ module fpm_backend_output
use iso_fortran_env, only: stdout=>output_unit
use fpm_filesystem, only: basename
use fpm_targets, only: build_target_ptr
-use fpm_backend_console, only: console_t
-use M_attr, only: attr, attr_mode
+use fpm_backend_console, only: console_t, LINE_RESET, COLOR_RED, COLOR_GREEN, COLOR_YELLOW, COLOR_RESET
implicit none
private
@@ -58,14 +57,6 @@ contains
logical, intent(in), optional :: plain_mode
!> Progress object to initialise
type(build_progress_t) :: progress
-
- if (plain_mode) then
- call attr_mode('plain')
- else
- call attr_mode('color')
- end if
-
- progress%console = console_t(plain_mode)
progress%n_target = size(target_queue,1)
progress%target_queue => target_queue
@@ -105,7 +96,8 @@ contains
else ! Pretty output
- write(output_string,'(A,T40,A,A)') target_name,attr('<yellow>compiling...</yellow>')
+ write(output_string,'(A,T40,A,A)') target_name, COLOR_YELLOW//'compiling...'//COLOR_RESET
+
call progress%console%write_line(trim(output_string),progress%output_lines(queue_index))
call progress%console%write_line(trim(overall_progress)//'Compiling...',advance=.false.)
@@ -142,9 +134,9 @@ contains
end if
if (build_stat == 0) then
- write(output_string,'(A,T40,A,A)') target_name,attr('<green>done.</green>')
+ write(output_string,'(A,T40,A,A)') target_name,COLOR_GREEN//'done.'//COLOR_RESET
else
- write(output_string,'(A,T40,A,A)') target_name,attr('<red>failed.</red>')
+ write(output_string,'(A,T40,A,A)') target_name,COLOR_RED//'failed.'//COLOR_RESET
end if
write(overall_progress,'(A,I4,A)') '[',100*progress%n_complete/progress%n_target,'%] '
@@ -173,11 +165,11 @@ contains
if (progress%plain_mode) then ! Plain output
- write(*,'(A)') attr('<green>[100%] Project compiled successfully.</green>')
+ write(*,'(A)') '[100%] Project compiled successfully.'
else ! Pretty output
- write(*,'(A)') progress%console%LINE_RESET//attr('<green>[100%] Project compiled successfully.</green>')
+ write(*,'(A)') LINE_RESET//COLOR_GREEN//'[100%] Project compiled successfully.'//COLOR_RESET
end if