summaryrefslogtreecommitdiff
path: root/src/Output.hs
blob: 7c4a8a5dcc1e281a445b77475b0f3dc9cdd501f8 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
module Output (
    Output, OutputStyle(..), OutputType(..),
    MonadOutput(..),
    startOutput,
    resetOutputTime,
    outLine,
    outPromptGetLine,
    outPromptGetLineCompletion,
) where

import Control.Concurrent.MVar
import Control.Monad.IO.Class
import Control.Monad.Reader

import Data.Text (Text)
import Data.Text qualified as T
import Data.Text.Lazy qualified as TL
import Data.Text.Lazy.IO qualified as TL

import System.Clock
import System.Console.Haskeline
import System.Console.Haskeline.History
import System.IO

import Text.Printf

data Output = Output
    { outState :: MVar OutputState
    , outConfig :: OutputConfig
    , outStartedAt :: MVar TimeSpec
    }

data OutputConfig = OutputConfig
    { outStyle :: OutputStyle
    , outUseColor :: Bool
    }

data OutputState = OutputState
    { outPrint :: TL.Text -> IO ()
    , outHistory :: History
    }

data OutputStyle
    = OutputStyleQuiet
    | OutputStyleVerbose
    | OutputStyleTest
    deriving (Eq)

data OutputType
    = OutputChildStdout
    | OutputChildStderr
    | OutputChildStdin
    | OutputChildInfo
    | OutputChildFail
    | OutputMatch
    | OutputMatchFail
    | OutputError
    | OutputAlways
    | OutputTestRaw

class MonadIO m => MonadOutput m where
    getOutput :: m Output

instance MonadIO m => MonadOutput (ReaderT Output m) where
    getOutput = ask

startOutput :: OutputStyle -> Bool -> IO Output
startOutput outStyle outUseColor = do
    outState <- newMVar OutputState { outPrint = TL.putStrLn, outHistory = emptyHistory }
    outConfig <- pure OutputConfig {..}
    outStartedAt <- newMVar =<< getTime Monotonic
    hSetBuffering stdout LineBuffering
    return Output {..}

resetOutputTime :: Output -> IO ()
resetOutputTime Output {..} = do
    modifyMVar_ outStartedAt . const $ getTime Monotonic

outColor :: OutputType -> Text
outColor OutputChildStdout = T.pack "0"
outColor OutputChildStderr = T.pack "31"
outColor OutputChildStdin = T.pack "0"
outColor OutputChildInfo = T.pack "0"
outColor OutputChildFail = T.pack "31"
outColor OutputMatch = T.pack "32"
outColor OutputMatchFail = T.pack "31"
outColor OutputError = T.pack "31"
outColor OutputAlways = "0"
outColor OutputTestRaw = "0"

outSign :: OutputType -> Text
outSign OutputChildStdout = T.empty
outSign OutputChildStderr = T.pack "!"
outSign OutputChildStdin = T.empty
outSign OutputChildInfo = T.pack "."
outSign OutputChildFail = T.pack "!!"
outSign OutputMatch = T.pack "+"
outSign OutputMatchFail = T.pack "/"
outSign OutputError = T.pack "!!"
outSign OutputAlways = T.empty
outSign OutputTestRaw = T.empty

outArr :: OutputType -> Text
outArr OutputChildStdin = "<"
outArr _ = ">"

outTestLabel :: OutputType -> Text
outTestLabel = \case
    OutputChildStdout -> "child-stdout"
    OutputChildStderr -> "child-stderr"
    OutputChildStdin -> "child-stdin"
    OutputChildInfo -> "child-info"
    OutputChildFail -> "child-fail"
    OutputMatch -> "match"
    OutputMatchFail -> "match-fail"
    OutputError -> "error"
    OutputAlways -> "other"
    OutputTestRaw -> ""

printWhenQuiet :: OutputType -> Bool
printWhenQuiet = \case
    OutputChildStderr -> True
    OutputChildFail -> True
    OutputMatchFail -> True
    OutputError -> True
    OutputAlways -> True
    _ -> False

ioWithOutput :: MonadOutput m => (Output -> IO a) -> m a
ioWithOutput act = liftIO . act =<< getOutput

outLine :: MonadOutput m => OutputType -> Maybe Text -> Text -> m ()
outLine otype prompt line = ioWithOutput $ \out ->
    case outStyle (outConfig out) of
        OutputStyleQuiet
            | printWhenQuiet otype -> normalOutput out
            | otherwise -> return ()
        OutputStyleVerbose -> normalOutput out
        OutputStyleTest -> testOutput out
  where
    normalOutput out = do
        stime <- readMVar (outStartedAt out)
        nsecs <- toNanoSecs . (`diffTimeSpec` stime) <$> getTime Monotonic
        withMVar (outState out) $ \st -> do
            outPrint st $ TL.fromChunks $ concat
                [ [ T.pack $ printf "[% 2d.%03d] " (nsecs `quot` 1000000000) ((nsecs `quot` 1000000) `rem` 1000) ]
                , if outUseColor (outConfig out)
                    then [ T.pack "\ESC[", outColor otype, T.pack "m" ]
                    else []
                , [ maybe "" (<> outSign otype <> outArr otype <> " ") prompt ]
                , [ line ]
                , if outUseColor (outConfig out)
                    then [ T.pack "\ESC[0m" ]
                    else []
                ]

    testOutput out = do
        withMVar (outState out) $ \st -> do
            outPrint st $ case otype of
                OutputTestRaw -> TL.fromStrict line
                _ -> TL.fromChunks
                    [ outTestLabel otype, " "
                    , maybe "-" id prompt, " "
                    , line
                    ]

outPromptGetLine :: MonadOutput m => Text -> m (Maybe Text)
outPromptGetLine = outPromptGetLineCompletion noCompletion

outPromptGetLineCompletion :: MonadOutput m => CompletionFunc IO -> Text -> m (Maybe Text)
outPromptGetLineCompletion compl prompt = ioWithOutput $ \out -> do
    st <- takeMVar (outState out)
    (x, st') <- runInputT (setComplete compl defaultSettings) $ do
        p <- getExternalPrint
        putHistory $ outHistory st
        liftIO $ putMVar (outState out) st { outPrint = p . TL.unpack . (<>"\n") }
        x <- getInputLine $ T.unpack prompt
        st' <- liftIO $ takeMVar (outState out)
        hist' <- getHistory
        return (x, st' { outPrint = outPrint st, outHistory = hist' })
    putMVar (outState out) st'
    return $ fmap T.pack x