{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StrictData #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_HADDOCK prune #-}
module Core.Program.Execute
( Program ()
, configure
, execute
, executeWith
, terminate
, getCommandLine
, queryCommandName
, queryOptionFlag
, queryOptionValue
, queryOptionValue'
, queryArgument
, queryRemaining
, queryEnvironmentValue
, queryEnvironmentValue'
, getProgramName
, setProgramName
, getVerbosityLevel
, setVerbosityLevel
, getConsoleWidth
, getApplicationState
, setApplicationState
, modifyApplicationState
, changeProgram
, outputEntire
, inputEntire
, sleepThread
, resetTimer
, trap_
, catch
, throw
, try
, readProcess
, callProcess
, execProcess_
, Context
, None (..)
, isNone
, unProgram
, invalid
, Boom (..)
, loopForever
, lookupOptionFlag
, lookupOptionValue
, lookupArgument
, lookupEnvironmentValue
, execProcess
)
where
import Control.Concurrent
( forkFinally
, forkIO
, killThread
, myThreadId
, threadDelay
)
import Control.Concurrent.MVar
( MVar
, modifyMVar_
, newMVar
, putMVar
, readMVar
, tryPutMVar
)
import Control.Concurrent.STM (atomically)
import Control.Concurrent.STM.TQueue
( TQueue
, readTQueue
, tryReadTQueue
, unGetTQueue
, writeTQueue
)
import Control.Concurrent.STM.TVar
( readTVarIO
)
import Control.Exception qualified as Base (throwIO)
import Control.Exception.Safe qualified as Safe
( catch
, onException
, throw
)
import Control.Monad
( forM_
, forever
, unless
, void
, when
)
import Control.Monad.Reader.Class (MonadReader (ask))
import Core.Data.Clock
import Core.Data.Structures
import Core.Encoding.External
import Core.Program.Arguments
import Core.Program.Context
import Core.Program.Exceptions
import Core.Program.Logging
import Core.Program.Signal
import Core.System.Base
( Exception
, Handle
, SomeException
, displayException
, hFlush
, liftIO
, stdout
)
import Core.Text.Bytes
import Core.Text.Rope
import Data.ByteString qualified as B (hPut)
import Data.ByteString.Char8 qualified as C (singleton)
import Data.List qualified as List (intersperse)
import GHC.Conc (getNumProcessors, numCapabilities, setNumCapabilities)
import GHC.IO.Encoding (setLocaleEncoding, utf8)
import GHC.Stack (HasCallStack)
import System.Directory
( findExecutable
)
import System.Exit (ExitCode (..))
import System.IO qualified as Base (IOMode (ReadMode), hClose, openFile)
import System.Posix.Internals (hostIsThreaded)
import System.Posix.Process qualified as Posix (executeFile, exitImmediately)
import System.Process qualified as Base
( CreateProcess (std_err, std_in, std_out)
, StdStream (Inherit, UseHandle)
, createProcess
, proc
, terminateProcess
, waitForProcess
)
import System.Process.Typed qualified as Typed (nullStream, proc, readProcess, setStdin)
import Prelude hiding (log)
trap_ :: Program τ α -> Program τ ()
trap_ :: forall τ α. Program τ α -> Program τ ()
trap_ Program τ α
action =
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
Safe.catch
(forall (f :: * -> *) a. Functor f => f a -> f ()
void Program τ α
action)
( \(SomeException
e :: SomeException) ->
let text :: Rope
text = forall α. Textual α => α -> Rope
intoRope (forall e. Exception e => e -> String
displayException SomeException
e)
in do
forall τ. Rope -> Program τ ()
warn Rope
"Trapped uncaught exception"
forall τ. Rope -> Rope -> Program τ ()
debug Rope
"e" Rope
text
)
execute :: Program None α -> IO ()
execute :: forall α. Program None α -> IO ()
execute Program None α
program = do
Context None
context <- forall τ. Version -> τ -> Config -> IO (Context τ)
configure Version
"" None
None ([Options] -> Config
simpleConfig [])
forall τ α. Context τ -> Program τ α -> IO ()
executeActual Context None
context Program None α
program
executeWith :: Context τ -> Program τ α -> IO ()
executeWith :: forall τ α. Context τ -> Program τ α -> IO ()
executeWith = forall τ α. Context τ -> Program τ α -> IO ()
executeActual
executeActual :: Context τ -> Program τ α -> IO ()
executeActual :: forall τ α. Context τ -> Program τ α -> IO ()
executeActual Context τ
context0 Program τ α
program = do
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
hostIsThreaded forall a b. (a -> b) -> a -> b
$ do
String -> IO ()
putStrLn String
"error: Application must be compiled with -threaded GHC option"
ExitCode -> IO ()
Posix.exitImmediately (Int -> ExitCode
ExitFailure Int
98)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
numCapabilities forall a. Eq a => a -> a -> Bool
== Int
1) forall a b. (a -> b) -> a -> b
$ do
IO Int
getNumProcessors forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> IO ()
setNumCapabilities
TextEncoding -> IO ()
setLocaleEncoding TextEncoding
utf8
Context τ
context1 <- forall τ. Context τ -> IO (Context τ)
handleCommandLine Context τ
context0
Context τ
context <- forall τ. Context τ -> IO (Context τ)
handleTelemetryChoice Context τ
context1
MVar Verbosity
level <- forall τ. Context τ -> IO (MVar Verbosity)
handleVerbosityLevel Context τ
context
let quit :: MVar ExitCode
quit = forall τ. Context τ -> MVar ExitCode
exitSemaphoreFrom Context τ
context
let vo :: MVar ()
vo = forall τ. Context τ -> MVar ()
outputSemaphoreFrom Context τ
context
let out :: TQueue (Maybe Rope)
out = forall τ. Context τ -> TQueue (Maybe Rope)
outputChannelFrom Context τ
context
let vl :: MVar ()
vl = forall τ. Context τ -> MVar ()
telemetrySemaphoreFrom Context τ
context
let tel :: TQueue (Maybe Datum)
tel = forall τ. Context τ -> TQueue (Maybe Datum)
telemetryChannelFrom Context τ
context
let forwarder :: Maybe Forwarder
forwarder = forall τ. Context τ -> Maybe Forwarder
telemetryForwarderFrom Context τ
context
ThreadId
_ <- IO () -> IO ThreadId
forkIO forall a b. (a -> b) -> a -> b
$ do
MVar ExitCode -> MVar Verbosity -> IO ()
setupSignalHandlers MVar ExitCode
quit MVar Verbosity
level
ThreadId
_ <-
forall a. IO a -> (Either SomeException a -> IO ()) -> IO ThreadId
forkFinally
(TQueue (Maybe Rope) -> IO ()
processStandardOutput TQueue (Maybe Rope)
out)
(\Either SomeException ()
_ -> forall a. MVar a -> a -> IO ()
putMVar MVar ()
vo ())
ThreadId
_ <-
forall a. IO a -> (Either SomeException a -> IO ()) -> IO ThreadId
forkFinally
(Maybe Forwarder
-> MVar Verbosity
-> TQueue (Maybe Rope)
-> TQueue (Maybe Datum)
-> IO ()
processTelemetryMessages Maybe Forwarder
forwarder MVar Verbosity
level TQueue (Maybe Rope)
out TQueue (Maybe Datum)
tel)
(\Either SomeException ()
_ -> forall a. MVar a -> a -> IO ()
putMVar MVar ()
vl ())
ThreadId
t1 <- IO () -> IO ThreadId
forkIO forall a b. (a -> b) -> a -> b
$ do
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
Safe.catch
( do
α
_ <- forall τ α. Context τ -> Program τ α -> IO α
subProgram Context τ
context Program τ α
program
Bool
_ <- forall a. MVar a -> a -> IO Bool
tryPutMVar MVar ExitCode
quit ExitCode
ExitSuccess
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
)
( \(SomeException
e :: SomeException) -> do
let text :: Rope
text = forall α. Textual α => α -> Rope
intoRope (forall e. Exception e => e -> String
displayException SomeException
e)
forall τ α. Context τ -> Program τ α -> IO α
subProgram Context τ
context forall a b. (a -> b) -> a -> b
$ do
forall τ. Verbosity -> Program τ ()
setVerbosityLevel Verbosity
Debug
forall τ. Rope -> Program τ ()
critical Rope
text
Bool
_ <- forall a. MVar a -> a -> IO Bool
tryPutMVar MVar ExitCode
quit (Int -> ExitCode
ExitFailure Int
127)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
)
ExitCode
code <- forall a. MVar a -> IO a
readMVar MVar ExitCode
quit
ThreadId -> IO ()
killThread ThreadId
t1
ThreadId
t2 <- IO () -> IO ThreadId
forkIO forall a b. (a -> b) -> a -> b
$ do
Int -> IO ()
threadDelay Int
10000000
String -> IO ()
putStrLn String
"error: Timeout"
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Safe.throw (Int -> ExitCode
ExitFailure Int
96)
ThreadId
t3 <- IO () -> IO ThreadId
forkIO forall a b. (a -> b) -> a -> b
$ do
let scope :: TVar (Set ThreadId)
scope = forall τ. Context τ -> TVar (Set ThreadId)
currentScopeFrom Context τ
context
Set ThreadId
pointers <- forall a. TVar a -> IO a
readTVarIO TVar (Set ThreadId)
scope
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ Set ThreadId
pointers ThreadId -> IO ()
killThread
forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ do
forall a. TQueue a -> a -> STM ()
writeTQueue TQueue (Maybe Datum)
tel forall a. Maybe a
Nothing
forall a. MVar a -> IO a
readMVar MVar ()
vl
forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ do
forall a. TQueue a -> a -> STM ()
writeTQueue TQueue (Maybe Rope)
out forall a. Maybe a
Nothing
forall a. MVar a -> IO a
readMVar MVar ()
vo
Handle -> IO ()
hFlush Handle
stdout
ThreadId -> IO ()
killThread ThreadId
t3
ThreadId -> IO ()
killThread ThreadId
t2
if ExitCode
code forall a. Eq a => a -> a -> Bool
== ExitCode
ExitSuccess
then forall (m :: * -> *) a. Monad m => a -> m a
return ()
else (forall e a. Exception e => e -> IO a
Base.throwIO ExitCode
code)
processStandardOutput :: TQueue (Maybe Rope) -> IO ()
processStandardOutput :: TQueue (Maybe Rope) -> IO ()
processStandardOutput TQueue (Maybe Rope)
out =
IO ()
loop
where
loop :: IO ()
loop :: IO ()
loop = do
Maybe Rope
probable <- forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ do
forall a. TQueue a -> STM a
readTQueue TQueue (Maybe Rope)
out
case Maybe Rope
probable of
Maybe Rope
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Just Rope
text -> do
Handle -> Rope -> IO ()
hWrite Handle
stdout Rope
text
Handle -> ByteString -> IO ()
B.hPut Handle
stdout (Char -> ByteString
C.singleton Char
'\n')
Handle -> IO ()
hFlush Handle
stdout
IO ()
loop
processTelemetryMessages :: Maybe Forwarder -> MVar Verbosity -> TQueue (Maybe Rope) -> TQueue (Maybe Datum) -> IO ()
processTelemetryMessages :: Maybe Forwarder
-> MVar Verbosity
-> TQueue (Maybe Rope)
-> TQueue (Maybe Datum)
-> IO ()
processTelemetryMessages Maybe Forwarder
Nothing MVar Verbosity
_ TQueue (Maybe Rope)
_ TQueue (Maybe Datum)
tel = do
forall {a}. TQueue (Maybe a) -> IO ()
ignoreForever TQueue (Maybe Datum)
tel
where
ignoreForever :: TQueue (Maybe a) -> IO ()
ignoreForever TQueue (Maybe a)
queue = do
Maybe a
possibleItem <- forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ do
forall a. TQueue a -> STM a
readTQueue TQueue (Maybe a)
queue
case Maybe a
possibleItem of
Maybe a
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Just a
_ -> do
TQueue (Maybe a) -> IO ()
ignoreForever TQueue (Maybe a)
queue
processTelemetryMessages (Just Forwarder
processor) MVar Verbosity
v TQueue (Maybe Rope)
out TQueue (Maybe Datum)
tel = do
forall a.
([a] -> IO ())
-> MVar Verbosity
-> TQueue (Maybe Rope)
-> TQueue (Maybe a)
-> IO ()
loopForever [Datum] -> IO ()
action MVar Verbosity
v TQueue (Maybe Rope)
out TQueue (Maybe Datum)
tel
where
action :: [Datum] -> IO ()
action = Forwarder -> [Datum] -> IO ()
telemetryHandlerFrom Forwarder
processor
loopForever :: ([a] -> IO ()) -> MVar Verbosity -> TQueue (Maybe Rope) -> TQueue (Maybe a) -> IO ()
loopForever :: forall a.
([a] -> IO ())
-> MVar Verbosity
-> TQueue (Maybe Rope)
-> TQueue (Maybe a)
-> IO ()
loopForever [a] -> IO ()
action MVar Verbosity
v TQueue (Maybe Rope)
out TQueue (Maybe a)
queue = do
Maybe [a]
possibleItems <- forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ do
Int -> [a] -> STM (Maybe [a])
cycleOverQueue Int
0 []
case Maybe [a]
possibleItems of
Maybe [a]
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Just [a]
items -> do
Time
start <- IO Time
getCurrentTimeNanoseconds
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
Safe.catch
( do
[a] -> IO ()
action (forall a. [a] -> [a]
reverse [a]
items)
forall {p}. (Eq p, Num p, Show p) => Time -> p -> IO ()
reportStatus Time
start (forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
items)
)
( \(SomeException
e :: SomeException) -> do
forall {p}. Show p => Time -> p -> IO ()
reportProblem Time
start SomeException
e
)
forall a.
([a] -> IO ())
-> MVar Verbosity
-> TQueue (Maybe Rope)
-> TQueue (Maybe a)
-> IO ()
loopForever [a] -> IO ()
action MVar Verbosity
v TQueue (Maybe Rope)
out TQueue (Maybe a)
queue
where
cycleOverQueue :: Int -> [a] -> STM (Maybe [a])
cycleOverQueue !Int
count [a]
items =
if Int
count forall a. Ord a => a -> a -> Bool
>= (Int
1024 :: Int)
then forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. a -> Maybe a
Just [a]
items)
else Int -> [a] -> STM (Maybe [a])
cycleOverQueue' Int
count [a]
items
cycleOverQueue' :: Int -> [a] -> STM (Maybe [a])
cycleOverQueue' !Int
count [a]
items =
case [a]
items of
[] -> do
Maybe a
possibleItem <- forall a. TQueue a -> STM a
readTQueue TQueue (Maybe a)
queue
case Maybe a
possibleItem of
Maybe a
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
Just a
item -> do
Int -> [a] -> STM (Maybe [a])
cycleOverQueue Int
1 (a
item forall a. a -> [a] -> [a]
: [])
[a]
_ -> do
Maybe (Maybe a)
pending <- forall a. TQueue a -> STM (Maybe a)
tryReadTQueue TQueue (Maybe a)
queue
case Maybe (Maybe a)
pending of
Maybe (Maybe a)
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. a -> Maybe a
Just [a]
items)
Just Maybe a
possibleItem -> do
case Maybe a
possibleItem of
Maybe a
Nothing -> do
forall a. TQueue a -> a -> STM ()
unGetTQueue TQueue (Maybe a)
queue forall a. Maybe a
Nothing
forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. a -> Maybe a
Just [a]
items)
Just a
item -> do
Int -> [a] -> STM (Maybe [a])
cycleOverQueue (Int
count forall a. Num a => a -> a -> a
+ Int
1) (a
item forall a. a -> [a] -> [a]
: [a]
items)
reportStatus :: Time -> p -> IO ()
reportStatus Time
start p
num = do
Verbosity
level <- forall a. MVar a -> IO a
readMVar MVar Verbosity
v
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity -> Bool
isInternal Verbosity
level) forall a b. (a -> b) -> a -> b
$ do
Time
now <- IO Time
getCurrentTimeNanoseconds
let desc :: Rope
desc = case p
num of
p
1 -> Rope
"1 event"
p
_ -> forall α. Textual α => α -> Rope
intoRope (forall a. Show a => a -> String
show p
num) forall a. Semigroup a => a -> a -> a
<> Rope
" events"
message :: Rope
message =
Time -> Time -> Bool -> Severity -> Rope -> Rope
formatLogMessage
Time
start
Time
now
Bool
True
Severity
SeverityInternal
(Rope
"Sent " forall a. Semigroup a => a -> a -> a
<> Rope
desc)
forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ do
forall a. TQueue a -> a -> STM ()
writeTQueue TQueue (Maybe Rope)
out (forall a. a -> Maybe a
Just Rope
message)
reportProblem :: Time -> p -> IO ()
reportProblem Time
start p
e = do
Verbosity
level <- forall a. MVar a -> IO a
readMVar MVar Verbosity
v
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity -> Bool
isEvent Verbosity
level) forall a b. (a -> b) -> a -> b
$ do
Time
now <- IO Time
getCurrentTimeNanoseconds
let message :: Rope
message =
Time -> Time -> Bool -> Severity -> Rope -> Rope
formatLogMessage
Time
start
Time
now
Bool
True
Severity
SeverityWarn
(Rope
"Sending telemetry failed (Exception: " forall a. Semigroup a => a -> a -> a
<> forall α. Textual α => α -> Rope
intoRope (forall a. Show a => a -> String
show p
e) forall a. Semigroup a => a -> a -> a
<> Rope
"); Restarting exporter.")
forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ do
forall a. TQueue a -> a -> STM ()
writeTQueue TQueue (Maybe Rope)
out (forall a. a -> Maybe a
Just Rope
message)
terminate :: Int -> Program τ α
terminate :: forall τ α. Int -> Program τ α
terminate Int
code = do
Context τ
context <- forall r (m :: * -> *). MonadReader r m => m r
ask
let quit :: MVar ExitCode
quit = forall τ. Context τ -> MVar ExitCode
exitSemaphoreFrom Context τ
context
let exit :: ExitCode
exit = case Int
code of
Int
0 -> ExitCode
ExitSuccess
Int
_ -> Int -> ExitCode
ExitFailure Int
code
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
forall a. MVar a -> a -> IO ()
putMVar MVar ExitCode
quit ExitCode
exit
ThreadId
self <- IO ThreadId
myThreadId
ThreadId -> IO ()
killThread ThreadId
self
forall (f :: * -> *) a b. Applicative f => f a -> f b
forever forall a b. (a -> b) -> a -> b
$ do
Int -> IO ()
threadDelay forall a. Bounded a => a
maxBound
getVerbosityLevel :: Program τ Verbosity
getVerbosityLevel :: forall τ. Program τ Verbosity
getVerbosityLevel = do
Context τ
context <- forall r (m :: * -> *). MonadReader r m => m r
ask
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
Verbosity
level <- forall a. MVar a -> IO a
readMVar (forall τ. Context τ -> MVar Verbosity
verbosityLevelFrom Context τ
context)
forall (m :: * -> *) a. Monad m => a -> m a
return Verbosity
level
setVerbosityLevel :: Verbosity -> Program τ ()
setVerbosityLevel :: forall τ. Verbosity -> Program τ ()
setVerbosityLevel Verbosity
level = do
Context τ
context <- forall r (m :: * -> *). MonadReader r m => m r
ask
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
let v :: MVar Verbosity
v = forall τ. Context τ -> MVar Verbosity
verbosityLevelFrom Context τ
context
forall a. MVar a -> (a -> IO a) -> IO ()
modifyMVar_ MVar Verbosity
v (\Verbosity
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Verbosity
level)
setProgramName :: Rope -> Program τ ()
setProgramName :: forall τ. Rope -> Program τ ()
setProgramName Rope
name = do
Context τ
context <- forall r (m :: * -> *). MonadReader r m => m r
ask
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
let v :: MVar Rope
v = forall τ. Context τ -> MVar Rope
programNameFrom Context τ
context
forall a. MVar a -> (a -> IO a) -> IO ()
modifyMVar_ MVar Rope
v (\Rope
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Rope
name)
getProgramName :: Program τ Rope
getProgramName :: forall τ. Program τ Rope
getProgramName = do
Context τ
context <- forall r (m :: * -> *). MonadReader r m => m r
ask
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
let v :: MVar Rope
v = forall τ. Context τ -> MVar Rope
programNameFrom Context τ
context
forall a. MVar a -> IO a
readMVar MVar Rope
v
getConsoleWidth :: Program τ Int
getConsoleWidth :: forall τ. Program τ Int
getConsoleWidth = do
Context τ
context <- forall r (m :: * -> *). MonadReader r m => m r
ask
let width :: Int
width = forall τ. Context τ -> Int
terminalWidthFrom Context τ
context
forall (m :: * -> *) a. Monad m => a -> m a
return Int
width
getApplicationState :: Program τ τ
getApplicationState :: forall τ. Program τ τ
getApplicationState = do
Context τ
context <- forall r (m :: * -> *). MonadReader r m => m r
ask
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
let v :: MVar τ
v = forall τ. Context τ -> MVar τ
applicationDataFrom Context τ
context
forall a. MVar a -> IO a
readMVar MVar τ
v
setApplicationState :: τ -> Program τ ()
setApplicationState :: forall τ. τ -> Program τ ()
setApplicationState τ
user = do
Context τ
context <- forall r (m :: * -> *). MonadReader r m => m r
ask
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
let v :: MVar τ
v = forall τ. Context τ -> MVar τ
applicationDataFrom Context τ
context
forall a. MVar a -> (a -> IO a) -> IO ()
modifyMVar_ MVar τ
v (\τ
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure τ
user)
modifyApplicationState :: (τ -> Program τ τ) -> Program τ ()
modifyApplicationState :: forall τ. (τ -> Program τ τ) -> Program τ ()
modifyApplicationState τ -> Program τ τ
program = do
Context τ
context <- forall r (m :: * -> *). MonadReader r m => m r
ask
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
let v :: MVar τ
v = forall τ. Context τ -> MVar τ
applicationDataFrom Context τ
context
forall a. MVar a -> (a -> IO a) -> IO ()
modifyMVar_
MVar τ
v
( \τ
user -> do
τ
user' <- forall τ α. Context τ -> Program τ α -> IO α
subProgram Context τ
context (τ -> Program τ τ
program τ
user)
forall (f :: * -> *) a. Applicative f => a -> f a
pure τ
user'
)
changeProgram :: υ -> Program υ α -> Program τ α
changeProgram :: forall υ α τ. υ -> Program υ α -> Program τ α
changeProgram υ
user' Program υ α
program = do
Context τ
context1 <- forall r (m :: * -> *). MonadReader r m => m r
ask
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
MVar υ
u <- forall a. a -> IO (MVar a)
newMVar υ
user'
let context2 :: Context υ
context2 = Context τ
context1 {$sel:applicationDataFrom:Context :: MVar υ
applicationDataFrom = MVar υ
u}
forall τ α. Context τ -> Program τ α -> IO α
subProgram Context υ
context2 Program υ α
program
outputEntire :: Handle -> Bytes -> Program τ ()
outputEntire :: forall τ. Handle -> Bytes -> Program τ ()
outputEntire Handle
handle Bytes
contents = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Handle -> Bytes -> IO ()
hOutput Handle
handle Bytes
contents)
inputEntire :: Handle -> Program τ Bytes
inputEntire :: forall τ. Handle -> Program τ Bytes
inputEntire Handle
handle = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Handle -> IO Bytes
hInput Handle
handle)
data ProcessProblem
= CommandNotFound Rope
deriving (Int -> ProcessProblem -> ShowS
[ProcessProblem] -> ShowS
ProcessProblem -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProcessProblem] -> ShowS
$cshowList :: [ProcessProblem] -> ShowS
show :: ProcessProblem -> String
$cshow :: ProcessProblem -> String
showsPrec :: Int -> ProcessProblem -> ShowS
$cshowsPrec :: Int -> ProcessProblem -> ShowS
Show)
instance Exception ProcessProblem
readProcess :: [Rope] -> Program τ (ExitCode, Rope, Rope)
readProcess :: forall τ. [Rope] -> Program τ (ExitCode, Rope, Rope)
readProcess [] = forall a. HasCallStack => String -> a
error String
"No command provided"
readProcess (Rope
cmd : [Rope]
args) =
let cmd' :: String
cmd' = forall α. Textual α => Rope -> α
fromRope Rope
cmd
args' :: [String]
args' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall α. Textual α => Rope -> α
fromRope [Rope]
args
task :: ProcessConfig () () ()
task = String -> [String] -> ProcessConfig () () ()
Typed.proc String
cmd' [String]
args'
task1 :: ProcessConfig () () ()
task1 = forall stdin stdin0 stdout stderr.
StreamSpec 'STInput stdin
-> ProcessConfig stdin0 stdout stderr
-> ProcessConfig stdin stdout stderr
Typed.setStdin forall (anyStreamType :: StreamType). StreamSpec anyStreamType ()
Typed.nullStream ProcessConfig () () ()
task
command :: Rope
command = forall a. Monoid a => [a] -> a
mconcat (forall a. a -> [a] -> [a]
List.intersperse (Char -> Rope
singletonRope Char
' ') (Rope
cmd forall a. a -> [a] -> [a]
: [Rope]
args))
in do
forall τ. Rope -> Rope -> Program τ ()
debug Rope
"command" Rope
command
Maybe String
probe <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
String -> IO (Maybe String)
findExecutable String
cmd'
case Maybe String
probe of
Maybe String
Nothing -> do
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Safe.throw (Rope -> ProcessProblem
CommandNotFound Rope
cmd)
Just String
_ -> do
(ExitCode
exit, ByteString
out, ByteString
err) <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
forall (m :: * -> *) stdin stdoutIgnored stderrIgnored.
MonadIO m =>
ProcessConfig stdin stdoutIgnored stderrIgnored
-> m (ExitCode, ByteString, ByteString)
Typed.readProcess ProcessConfig () () ()
task1
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ExitCode
exit, forall α. Textual α => α -> Rope
intoRope ByteString
out, forall α. Textual α => α -> Rope
intoRope ByteString
err)
execProcess :: [Rope] -> Program τ (ExitCode, Rope, Rope)
execProcess :: forall τ. [Rope] -> Program τ (ExitCode, Rope, Rope)
execProcess = forall τ. [Rope] -> Program τ (ExitCode, Rope, Rope)
readProcess
{-# DEPRECATED execProcess "Use readProcess intead" #-}
execProcess_ :: [Rope] -> Program τ ()
execProcess_ :: forall τ. [Rope] -> Program τ ()
execProcess_ [] = forall a. HasCallStack => String -> a
error String
"No command provided"
execProcess_ (Rope
cmd : [Rope]
args) = do
Context τ
context <- forall r (m :: * -> *). MonadReader r m => m r
ask
let cmd' :: String
cmd' = forall α. Textual α => Rope -> α
fromRope Rope
cmd
let args' :: [String]
args' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall α. Textual α => Rope -> α
fromRope [Rope]
args
let command :: Rope
command = forall a. Monoid a => [a] -> a
mconcat (forall a. a -> [a] -> [a]
List.intersperse (Char -> Rope
singletonRope Char
' ') (Rope
cmd forall a. a -> [a] -> [a]
: [Rope]
args))
let vo :: MVar ()
vo = forall τ. Context τ -> MVar ()
outputSemaphoreFrom Context τ
context
let out :: TQueue (Maybe Rope)
out = forall τ. Context τ -> TQueue (Maybe Rope)
outputChannelFrom Context τ
context
let vl :: MVar ()
vl = forall τ. Context τ -> MVar ()
telemetrySemaphoreFrom Context τ
context
let tel :: TQueue (Maybe Datum)
tel = forall τ. Context τ -> TQueue (Maybe Datum)
telemetryChannelFrom Context τ
context
forall τ. Rope -> Rope -> Program τ ()
debug Rope
"command" Rope
command
Maybe String
probe <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
String -> IO (Maybe String)
findExecutable String
cmd'
case Maybe String
probe of
Maybe String
Nothing -> do
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Safe.throw (Rope -> ProcessProblem
CommandNotFound Rope
cmd)
Just String
_ -> do
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ do
forall a. TQueue a -> a -> STM ()
writeTQueue TQueue (Maybe Datum)
tel forall a. Maybe a
Nothing
forall a. TQueue a -> a -> STM ()
writeTQueue TQueue (Maybe Rope)
out forall a. Maybe a
Nothing
ThreadId
_ <- IO () -> IO ThreadId
forkIO forall a b. (a -> b) -> a -> b
$ do
Int -> IO ()
threadDelay Int
10000000
String -> IO ()
putStrLn String
"error: Timeout"
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Safe.throw (Int -> ExitCode
ExitFailure Int
97)
forall a. MVar a -> IO a
readMVar MVar ()
vl
forall a. MVar a -> IO a
readMVar MVar ()
vo
Any
_ <- forall a.
String -> Bool -> [String] -> Maybe [(String, String)] -> IO a
Posix.executeFile String
cmd' Bool
True [String]
args' forall a. Maybe a
Nothing
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
callProcess :: [Rope] -> Program τ ExitCode
callProcess :: forall τ. [Rope] -> Program τ ExitCode
callProcess [] = forall a. HasCallStack => String -> a
error String
"No command provided"
callProcess (Rope
cmd : [Rope]
args) = do
let cmd' :: String
cmd' = forall α. Textual α => Rope -> α
fromRope Rope
cmd
let args' :: [String]
args' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall α. Textual α => Rope -> α
fromRope [Rope]
args
let task1 :: CreateProcess
task1 = String -> [String] -> CreateProcess
Base.proc String
cmd' [String]
args'
let command :: Rope
command = forall a. Monoid a => [a] -> a
mconcat (forall a. a -> [a] -> [a]
List.intersperse (Char -> Rope
singletonRope Char
' ') (Rope
cmd forall a. a -> [a] -> [a]
: [Rope]
args))
forall τ. Rope -> Rope -> Program τ ()
debug Rope
"command" Rope
command
Maybe String
probe <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
String -> IO (Maybe String)
findExecutable String
cmd'
case Maybe String
probe of
Maybe String
Nothing -> do
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Safe.throw (Rope -> ProcessProblem
CommandNotFound Rope
cmd)
Just String
_ -> do
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
Handle
i <- String -> IOMode -> IO Handle
Base.openFile String
"/dev/null" IOMode
Base.ReadMode
let task2 :: CreateProcess
task2 =
CreateProcess
task1
{ std_in :: StdStream
Base.std_in = Handle -> StdStream
Base.UseHandle Handle
i
, std_out :: StdStream
Base.std_out = StdStream
Base.Inherit
, std_err :: StdStream
Base.std_err = StdStream
Base.Inherit
}
(Maybe Handle
_, Maybe Handle
_, Maybe Handle
_, ProcessHandle
p) <- CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
Base.createProcess CreateProcess
task2
forall (m :: * -> *) a b. MonadMask m => m a -> m b -> m a
Safe.onException
( do
ExitCode
exit <- ProcessHandle -> IO ExitCode
Base.waitForProcess ProcessHandle
p
Handle -> IO ()
Base.hClose Handle
i
forall (f :: * -> *) a. Applicative f => a -> f a
pure ExitCode
exit
)
( do
ProcessHandle -> IO ()
Base.terminateProcess ProcessHandle
p
ExitCode
_ <- ProcessHandle -> IO ExitCode
Base.waitForProcess ProcessHandle
p
Handle -> IO ()
Base.hClose Handle
i
)
resetTimer :: Program τ ()
resetTimer :: forall τ. Program τ ()
resetTimer = do
Context τ
context <- forall r (m :: * -> *). MonadReader r m => m r
ask
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
Time
start <- IO Time
getCurrentTimeNanoseconds
let v :: MVar Time
v = forall τ. Context τ -> MVar Time
startTimeFrom Context τ
context
forall a. MVar a -> (a -> IO a) -> IO ()
modifyMVar_ MVar Time
v (\Time
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Time
start)
sleepThread :: Rational -> Program τ ()
sleepThread :: forall τ. Rational -> Program τ ()
sleepThread Rational
seconds =
let us :: Int
us = forall a b. (RealFrac a, Integral b) => a -> b
floor (forall a. Real a => a -> Rational
toRational (Rational
seconds forall a. Num a => a -> a -> a
* Rational
1e6))
in forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Int -> IO ()
threadDelay Int
us
getCommandLine :: Program τ (Parameters)
getCommandLine :: forall τ. Program τ Parameters
getCommandLine = do
Context τ
context <- forall r (m :: * -> *). MonadReader r m => m r
ask
forall (m :: * -> *) a. Monad m => a -> m a
return (forall τ. Context τ -> Parameters
commandLineFrom Context τ
context)
queryArgument :: LongName -> Program τ Rope
queryArgument :: forall τ. LongName -> Program τ Rope
queryArgument LongName
name = do
Context τ
context <- forall r (m :: * -> *). MonadReader r m => m r
ask
let params :: Parameters
params = forall τ. Context τ -> Parameters
commandLineFrom Context τ
context
case forall κ ν. Key κ => κ -> Map κ ν -> Maybe ν
lookupKeyValue LongName
name (Parameters -> Map LongName ParameterValue
parameterValuesFrom Parameters
params) of
Maybe ParameterValue
Nothing -> forall a. HasCallStack => String -> a
error String
"Attempted lookup of unconfigured argument"
Just ParameterValue
argument -> case ParameterValue
argument of
ParameterValue
Empty -> forall a. HasCallStack => String -> a
error String
"Invalid State"
Value String
value -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall α. Textual α => α -> Rope
intoRope String
value)
lookupArgument :: LongName -> Parameters -> Maybe String
lookupArgument :: LongName -> Parameters -> Maybe String
lookupArgument LongName
name Parameters
params =
case forall κ ν. Key κ => κ -> Map κ ν -> Maybe ν
lookupKeyValue LongName
name (Parameters -> Map LongName ParameterValue
parameterValuesFrom Parameters
params) of
Maybe ParameterValue
Nothing -> forall a. Maybe a
Nothing
Just ParameterValue
argument -> case ParameterValue
argument of
ParameterValue
Empty -> forall a. HasCallStack => String -> a
error String
"Invalid State"
Value String
value -> forall a. a -> Maybe a
Just String
value
{-# DEPRECATED lookupArgument "Use queryArgument instead" #-}
queryRemaining :: Program τ [Rope]
queryRemaining :: forall τ. Program τ [Rope]
queryRemaining = do
Context τ
context <- forall r (m :: * -> *). MonadReader r m => m r
ask
let params :: Parameters
params = forall τ. Context τ -> Parameters
commandLineFrom Context τ
context
let remaining :: [String]
remaining = Parameters -> [String]
remainingArgumentsFrom Parameters
params
forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall α. Textual α => α -> Rope
intoRope [String]
remaining)
queryOptionValue :: LongName -> Program τ (Maybe Rope)
queryOptionValue :: forall τ. LongName -> Program τ (Maybe Rope)
queryOptionValue LongName
name = do
Context τ
context <- forall r (m :: * -> *). MonadReader r m => m r
ask
let params :: Parameters
params = forall τ. Context τ -> Parameters
commandLineFrom Context τ
context
case forall κ ν. Key κ => κ -> Map κ ν -> Maybe ν
lookupKeyValue LongName
name (Parameters -> Map LongName ParameterValue
parameterValuesFrom Parameters
params) of
Maybe ParameterValue
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
Just ParameterValue
argument -> case ParameterValue
argument of
ParameterValue
Empty -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. a -> Maybe a
Just Rope
emptyRope)
Value String
value -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. a -> Maybe a
Just (forall α. Textual α => α -> Rope
intoRope String
value))
lookupOptionValue :: LongName -> Parameters -> Maybe String
lookupOptionValue :: LongName -> Parameters -> Maybe String
lookupOptionValue LongName
name Parameters
params =
case forall κ ν. Key κ => κ -> Map κ ν -> Maybe ν
lookupKeyValue LongName
name (Parameters -> Map LongName ParameterValue
parameterValuesFrom Parameters
params) of
Maybe ParameterValue
Nothing -> forall a. Maybe a
Nothing
Just ParameterValue
argument -> case ParameterValue
argument of
ParameterValue
Empty -> forall a. Maybe a
Nothing
Value String
value -> forall a. a -> Maybe a
Just String
value
{-# DEPRECATED lookupOptionValue "Use queryOptionValue instead" #-}
data QueryParameterError
= OptionValueMissing LongName
| UnableParseOption LongName
| EnvironmentVariableMissing LongName
| UnableParseVariable LongName
deriving (Int -> QueryParameterError -> ShowS
[QueryParameterError] -> ShowS
QueryParameterError -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QueryParameterError] -> ShowS
$cshowList :: [QueryParameterError] -> ShowS
show :: QueryParameterError -> String
$cshow :: QueryParameterError -> String
showsPrec :: Int -> QueryParameterError -> ShowS
$cshowsPrec :: Int -> QueryParameterError -> ShowS
Show)
instance Exception QueryParameterError where
displayException :: QueryParameterError -> String
displayException QueryParameterError
e = case QueryParameterError
e of
OptionValueMissing (LongName String
name) -> String
"Option --" forall a. [a] -> [a] -> [a]
++ String
name forall a. [a] -> [a] -> [a]
++ String
" specified but without a value."
UnableParseOption (LongName String
name) -> String
"Unable to parse the value supplied to --" forall a. [a] -> [a] -> [a]
++ String
name forall a. [a] -> [a] -> [a]
++ String
"."
EnvironmentVariableMissing (LongName String
name) -> String
"Variable " forall a. [a] -> [a] -> [a]
++ String
name forall a. [a] -> [a] -> [a]
++ String
" requested but is unset."
UnableParseVariable (LongName String
name) -> String
"Unable to parse the value present in " forall a. [a] -> [a] -> [a]
++ String
name forall a. [a] -> [a] -> [a]
++ String
"."
queryOptionValue' :: (Externalize ξ) => LongName -> Program τ (Maybe ξ)
queryOptionValue' :: forall ξ τ. Externalize ξ => LongName -> Program τ (Maybe ξ)
queryOptionValue' LongName
name = do
Context τ
context <- forall r (m :: * -> *). MonadReader r m => m r
ask
let params :: Parameters
params = forall τ. Context τ -> Parameters
commandLineFrom Context τ
context
case forall κ ν. Key κ => κ -> Map κ ν -> Maybe ν
lookupKeyValue LongName
name (Parameters -> Map LongName ParameterValue
parameterValuesFrom Parameters
params) of
Maybe ParameterValue
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
Just ParameterValue
parameter -> case ParameterValue
parameter of
ParameterValue
Empty -> forall ε τ α. Exception ε => ε -> Program τ α
throw (LongName -> QueryParameterError
OptionValueMissing LongName
name)
Value String
value -> case forall ξ. Externalize ξ => Rope -> Maybe ξ
parseExternal (String -> Rope
packRope String
value) of
Maybe ξ
Nothing -> forall ε τ α. Exception ε => ε -> Program τ α
throw (LongName -> QueryParameterError
UnableParseOption LongName
name)
Just ξ
actual -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. a -> Maybe a
Just ξ
actual)
queryOptionFlag :: LongName -> Program τ Bool
queryOptionFlag :: forall τ. LongName -> Program τ Bool
queryOptionFlag LongName
name = do
Context τ
context <- forall r (m :: * -> *). MonadReader r m => m r
ask
let params :: Parameters
params = forall τ. Context τ -> Parameters
commandLineFrom Context τ
context
case forall κ ν. Key κ => κ -> Map κ ν -> Maybe ν
lookupKeyValue LongName
name (Parameters -> Map LongName ParameterValue
parameterValuesFrom Parameters
params) of
Maybe ParameterValue
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
Just ParameterValue
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True
lookupOptionFlag :: LongName -> Parameters -> Maybe Bool
lookupOptionFlag :: LongName -> Parameters -> Maybe Bool
lookupOptionFlag LongName
name Parameters
params =
case forall κ ν. Key κ => κ -> Map κ ν -> Maybe ν
lookupKeyValue LongName
name (Parameters -> Map LongName ParameterValue
parameterValuesFrom Parameters
params) of
Maybe ParameterValue
Nothing -> forall a. Maybe a
Nothing
Just ParameterValue
argument -> case ParameterValue
argument of
ParameterValue
_ -> forall a. a -> Maybe a
Just Bool
True
{-# DEPRECATED lookupOptionFlag "Use queryOptionFlag instead" #-}
queryEnvironmentValue :: LongName -> Program τ (Maybe Rope)
queryEnvironmentValue :: forall τ. LongName -> Program τ (Maybe Rope)
queryEnvironmentValue LongName
name = do
Context τ
context <- forall r (m :: * -> *). MonadReader r m => m r
ask
let params :: Parameters
params = forall τ. Context τ -> Parameters
commandLineFrom Context τ
context
case forall κ ν. Key κ => κ -> Map κ ν -> Maybe ν
lookupKeyValue LongName
name (Parameters -> Map LongName ParameterValue
environmentValuesFrom Parameters
params) of
Maybe ParameterValue
Nothing -> forall a. HasCallStack => String -> a
error String
"Attempted lookup of unconfigured environment variable"
Just ParameterValue
param -> case ParameterValue
param of
ParameterValue
Empty -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
Value String
str -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. a -> Maybe a
Just (forall α. Textual α => α -> Rope
intoRope String
str))
queryEnvironmentValue' :: (Externalize ξ) => LongName -> Program τ (Maybe ξ)
queryEnvironmentValue' :: forall ξ τ. Externalize ξ => LongName -> Program τ (Maybe ξ)
queryEnvironmentValue' LongName
name = do
Context τ
context <- forall r (m :: * -> *). MonadReader r m => m r
ask
let params :: Parameters
params = forall τ. Context τ -> Parameters
commandLineFrom Context τ
context
case forall κ ν. Key κ => κ -> Map κ ν -> Maybe ν
lookupKeyValue LongName
name (Parameters -> Map LongName ParameterValue
environmentValuesFrom Parameters
params) of
Maybe ParameterValue
Nothing -> forall a. HasCallStack => String -> a
error String
"Attempted lookup of unconfigured environment variable"
Just ParameterValue
param -> case ParameterValue
param of
ParameterValue
Empty -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
Value String
value -> case forall ξ. Externalize ξ => Rope -> Maybe ξ
parseExternal (String -> Rope
packRope String
value) of
Maybe ξ
Nothing -> forall ε τ α. Exception ε => ε -> Program τ α
throw (LongName -> QueryParameterError
UnableParseVariable LongName
name)
Just ξ
actual -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. a -> Maybe a
Just ξ
actual)
lookupEnvironmentValue :: LongName -> Parameters -> Maybe String
lookupEnvironmentValue :: LongName -> Parameters -> Maybe String
lookupEnvironmentValue LongName
name Parameters
params =
case forall κ ν. Key κ => κ -> Map κ ν -> Maybe ν
lookupKeyValue LongName
name (Parameters -> Map LongName ParameterValue
environmentValuesFrom Parameters
params) of
Maybe ParameterValue
Nothing -> forall a. Maybe a
Nothing
Just ParameterValue
param -> case ParameterValue
param of
ParameterValue
Empty -> forall a. Maybe a
Nothing
Value String
str -> forall a. a -> Maybe a
Just String
str
{-# DEPRECATED lookupEnvironmentValue "Use queryEnvironment instead" #-}
queryCommandName :: Program τ Rope
queryCommandName :: forall τ. Program τ Rope
queryCommandName = do
Context τ
context <- forall r (m :: * -> *). MonadReader r m => m r
ask
let params :: Parameters
params = forall τ. Context τ -> Parameters
commandLineFrom Context τ
context
case Parameters -> Maybe LongName
commandNameFrom Parameters
params of
Just (LongName String
name) -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall α. Textual α => α -> Rope
intoRope String
name)
Maybe LongName
Nothing -> forall a. HasCallStack => String -> a
error String
"Attempted lookup of command but not a Complex Config"
data InvalidState = InvalidState
deriving (Int -> InvalidState -> ShowS
[InvalidState] -> ShowS
InvalidState -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InvalidState] -> ShowS
$cshowList :: [InvalidState] -> ShowS
show :: InvalidState -> String
$cshow :: InvalidState -> String
showsPrec :: Int -> InvalidState -> ShowS
$cshowsPrec :: Int -> InvalidState -> ShowS
Show)
instance Exception InvalidState
invalid :: (HasCallStack) => Program τ α
invalid :: forall τ α. HasCallStack => Program τ α
invalid = do
forall τ. Rope -> Program τ ()
critical Rope
"Invalid state reached"
forall τ. Rope -> Program τ ()
write Rope
"error: invalid state"
forall τ α. Int -> Program τ α
terminate Int
99