{-# LANGUAGE MultiWayIf #-}
{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
module Test.Sandwich.Formatters.TerminalUI.Draw.TopBox (
topBox
) where
import Brick
import qualified Brick.Widgets.List as L
import Control.Monad.Logger
import qualified Data.List as L
import Data.Maybe
import Lens.Micro
import Test.Sandwich.Formatters.TerminalUI.AttrMap
import Test.Sandwich.Formatters.TerminalUI.Keys
import Test.Sandwich.Formatters.TerminalUI.Types
import Test.Sandwich.RunTree
import Test.Sandwich.Types.RunTree
import Test.Sandwich.Types.Spec
topBox :: AppState -> Widget n
topBox AppState
app = [Widget n] -> Widget n
forall n. [Widget n] -> Widget n
hBox [Widget n -> Widget n
forall {n}. Widget n -> Widget n
columnPadding Widget n
forall {n}. Widget n
settingsColumn
, Widget n -> Widget n
forall {n}. Widget n -> Widget n
columnPadding Widget n
forall {n}. Widget n
actionsColumn
, Widget n -> Widget n
forall {n}. Widget n -> Widget n
columnPadding Widget n
forall {n}. Widget n
otherActionsColumn]
where
settingsColumn :: Widget n
settingsColumn = [Widget n] -> Widget n
forall n. [Widget n] -> Widget n
keybindingBox [String -> String -> Widget n
forall {n}. String -> String -> Widget n
keyIndicator (Char -> String -> String
forall a. a -> [a] -> [a]
L.intersperse Char
'/' [Key -> Char
unKChar Key
nextKey, Key -> Char
unKChar Key
previousKey, Char
'↑', Char
'↓']) String
"Navigate"
, AppState -> String -> String -> Widget n
forall {n}. AppState -> String -> String -> Widget n
keyIndicatorHasSelected AppState
app ([Key] -> String
showKeys [Key]
toggleKeys) String
"Open/close node"
, AppState -> String -> String -> Widget n
forall {n}. AppState -> String -> String -> Widget n
keyIndicatorHasSelectedOpen AppState
app String
"Control-v/Meta-v" String
"Scroll node"
, AppState -> String -> String -> Widget n
forall {n}. AppState -> String -> String -> Widget n
keyIndicatorHasSelected AppState
app (Key -> Char
unKChar Key
closeNodeKey Char -> String -> String
forall a. a -> [a] -> [a]
: Char
'/' Char -> String -> String
forall a. a -> [a] -> [a]
: [Key -> Char
unKChar Key
openNodeKey]) String
"Fold/unfold node"
, String -> String -> Widget n
forall {n}. String -> String -> Widget n
keyIndicator String
"Meta + [0-9]" String
"Unfold top # nodes"
, String -> String -> Widget n
forall {n}. String -> String -> Widget n
keyIndicator (Key -> Char
unKChar Key
nextFailureKey Char -> String -> String
forall a. a -> [a] -> [a]
: Char
'/' Char -> String -> String
forall a. a -> [a] -> [a]
: [Key -> Char
unKChar Key
previousFailureKey]) String
"Next/previous failure"
]
actionsColumn :: Widget n
actionsColumn = [Widget n] -> Widget n
forall n. [Widget n] -> Widget n
keybindingBox [[Widget n] -> Widget n
forall n. [Widget n] -> Widget n
hBox [String -> Widget n
forall n. String -> Widget n
str String
"["
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightKeyIfPredicate AppState -> Bool
selectedTestRunning AppState
app (String -> Widget n
forall n. String -> Widget n
str (String -> Widget n) -> String -> Widget n
forall a b. (a -> b) -> a -> b
$ Key -> String
showKey Key
cancelSelectedKey)
, String -> Widget n
forall n. String -> Widget n
str String
"/"
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightKeyIfPredicate AppState -> Bool
someTestRunning AppState
app (String -> Widget n
forall n. String -> Widget n
str (String -> Widget n) -> String -> Widget n
forall a b. (a -> b) -> a -> b
$ Key -> String
showKey Key
cancelAllKey)
, String -> Widget n
forall n. String -> Widget n
str String
"] "
, AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
hotkeyMessageAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ String -> Widget n
forall n. String -> Widget n
str String
"Cancel "
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightMessageIfPredicate AppState -> Bool
selectedTestRunning AppState
app (String -> Widget n
forall n. String -> Widget n
str String
"selected")
, String -> Widget n
forall n. String -> Widget n
str String
"/"
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightMessageIfPredicate AppState -> Bool
someTestRunning AppState
app (String -> Widget n
forall n. String -> Widget n
str String
"all")
]
, [Widget n] -> Widget n
forall n. [Widget n] -> Widget n
hBox [String -> Widget n
forall n. String -> Widget n
str String
"["
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightKeyIfPredicate AppState -> Bool
selectedTestDone AppState
app (String -> Widget n
forall n. String -> Widget n
str (String -> Widget n) -> String -> Widget n
forall a b. (a -> b) -> a -> b
$ Key -> String
showKey Key
runSelectedKey)
, String -> Widget n
forall n. String -> Widget n
str String
"/"
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightKeyIfPredicate AppState -> Bool
noTestsRunning AppState
app (String -> Widget n
forall n. String -> Widget n
str (String -> Widget n) -> String -> Widget n
forall a b. (a -> b) -> a -> b
$ Key -> String
showKey Key
runAllKey)
, String -> Widget n
forall n. String -> Widget n
str String
"] "
, AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
hotkeyMessageAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ String -> Widget n
forall n. String -> Widget n
str String
"Run "
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightMessageIfPredicate AppState -> Bool
selectedTestDone AppState
app (String -> Widget n
forall n. String -> Widget n
str String
"selected")
, String -> Widget n
forall n. String -> Widget n
str String
"/"
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightMessageIfPredicate AppState -> Bool
noTestsRunning AppState
app (String -> Widget n
forall n. String -> Widget n
str String
"all")
]
, [Widget n] -> Widget n
forall n. [Widget n] -> Widget n
hBox [String -> Widget n
forall n. String -> Widget n
str String
"["
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightKeyIfPredicate AppState -> Bool
selectedTestDone AppState
app (String -> Widget n
forall n. String -> Widget n
str (String -> Widget n) -> String -> Widget n
forall a b. (a -> b) -> a -> b
$ Key -> String
showKey Key
clearSelectedKey)
, String -> Widget n
forall n. String -> Widget n
str String
"/"
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightKeyIfPredicate AppState -> Bool
allTestsDone AppState
app (String -> Widget n
forall n. String -> Widget n
str (String -> Widget n) -> String -> Widget n
forall a b. (a -> b) -> a -> b
$ Key -> String
showKey Key
clearAllKey)
, String -> Widget n
forall n. String -> Widget n
str String
"] "
, AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
hotkeyMessageAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ String -> Widget n
forall n. String -> Widget n
str String
"Clear "
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightMessageIfPredicate AppState -> Bool
selectedTestDone AppState
app (String -> Widget n
forall n. String -> Widget n
str String
"selected")
, String -> Widget n
forall n. String -> Widget n
str String
"/"
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightMessageIfPredicate AppState -> Bool
allTestsDone AppState
app (String -> Widget n
forall n. String -> Widget n
str String
"all")
]
, [Widget n] -> Widget n
forall n. [Widget n] -> Widget n
hBox [String -> Widget n
forall n. String -> Widget n
str String
"["
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightKeyIfPredicate AppState -> Bool
someTestSelected AppState
app (String -> Widget n
forall n. String -> Widget n
str (String -> Widget n) -> String -> Widget n
forall a b. (a -> b) -> a -> b
$ Key -> String
showKey Key
openSelectedFolderInFileExplorer)
, String -> Widget n
forall n. String -> Widget n
str String
"/"
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightKeyIfPredicate (Bool -> AppState -> Bool
forall a b. a -> b -> a
const Bool
True) AppState
app (String -> Widget n
forall n. String -> Widget n
str (String -> Widget n) -> String -> Widget n
forall a b. (a -> b) -> a -> b
$ Key -> String
showKey Key
openTestRootKey)
, String -> Widget n
forall n. String -> Widget n
str String
"] "
, AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
hotkeyMessageAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ String -> Widget n
forall n. String -> Widget n
str String
"Open "
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightMessageIfPredicate AppState -> Bool
someTestSelected AppState
app (String -> Widget n
forall n. String -> Widget n
str String
"selected")
, String -> Widget n
forall n. String -> Widget n
str String
"/"
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightMessageIfPredicate (Bool -> AppState -> Bool
forall a b. a -> b -> a
const Bool
True) AppState
app (String -> Widget n
forall n. String -> Widget n
str String
"root")
, AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
hotkeyMessageAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ String -> Widget n
forall n. String -> Widget n
str String
" folder"
]
, [Widget n] -> Widget n
forall n. [Widget n] -> Widget n
hBox [String -> Widget n
forall n. String -> Widget n
str String
"["
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightKeyIfPredicate AppState -> Bool
someTestSelected AppState
app (String -> Widget n
forall n. String -> Widget n
str (String -> Widget n) -> String -> Widget n
forall a b. (a -> b) -> a -> b
$ Key -> String
showKey Key
openTestInEditorKey)
, String -> Widget n
forall n. String -> Widget n
str String
"/"
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightKeyIfPredicate AppState -> Bool
someTestSelected AppState
app (String -> Widget n
forall n. String -> Widget n
str (String -> Widget n) -> String -> Widget n
forall a b. (a -> b) -> a -> b
$ Key -> String
showKey Key
openLogsInEditorKey)
, String -> Widget n
forall n. String -> Widget n
str String
"/"
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightKeyIfPredicate AppState -> Bool
someTestSelected AppState
app (String -> Widget n
forall n. String -> Widget n
str (String -> Widget n) -> String -> Widget n
forall a b. (a -> b) -> a -> b
$ Key -> String
showKey Key
openFailureInEditorKey)
, String -> Widget n
forall n. String -> Widget n
str String
"] "
, AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
hotkeyMessageAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ String -> Widget n
forall n. String -> Widget n
str String
"Edit "
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightMessageIfPredicate AppState -> Bool
someTestSelected AppState
app (String -> Widget n
forall n. String -> Widget n
str String
"test")
, String -> Widget n
forall n. String -> Widget n
str String
"/"
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightMessageIfPredicate AppState -> Bool
someTestSelected AppState
app (String -> Widget n
forall n. String -> Widget n
str String
"logs")
, String -> Widget n
forall n. String -> Widget n
str String
"/"
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightMessageIfPredicate AppState -> Bool
selectedTestHasCallStack AppState
app (String -> Widget n
forall n. String -> Widget n
str String
"failure")
]
]
otherActionsColumn :: Widget n
otherActionsColumn = [Widget n] -> Widget n
forall n. [Widget n] -> Widget n
keybindingBox [String -> Widget n -> Widget n
forall {n}. String -> Widget n -> Widget n
keyIndicator' (Key -> String
showKey Key
cycleVisibilityThresholdKey) (AppState -> Widget n
forall {n}. AppState -> Widget n
visibilityThresholdWidget AppState
app)
, [Widget n] -> Widget n
forall n. [Widget n] -> Widget n
hBox [String -> Widget n
forall n. String -> Widget n
str String
"["
, String -> Widget n
forall n. String -> Widget n
str (String -> Widget n) -> String -> Widget n
forall a b. (a -> b) -> a -> b
$ Key -> String
showKey Key
toggleShowRunTimesKey
, String -> Widget n
forall n. String -> Widget n
str String
"/"
, String -> Widget n
forall n. String -> Widget n
str (String -> Widget n) -> String -> Widget n
forall a b. (a -> b) -> a -> b
$ Key -> String
showKey Key
toggleFileLocationsKey
, String -> Widget n
forall n. String -> Widget n
str String
"/"
, String -> Widget n
forall n. String -> Widget n
str (String -> Widget n) -> String -> Widget n
forall a b. (a -> b) -> a -> b
$ Key -> String
showKey Key
toggleVisibilityThresholdsKey
, String -> Widget n
forall n. String -> Widget n
str String
"] "
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightMessageIfPredicate (AppState -> Getting Bool AppState Bool -> Bool
forall s a. s -> Getting a s a -> a
^. Getting Bool AppState Bool
Lens' AppState Bool
appShowRunTimes) AppState
app (String -> Widget n
forall n. String -> Widget n
str String
"Times")
, String -> Widget n
forall n. String -> Widget n
str String
"/"
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightMessageIfPredicate (AppState -> Getting Bool AppState Bool -> Bool
forall s a. s -> Getting a s a -> a
^. Getting Bool AppState Bool
Lens' AppState Bool
appShowFileLocations) AppState
app (String -> Widget n
forall n. String -> Widget n
str String
"locations")
, String -> Widget n
forall n. String -> Widget n
str String
"/"
, (AppState -> Bool) -> AppState -> Widget n -> Widget n
forall {t} {n}. (t -> Bool) -> t -> Widget n -> Widget n
highlightMessageIfPredicate (AppState -> Getting Bool AppState Bool -> Bool
forall s a. s -> Getting a s a -> a
^. Getting Bool AppState Bool
Lens' AppState Bool
appShowVisibilityThresholds) AppState
app (String -> Widget n
forall n. String -> Widget n
str String
"thresholds")
]
, [Widget n] -> Widget n
forall n. [Widget n] -> Widget n
hBox [String -> Widget n
forall n. String -> Widget n
str String
"["
, AppState -> LogLevel -> String -> Widget n
forall {n}. AppState -> LogLevel -> String -> Widget n
highlightIfLogLevel AppState
app LogLevel
LevelDebug [Key -> Char
unKChar Key
debugKey]
, String -> Widget n
forall n. String -> Widget n
str String
"/"
, AppState -> LogLevel -> String -> Widget n
forall {n}. AppState -> LogLevel -> String -> Widget n
highlightIfLogLevel AppState
app LogLevel
LevelInfo [Key -> Char
unKChar Key
infoKey]
, String -> Widget n
forall n. String -> Widget n
str String
"/"
, AppState -> LogLevel -> String -> Widget n
forall {n}. AppState -> LogLevel -> String -> Widget n
highlightIfLogLevel AppState
app LogLevel
LevelWarn [Key -> Char
unKChar Key
warnKey]
, String -> Widget n
forall n. String -> Widget n
str String
"/"
, AppState -> LogLevel -> String -> Widget n
forall {n}. AppState -> LogLevel -> String -> Widget n
highlightIfLogLevel AppState
app LogLevel
LevelError [Key -> Char
unKChar Key
errorKey]
, String -> Widget n
forall n. String -> Widget n
str String
"] "
, String -> Widget n
forall n. String -> Widget n
str String
"Log level"]
, String -> String -> Widget n
forall {n}. String -> String -> Widget n
keyIndicator String
"q" String
"Exit"]
visibilityThresholdWidget :: AppState -> Widget n
visibilityThresholdWidget AppState
app = [Widget n] -> Widget n
forall n. [Widget n] -> Widget n
hBox ([Widget n] -> Widget n) -> [Widget n] -> Widget n
forall a b. (a -> b) -> a -> b
$
[AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
hotkeyMessageAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ String -> Widget n
forall n. String -> Widget n
str String
"Visibility threshold ("]
[Widget n] -> [Widget n] -> [Widget n]
forall a. Semigroup a => a -> a -> a
<> Widget n -> [Widget n] -> [Widget n]
forall a. a -> [a] -> [a]
L.intersperse (String -> Widget n
forall n. String -> Widget n
str String
", ") [AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr (if Int
x Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== AppState
app AppState -> Getting Int AppState Int -> Int
forall s a. s -> Getting a s a -> a
^. Getting Int AppState Int
Lens' AppState Int
appVisibilityThreshold then AttrName
visibilityThresholdSelectedAttr else AttrName
visibilityThresholdNotSelectedAttr) (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ String -> Widget n
forall n. String -> Widget n
str (String -> Widget n) -> String -> Widget n
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show Int
x | Int
x <- (AppState
app AppState -> Getting [Int] AppState [Int] -> [Int]
forall s a. s -> Getting a s a -> a
^. Getting [Int] AppState [Int]
Lens' AppState [Int]
appVisibilityThresholdSteps)]
[Widget n] -> [Widget n] -> [Widget n]
forall a. Semigroup a => a -> a -> a
<> [(String -> Widget n
forall n. String -> Widget n
str String
")")]
columnPadding :: Widget n -> Widget n
columnPadding = Padding -> Widget n -> Widget n
forall n. Padding -> Widget n -> Widget n
padLeft (Int -> Padding
Pad Int
1) (Widget n -> Widget n)
-> (Widget n -> Widget n) -> Widget n -> Widget n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Padding -> Widget n -> Widget n
forall n. Padding -> Widget n -> Widget n
padRight (Int -> Padding
Pad Int
3)
keybindingBox :: [Widget n] -> Widget n
keybindingBox = [Widget n] -> Widget n
forall n. [Widget n] -> Widget n
vBox
highlightIfLogLevel :: AppState -> LogLevel -> String -> Widget n
highlightIfLogLevel AppState
app LogLevel
desiredLevel String
thing =
if | AppState
app AppState
-> Getting (Maybe LogLevel) AppState (Maybe LogLevel)
-> Maybe LogLevel
forall s a. s -> Getting a s a -> a
^. Getting (Maybe LogLevel) AppState (Maybe LogLevel)
Lens' AppState (Maybe LogLevel)
appLogLevel Maybe LogLevel -> Maybe LogLevel -> Bool
forall a. Eq a => a -> a -> Bool
== LogLevel -> Maybe LogLevel
forall a. a -> Maybe a
Just LogLevel
desiredLevel -> AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
visibilityThresholdSelectedAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ String -> Widget n
forall n. String -> Widget n
str String
thing
| Bool
otherwise -> AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
hotkeyAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ String -> Widget n
forall n. String -> Widget n
str String
thing
highlightKeyIfPredicate :: (t -> Bool) -> t -> Widget n -> Widget n
highlightKeyIfPredicate t -> Bool
p t
app Widget n
x = case t -> Bool
p t
app of
Bool
True -> AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
hotkeyAttr Widget n
x
Bool
False -> AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
disabledHotkeyAttr Widget n
x
highlightMessageIfPredicate :: (t -> Bool) -> t -> Widget n -> Widget n
highlightMessageIfPredicate t -> Bool
p t
app Widget n
x = case t -> Bool
p t
app of
Bool
True -> AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
hotkeyMessageAttr Widget n
x
Bool
False -> AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
disabledHotkeyMessageAttr Widget n
x
keyIndicator :: String -> String -> Widget n
keyIndicator String
key String
msg = String -> Widget n -> Widget n
forall {n}. String -> Widget n -> Widget n
keyIndicator' String
key (AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
hotkeyMessageAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ String -> Widget n
forall n. String -> Widget n
str String
msg)
keyIndicator' :: String -> Widget n -> Widget n
keyIndicator' String
key Widget n
label = [Widget n] -> Widget n
forall n. [Widget n] -> Widget n
hBox [String -> Widget n
forall n. String -> Widget n
str String
"[", AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
hotkeyAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ String -> Widget n
forall n. String -> Widget n
str String
key, String -> Widget n
forall n. String -> Widget n
str String
"] ", Widget n
label]
keyIndicatorHasSelected :: AppState -> String -> String -> Widget n
keyIndicatorHasSelected AppState
app = AppState -> (AppState -> Bool) -> String -> String -> Widget n
forall {t} {n}. t -> (t -> Bool) -> String -> String -> Widget n
keyIndicatorContextual AppState
app AppState -> Bool
someTestSelected
keyIndicatorHasSelectedOpen :: AppState -> String -> String -> Widget n
keyIndicatorHasSelectedOpen AppState
app = AppState -> (AppState -> Bool) -> String -> String -> Widget n
forall {t} {n}. t -> (t -> Bool) -> String -> String -> Widget n
keyIndicatorContextual AppState
app AppState -> Bool
selectedTestToggled
keyIndicatorContextual :: t -> (t -> Bool) -> String -> String -> Widget n
keyIndicatorContextual t
app t -> Bool
p String
key String
msg = case t -> Bool
p t
app of
Bool
True -> [Widget n] -> Widget n
forall n. [Widget n] -> Widget n
hBox [String -> Widget n
forall n. String -> Widget n
str String
"[", AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
hotkeyAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ String -> Widget n
forall n. String -> Widget n
str String
key, String -> Widget n
forall n. String -> Widget n
str String
"] ", AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
hotkeyMessageAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ String -> Widget n
forall n. String -> Widget n
str String
msg]
Bool
False -> [Widget n] -> Widget n
forall n. [Widget n] -> Widget n
hBox [String -> Widget n
forall n. String -> Widget n
str String
"[", AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
disabledHotkeyAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ String -> Widget n
forall n. String -> Widget n
str String
key, String -> Widget n
forall n. String -> Widget n
str String
"] ", AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
disabledHotkeyMessageAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ String -> Widget n
forall n. String -> Widget n
str String
msg]
selectedTestRunning :: AppState -> Bool
selectedTestRunning AppState
s = case GenericList ClickableName Vector MainListElem
-> Maybe (Int, MainListElem)
forall (t :: * -> *) e n.
(Splittable t, Traversable t, Semigroup (t e)) =>
GenericList n t e -> Maybe (Int, e)
L.listSelectedElement (AppState
s AppState
-> Getting
(GenericList ClickableName Vector MainListElem)
AppState
(GenericList ClickableName Vector MainListElem)
-> GenericList ClickableName Vector MainListElem
forall s a. s -> Getting a s a -> a
^. Getting
(GenericList ClickableName Vector MainListElem)
AppState
(GenericList ClickableName Vector MainListElem)
Lens' AppState (GenericList ClickableName Vector MainListElem)
appMainList) of
Maybe (Int, MainListElem)
Nothing -> Bool
False
Just (Int
_, MainListElem {Bool
Int
String
Maybe String
Seq LogEntry
RunNodeCommon
Status
label :: String
depth :: Int
toggled :: Bool
open :: Bool
status :: Status
logs :: Seq LogEntry
visibilityLevel :: Int
folderPath :: Maybe String
node :: RunNodeCommon
ident :: Int
label :: MainListElem -> String
depth :: MainListElem -> Int
toggled :: MainListElem -> Bool
open :: MainListElem -> Bool
status :: MainListElem -> Status
logs :: MainListElem -> Seq LogEntry
visibilityLevel :: MainListElem -> Int
folderPath :: MainListElem -> Maybe String
node :: MainListElem -> RunNodeCommon
ident :: MainListElem -> Int
..}) -> Status -> Bool
isRunning Status
status
selectedTestDone :: AppState -> Bool
selectedTestDone AppState
s = case GenericList ClickableName Vector MainListElem
-> Maybe (Int, MainListElem)
forall (t :: * -> *) e n.
(Splittable t, Traversable t, Semigroup (t e)) =>
GenericList n t e -> Maybe (Int, e)
L.listSelectedElement (AppState
s AppState
-> Getting
(GenericList ClickableName Vector MainListElem)
AppState
(GenericList ClickableName Vector MainListElem)
-> GenericList ClickableName Vector MainListElem
forall s a. s -> Getting a s a -> a
^. Getting
(GenericList ClickableName Vector MainListElem)
AppState
(GenericList ClickableName Vector MainListElem)
Lens' AppState (GenericList ClickableName Vector MainListElem)
appMainList) of
Maybe (Int, MainListElem)
Nothing -> Bool
False
Just (Int
_, MainListElem {Bool
Int
String
Maybe String
Seq LogEntry
RunNodeCommon
Status
label :: MainListElem -> String
depth :: MainListElem -> Int
toggled :: MainListElem -> Bool
open :: MainListElem -> Bool
status :: MainListElem -> Status
logs :: MainListElem -> Seq LogEntry
visibilityLevel :: MainListElem -> Int
folderPath :: MainListElem -> Maybe String
node :: MainListElem -> RunNodeCommon
ident :: MainListElem -> Int
label :: String
depth :: Int
toggled :: Bool
open :: Bool
status :: Status
logs :: Seq LogEntry
visibilityLevel :: Int
folderPath :: Maybe String
node :: RunNodeCommon
ident :: Int
..}) -> Status -> Bool
isDone Status
status
selectedTestHasCallStack :: AppState -> Bool
selectedTestHasCallStack AppState
s = case GenericList ClickableName Vector MainListElem
-> Maybe (Int, MainListElem)
forall (t :: * -> *) e n.
(Splittable t, Traversable t, Semigroup (t e)) =>
GenericList n t e -> Maybe (Int, e)
L.listSelectedElement (AppState
s AppState
-> Getting
(GenericList ClickableName Vector MainListElem)
AppState
(GenericList ClickableName Vector MainListElem)
-> GenericList ClickableName Vector MainListElem
forall s a. s -> Getting a s a -> a
^. Getting
(GenericList ClickableName Vector MainListElem)
AppState
(GenericList ClickableName Vector MainListElem)
Lens' AppState (GenericList ClickableName Vector MainListElem)
appMainList) of
Maybe (Int, MainListElem)
Nothing -> Bool
False
Just (Int
_, MainListElem {Bool
Int
String
Maybe String
Seq LogEntry
RunNodeCommon
Status
label :: MainListElem -> String
depth :: MainListElem -> Int
toggled :: MainListElem -> Bool
open :: MainListElem -> Bool
status :: MainListElem -> Status
logs :: MainListElem -> Seq LogEntry
visibilityLevel :: MainListElem -> Int
folderPath :: MainListElem -> Maybe String
node :: MainListElem -> RunNodeCommon
ident :: MainListElem -> Int
label :: String
depth :: Int
toggled :: Bool
open :: Bool
status :: Status
logs :: Seq LogEntry
visibilityLevel :: Int
folderPath :: Maybe String
node :: RunNodeCommon
ident :: Int
..}) -> case Status
status of
(Done UTCTime
_ Maybe UTCTime
_ Maybe UTCTime
_ UTCTime
_ (Failure FailureReason
failureReason)) -> Maybe CallStack -> Bool
forall a. Maybe a -> Bool
isJust (Maybe CallStack -> Bool) -> Maybe CallStack -> Bool
forall a b. (a -> b) -> a -> b
$ FailureReason -> Maybe CallStack
failureCallStack FailureReason
failureReason
Status
_ -> Bool
False
selectedTestToggled :: AppState -> Bool
selectedTestToggled AppState
s = case GenericList ClickableName Vector MainListElem
-> Maybe (Int, MainListElem)
forall (t :: * -> *) e n.
(Splittable t, Traversable t, Semigroup (t e)) =>
GenericList n t e -> Maybe (Int, e)
L.listSelectedElement (AppState
s AppState
-> Getting
(GenericList ClickableName Vector MainListElem)
AppState
(GenericList ClickableName Vector MainListElem)
-> GenericList ClickableName Vector MainListElem
forall s a. s -> Getting a s a -> a
^. Getting
(GenericList ClickableName Vector MainListElem)
AppState
(GenericList ClickableName Vector MainListElem)
Lens' AppState (GenericList ClickableName Vector MainListElem)
appMainList) of
Maybe (Int, MainListElem)
Nothing -> Bool
False
Just (Int
_, MainListElem {Bool
Int
String
Maybe String
Seq LogEntry
RunNodeCommon
Status
label :: MainListElem -> String
depth :: MainListElem -> Int
toggled :: MainListElem -> Bool
open :: MainListElem -> Bool
status :: MainListElem -> Status
logs :: MainListElem -> Seq LogEntry
visibilityLevel :: MainListElem -> Int
folderPath :: MainListElem -> Maybe String
node :: MainListElem -> RunNodeCommon
ident :: MainListElem -> Int
label :: String
depth :: Int
toggled :: Bool
open :: Bool
status :: Status
logs :: Seq LogEntry
visibilityLevel :: Int
folderPath :: Maybe String
node :: RunNodeCommon
ident :: Int
..}) -> Bool
toggled
noTestsRunning :: AppState -> Bool
noTestsRunning AppState
s = (RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool -> Bool)
-> [RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool]
-> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Bool -> Bool
not (Bool -> Bool)
-> (RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool
-> Bool)
-> RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Status -> Bool
isRunning (Status -> Bool)
-> (RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool
-> Status)
-> RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RunNodeCommonWithStatus Status (Seq LogEntry) Bool -> Status
forall s l t. RunNodeCommonWithStatus s l t -> s
runTreeStatus (RunNodeCommonWithStatus Status (Seq LogEntry) Bool -> Status)
-> (RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool
-> RunNodeCommonWithStatus Status (Seq LogEntry) Bool)
-> RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool
-> Status
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool
-> RunNodeCommonWithStatus Status (Seq LogEntry) Bool
forall s l t context.
RunNodeWithStatus context s l t -> RunNodeCommonWithStatus s l t
runNodeCommon) (AppState
s AppState
-> Getting
[RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool]
AppState
[RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool]
-> [RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool]
forall s a. s -> Getting a s a -> a
^. Getting
[RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool]
AppState
[RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool]
Lens'
AppState [RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool]
appRunTree)
someTestRunning :: AppState -> Bool
someTestRunning AppState
s = (RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool -> Bool)
-> [RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool]
-> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Status -> Bool
isRunning (Status -> Bool)
-> (RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool
-> Status)
-> RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RunNodeCommonWithStatus Status (Seq LogEntry) Bool -> Status
forall s l t. RunNodeCommonWithStatus s l t -> s
runTreeStatus (RunNodeCommonWithStatus Status (Seq LogEntry) Bool -> Status)
-> (RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool
-> RunNodeCommonWithStatus Status (Seq LogEntry) Bool)
-> RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool
-> Status
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool
-> RunNodeCommonWithStatus Status (Seq LogEntry) Bool
forall s l t context.
RunNodeWithStatus context s l t -> RunNodeCommonWithStatus s l t
runNodeCommon) (AppState
s AppState
-> Getting
[RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool]
AppState
[RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool]
-> [RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool]
forall s a. s -> Getting a s a -> a
^. Getting
[RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool]
AppState
[RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool]
Lens'
AppState [RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool]
appRunTree)
allTestsDone :: AppState -> Bool
allTestsDone AppState
s = (RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool -> Bool)
-> [RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool]
-> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Status -> Bool
isDone (Status -> Bool)
-> (RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool
-> Status)
-> RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RunNodeCommonWithStatus Status (Seq LogEntry) Bool -> Status
forall s l t. RunNodeCommonWithStatus s l t -> s
runTreeStatus (RunNodeCommonWithStatus Status (Seq LogEntry) Bool -> Status)
-> (RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool
-> RunNodeCommonWithStatus Status (Seq LogEntry) Bool)
-> RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool
-> Status
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool
-> RunNodeCommonWithStatus Status (Seq LogEntry) Bool
forall s l t context.
RunNodeWithStatus context s l t -> RunNodeCommonWithStatus s l t
runNodeCommon) (AppState
s AppState
-> Getting
[RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool]
AppState
[RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool]
-> [RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool]
forall s a. s -> Getting a s a -> a
^. Getting
[RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool]
AppState
[RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool]
Lens'
AppState [RunNodeWithStatus BaseContext Status (Seq LogEntry) Bool]
appRunTree)
someTestSelected :: AppState -> Bool
someTestSelected AppState
s = Maybe (Int, MainListElem) -> Bool
forall a. Maybe a -> Bool
isJust (Maybe (Int, MainListElem) -> Bool)
-> Maybe (Int, MainListElem) -> Bool
forall a b. (a -> b) -> a -> b
$ GenericList ClickableName Vector MainListElem
-> Maybe (Int, MainListElem)
forall (t :: * -> *) e n.
(Splittable t, Traversable t, Semigroup (t e)) =>
GenericList n t e -> Maybe (Int, e)
L.listSelectedElement (AppState
s AppState
-> Getting
(GenericList ClickableName Vector MainListElem)
AppState
(GenericList ClickableName Vector MainListElem)
-> GenericList ClickableName Vector MainListElem
forall s a. s -> Getting a s a -> a
^. Getting
(GenericList ClickableName Vector MainListElem)
AppState
(GenericList ClickableName Vector MainListElem)
Lens' AppState (GenericList ClickableName Vector MainListElem)
appMainList)