aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorLaurence Kedward <laurence.kedward@bristol.ac.uk>2021-11-27 17:35:12 +0000
committerLaurence Kedward <laurence.kedward@bristol.ac.uk>2021-11-27 17:35:12 +0000
commit93b629e504900432ea712cc3ed65dd937483e1c1 (patch)
tree61b56ecf7e8758620ab262c03a9be7d7867257d5
parent37ba9d7cf61d6b9ddbfe59a4456311fda62ef101 (diff)
downloadfpm-93b629e504900432ea712cc3ed65dd937483e1c1.tar.gz
fpm-93b629e504900432ea712cc3ed65dd937483e1c1.zip
Add: developer documentation to new files
-rw-r--r--src/fpm_backend_console.f9031
-rw-r--r--src/fpm_backend_output.f9058
-rw-r--r--src/fpm_environment.f907
-rw-r--r--src/ptycheck/isatty.c7
4 files changed, 81 insertions, 22 deletions
diff --git a/src/fpm_backend_console.f90 b/src/fpm_backend_console.f90
index 7daff14..4422037 100644
--- a/src/fpm_backend_console.f90
+++ b/src/fpm_backend_console.f90
@@ -1,3 +1,13 @@
+!># Build Backend Console
+!> This module provides a lightweight implementation for printing to the console
+!> and updating previously-printed console lines. It used by `[[fpm_backend_output]]`
+!> for pretty-printing build status and progress.
+!>
+!> @note The implementation for updating previous lines relies on no other output
+!> going to `stdout`/`stderr` except through the `console_t` object provided.
+!>
+!> @note All write statements to `stdout` are enclosed within OpenMP `critical` regions
+!>
module fpm_backend_console
use iso_fortran_env, only: stdout=>output_unit
implicit none
@@ -7,22 +17,34 @@ public :: console_t
character(len=*), parameter :: ESC = char(27)
+!> 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
+ !> Initialise the console object
procedure :: init => console_init
+ !> Write a single line to the console
procedure :: write_line => console_write_line
+ !> Update a previously-written console line
procedure :: update_line => console_update_line
end type console_t
contains
+!> Initialise the console object
subroutine console_init(console,plain_mode)
+ !> Console object to initialise
class(console_t), intent(out), target :: console
+ !> 'Plain' output (no escape codes)
logical, intent(in), optional :: plain_mode
if (present(plain_mode)) then
@@ -41,10 +63,15 @@ subroutine console_init(console,plain_mode)
end subroutine console_init
+!> Write a single line to the standard output
subroutine console_write_line(console,str,line,advance)
+ !> Console object
class(console_t), intent(inout), target :: console
+ !> String to write
character(*), intent(in) :: str
+ !> Integer needed to later update console line
integer, intent(out), optional :: line
+ !> Advancing output (print newline?)
logical, intent(in), optional :: advance
character(3) :: adv
@@ -72,9 +99,13 @@ subroutine console_write_line(console,str,line,advance)
end subroutine console_write_line
+!> Overwrite a previously-written line in standard output
subroutine console_update_line(console,line_no,str)
+ !> Console object
class(console_t), intent(in) :: console
+ !> Integer output from `[[console_write_line]]`
integer, intent(in) :: line_no
+ !> New string to overwrite line
character(*), intent(in) :: str
integer :: n
diff --git a/src/fpm_backend_output.f90 b/src/fpm_backend_output.f90
index 4eb2889..8c7fd7d 100644
--- a/src/fpm_backend_output.f90
+++ b/src/fpm_backend_output.f90
@@ -1,3 +1,14 @@
+!># Build Backend Progress Output
+!> This module provides a derived type `build_progress_t` for printing build status
+!> and progress messages to the console while the backend is building the package.
+!>
+!> The `build_progress_t` type supports two modes: `normal` and `plain`
+!> where the former does 'pretty' output and the latter does not.
+!> The `normal` mode is intended for typical interactive usage whereas
+!> 'plain' mode is used with the `--verbose` flag or when `stdout` is not attached
+!> to a terminal (e.g. when piping or redirecting `stdout`). In these cases,
+!> the pretty output must be suppressed to avoid control codes being output.
+
module fpm_backend_output
use iso_fortran_env, only: stdout=>output_unit
use fpm_filesystem, only: basename
@@ -6,33 +17,43 @@ use fpm_backend_console, only: console_t
use M_attr, only: attr, attr_mode
implicit none
-type build_progress_t
+private
+public build_progress_t
+!> Build progress object
+type build_progress_t
+ !> Console object for updating console lines
type(console_t) :: console
-
+ !> Number of completed targets
integer :: n_complete
-
+ !> Total number of targets scheduled
integer :: n_target
-
+ !> 'Plain' output (no colors or updating)
logical :: plain_mode = .true.
-
+ !> Store needed when updating previous console lines
integer, allocatable :: output_lines(:)
-
+ !> Queue of scheduled build targets
type(build_target_ptr), pointer :: target_queue(:)
-
contains
+ !> Initialise build progress object
procedure :: init => output_init
+ !> Output 'compiling' status for build target
procedure :: compiling_status => output_status_compiling
+ !> Output 'complete' status for build target
procedure :: completed_status => output_status_complete
+ !> Output finished status for whole package
procedure :: success => output_progress_success
-
end type build_progress_t
contains
+ !> Initialise build progress object
subroutine output_init(progress,target_queue,plain_mode)
+ !> Progress object to initialise
class(build_progress_t), intent(out) :: progress
+ !> The queue of scheduled targets
type(build_target_ptr), intent(in), target :: target_queue(:)
+ !> Enable 'plain' output for progress object
logical, intent(in), optional :: plain_mode
if (plain_mode) then
@@ -51,8 +72,11 @@ contains
end subroutine output_init
+ !> Output 'compiling' status for build target and overall percentage progress
subroutine output_status_compiling(progress, queue_index)
+ !> Progress object
class(build_progress_t), intent(inout) :: progress
+ !> Index of build target in the target queue
integer, intent(in) :: queue_index
character(:), allocatable :: target_name
@@ -69,13 +93,13 @@ contains
write(overall_progress,'(A,I4,A)') '[',100*progress%n_complete/progress%n_target,'%]'
- if (progress%plain_mode) then
+ if (progress%plain_mode) then ! Plain output
!$omp critical
write(*,'(A8,A30)') trim(overall_progress),target_name
!$omp end critical
- else
+ else ! Pretty output
write(output_string,'(A,T40,A,A)') target_name,attr('<yellow>compiling...</yellow>')
call progress%console%write_line(trim(output_string),progress%output_lines(queue_index))
@@ -88,10 +112,13 @@ contains
end subroutine output_status_compiling
-
+ !> Output 'complete' status for build target and update overall percentage progress
subroutine output_status_complete(progress, queue_index, build_stat)
+ !> Progress object
class(build_progress_t), intent(inout) :: progress
+ !> Index of build target in the target queue
integer, intent(in) :: queue_index
+ !> Build status flag
integer, intent(in) :: build_stat
character(:), allocatable :: target_name
@@ -118,13 +145,13 @@ contains
write(overall_progress,'(A,I4,A)') '[',100*progress%n_complete/progress%n_target,'%] '
- if (progress%plain_mode) then
+ if (progress%plain_mode) then ! Plain output
!$omp critical
write(*,'(A8,A30,A7)') trim(overall_progress),target_name, 'done.'
!$omp end critical
- else
+ else ! Pretty output
call progress%console%update_line(progress%output_lines(queue_index),trim(output_string))
@@ -136,14 +163,15 @@ contains
end subroutine output_status_complete
+ !> Output finished status for whole package
subroutine output_progress_success(progress)
class(build_progress_t), intent(inout) :: progress
- if (progress%plain_mode) then
+ if (progress%plain_mode) then ! Plain output
write(*,'(A)') attr('<green>[100%] Project compiled successfully.</green>')
- else
+ else ! Pretty output
write(*,'(A)') progress%console%LINE_RESET//attr('<green>[100%] Project compiled successfully.</green>')
diff --git a/src/fpm_environment.f90 b/src/fpm_environment.f90
index e8534ac..224d2aa 100644
--- a/src/fpm_environment.f90
+++ b/src/fpm_environment.f90
@@ -198,13 +198,6 @@ contains
end if
end if
end if
-
-
- if(present(redirect))then
- verbose_local=verbose
- else
- verbose_local=.true.
- end if
if(echo_local) print *, '+ ', cmd
diff --git a/src/ptycheck/isatty.c b/src/ptycheck/isatty.c
index 61acee6..9b7f519 100644
--- a/src/ptycheck/isatty.c
+++ b/src/ptycheck/isatty.c
@@ -1,10 +1,17 @@
+// This file provides a `c_isatty` wrapper function to check if `stdout` is connected
+// to a terminal or not. This wrapper is required for better portability, specifically
+// for supporting the MS Windows command prompt and the MinTTY terminal used by MSYS2.
+
#include <unistd.h> //for isatty()
#include <stdio.h> //for fileno()
#ifdef __MINGW64__
+// ptycheck/iscygpty allows us to check if connected to MinTTY in MSYS2 on Windows
#include "iscygpty.h"
#endif
+// Check if `stdout` is connected to a terminal
+// Returns 1 if is a terminal, and 0 otherwise
int c_isatty(void)
{