{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RecordWildCards #-}
module Cryptol.REPL.Command (
Command(..), CommandDescr(..), CommandBody(..), CommandExitCode(..)
, parseCommand
, runCommand
, splitCommand
, findCommand
, findCommandExact
, findNbCommand
, commandList
, moduleCmd, loadCmd, loadPrelude, setOptionCmd
, interactiveConfig
, replParseExpr
, replEvalExpr
, replCheckExpr
, qcCmd, QCMode(..)
, satCmd
, proveCmd
, onlineProveSat
, offlineProveSat
, handleCtrlC
, sanitize
, replParse
, liftModuleCmd
, moduleCmdResult
) where
import Cryptol.REPL.Monad
import Cryptol.REPL.Trie
import qualified Cryptol.ModuleSystem as M
import qualified Cryptol.ModuleSystem.Name as M
import qualified Cryptol.ModuleSystem.NamingEnv as M
import qualified Cryptol.ModuleSystem.Renamer as M (RenamerWarning(SymbolShadowed))
import qualified Cryptol.Utils.Ident as M
import qualified Cryptol.ModuleSystem.Env as M
import qualified Cryptol.Backend.Monad as E
import Cryptol.Eval.Concrete( Concrete(..) )
import qualified Cryptol.Eval.Concrete as Concrete
import qualified Cryptol.Eval.Env as E
import qualified Cryptol.Eval.Type as E
import qualified Cryptol.Eval.Value as E
import qualified Cryptol.Eval.Reference as R
import Cryptol.Testing.Random
import qualified Cryptol.Testing.Random as TestR
import Cryptol.Parser
(parseExprWith,parseReplWith,ParseError(),Config(..),defaultConfig
,parseModName,parseHelpName)
import qualified Cryptol.TypeCheck.AST as T
import qualified Cryptol.TypeCheck.Error as T
import qualified Cryptol.TypeCheck.Parseable as T
import qualified Cryptol.TypeCheck.Subst as T
import Cryptol.TypeCheck.Solve(defaultReplExpr)
import qualified Cryptol.TypeCheck.Solver.SMT as SMT
import Cryptol.TypeCheck.PP (dump,ppWithNames,emptyNameMap)
import Cryptol.Utils.PP
import Cryptol.Utils.Panic(panic)
import Cryptol.Utils.RecordMap
import qualified Cryptol.Parser.AST as P
import qualified Cryptol.Transform.Specialize as S
import Cryptol.Symbolic
( ProverCommand(..), QueryType(..)
, ProverStats,ProverResult(..),CounterExampleType(..)
)
import qualified Cryptol.Symbolic.SBV as SBV
import qualified Cryptol.Symbolic.What4 as W4
import Cryptol.Version (displayVersion)
import qualified Control.Exception as X
import Control.Monad hiding (mapM, mapM)
import qualified Control.Monad.Catch as Ex
import Control.Monad.IO.Class(liftIO)
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BS8
import Data.Bits (shiftL, (.&.), (.|.))
import Data.Char (isSpace,isPunctuation,isSymbol,isAlphaNum,isAscii)
import Data.Function (on)
import Data.List (intercalate, nub, sortBy, groupBy,
partition, isPrefixOf,intersperse)
import Data.Maybe (fromMaybe,mapMaybe,isNothing)
import System.Environment (lookupEnv)
import System.Exit (ExitCode(ExitSuccess))
import System.Process (shell,createProcess,waitForProcess)
import qualified System.Process as Process(runCommand)
import System.FilePath((</>), isPathSeparator)
import System.Directory(getHomeDirectory,setCurrentDirectory,doesDirectoryExist
,getTemporaryDirectory,setPermissions,removeFile
,emptyPermissions,setOwnerReadable)
import Data.Map (Map)
import qualified Data.Map as Map
import qualified Data.Set as Set
import System.IO
(Handle,hFlush,stdout,openTempFile,hClose,openFile
,IOMode(..),hGetContents,hSeek,SeekMode(..))
import System.Random.TF(newTFGen)
import Numeric (showFFloat)
import qualified Data.Text as T
import Data.IORef(newIORef,readIORef,writeIORef)
import GHC.Float (log1p, expm1)
import Prelude ()
import Prelude.Compat
import qualified Data.SBV.Internals as SBV (showTDiff)
data Command
= Command (REPL ())
| Ambiguous String [String]
| Unknown String
data CommandDescr = CommandDescr
{ CommandDescr -> [String]
cNames :: [String]
, CommandDescr -> [String]
cArgs :: [String]
, CommandDescr -> CommandBody
cBody :: CommandBody
, CommandDescr -> String
cHelp :: String
, CommandDescr -> String
cLongHelp :: String
}
instance Show CommandDescr where
show :: CommandDescr -> String
show = [String] -> String
forall a. Show a => a -> String
show ([String] -> String)
-> (CommandDescr -> [String]) -> CommandDescr -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CommandDescr -> [String]
cNames
instance Eq CommandDescr where
== :: CommandDescr -> CommandDescr -> Bool
(==) = [String] -> [String] -> Bool
forall a. Eq a => a -> a -> Bool
(==) ([String] -> [String] -> Bool)
-> (CommandDescr -> [String])
-> CommandDescr
-> CommandDescr
-> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` CommandDescr -> [String]
cNames
instance Ord CommandDescr where
compare :: CommandDescr -> CommandDescr -> Ordering
compare = [String] -> [String] -> Ordering
forall a. Ord a => a -> a -> Ordering
compare ([String] -> [String] -> Ordering)
-> (CommandDescr -> [String])
-> CommandDescr
-> CommandDescr
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` CommandDescr -> [String]
cNames
data CommandBody
= ExprArg (String -> REPL ())
| FileExprArg (FilePath -> String -> REPL ())
| DeclsArg (String -> REPL ())
| ExprTypeArg (String -> REPL ())
| ModNameArg (String -> REPL ())
| FilenameArg (FilePath -> REPL ())
| OptionArg (String -> REPL ())
| ShellArg (String -> REPL ())
| HelpArg (String -> REPL ())
| NoArg (REPL ())
data CommandExitCode = CommandOk
| CommandError
commands :: CommandMap
commands :: CommandMap
commands = (CommandMap -> CommandDescr -> CommandMap)
-> CommandMap -> [CommandDescr] -> CommandMap
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl CommandMap -> CommandDescr -> CommandMap
insert CommandMap
forall a. Trie a
emptyTrie [CommandDescr]
commandList
where
insert :: CommandMap -> CommandDescr -> CommandMap
insert CommandMap
m CommandDescr
d = (CommandMap -> String -> CommandMap)
-> CommandMap -> [String] -> CommandMap
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (CommandDescr -> CommandMap -> String -> CommandMap
forall a. a -> Trie a -> String -> Trie a
insertOne CommandDescr
d) CommandMap
m (CommandDescr -> [String]
cNames CommandDescr
d)
insertOne :: a -> Trie a -> String -> Trie a
insertOne a
d Trie a
m String
name = String -> a -> Trie a -> Trie a
forall a. String -> a -> Trie a -> Trie a
insertTrie String
name a
d Trie a
m
nbCommands :: CommandMap
nbCommands :: CommandMap
nbCommands = (CommandMap -> CommandDescr -> CommandMap)
-> CommandMap -> [CommandDescr] -> CommandMap
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl CommandMap -> CommandDescr -> CommandMap
insert CommandMap
forall a. Trie a
emptyTrie [CommandDescr]
nbCommandList
where
insert :: CommandMap -> CommandDescr -> CommandMap
insert CommandMap
m CommandDescr
d = (CommandMap -> String -> CommandMap)
-> CommandMap -> [String] -> CommandMap
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (CommandDescr -> CommandMap -> String -> CommandMap
forall a. a -> Trie a -> String -> Trie a
insertOne CommandDescr
d) CommandMap
m (CommandDescr -> [String]
cNames CommandDescr
d)
insertOne :: a -> Trie a -> String -> Trie a
insertOne a
d Trie a
m String
name = String -> a -> Trie a -> Trie a
forall a. String -> a -> Trie a -> Trie a
insertTrie String
name a
d Trie a
m
nbCommandList :: [CommandDescr]
nbCommandList :: [CommandDescr]
nbCommandList =
[ [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":t", String
":type" ] [String
"EXPR"] ((String -> REPL ()) -> CommandBody
ExprArg String -> REPL ()
typeOfCmd)
String
"Check the type of an expression."
String
""
, [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":b", String
":browse" ] [String
"[ MODULE ]"] ((String -> REPL ()) -> CommandBody
ModNameArg String -> REPL ()
browseCmd)
String
"Display environment for all loaded modules, or for a specific module."
String
""
, [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":version"] [] (REPL () -> CommandBody
NoArg REPL ()
versionCmd)
String
"Display the version of this Cryptol executable"
String
""
, [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":?", String
":help" ] [String
"[ TOPIC ]"] ((String -> REPL ()) -> CommandBody
HelpArg String -> REPL ()
helpCmd)
String
"Display a brief description of a function, type, or command. (e.g. :help :help)"
([String] -> String
unlines
[ String
"TOPIC can be any of:"
, String
" * Specific REPL colon-commands (e.g. :help :prove)"
, String
" * Functions (e.g. :help join)"
, String
" * Infix operators (e.g. :help +)"
, String
" * Type constructors (e.g. :help Z)"
, String
" * Type constraints (e.g. :help fin)"
, String
" * :set-able options (e.g. :help :set base)" ])
, [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":s", String
":set" ] [String
"[ OPTION [ = VALUE ] ]"] ((String -> REPL ()) -> CommandBody
OptionArg String -> REPL ()
setOptionCmd)
String
"Set an environmental option (:set on its own displays current values)."
String
""
, [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":check" ] [String
"[ EXPR ]"] ((String -> REPL ()) -> CommandBody
ExprArg (REPL [TestReport] -> REPL ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (REPL [TestReport] -> REPL ())
-> (String -> REPL [TestReport]) -> String -> REPL ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QCMode -> String -> REPL [TestReport]
qcCmd QCMode
QCRandom))
String
"Use random testing to check that the argument always returns true.\n(If no argument, check all properties.)"
String
""
, [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":exhaust" ] [String
"[ EXPR ]"] ((String -> REPL ()) -> CommandBody
ExprArg (REPL [TestReport] -> REPL ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (REPL [TestReport] -> REPL ())
-> (String -> REPL [TestReport]) -> String -> REPL ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QCMode -> String -> REPL [TestReport]
qcCmd QCMode
QCExhaust))
String
"Use exhaustive testing to prove that the argument always returns\ntrue. (If no argument, check all properties.)"
String
""
, [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":prove" ] [String
"[ EXPR ]"] ((String -> REPL ()) -> CommandBody
ExprArg String -> REPL ()
proveCmd)
String
"Use an external solver to prove that the argument always returns\ntrue. (If no argument, check all properties.)"
String
""
, [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":sat" ] [String
"[ EXPR ]"] ((String -> REPL ()) -> CommandBody
ExprArg String -> REPL ()
satCmd)
String
"Use a solver to find a satisfying assignment for which the argument\nreturns true. (If no argument, find an assignment for all properties.)"
String
""
, [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":safe" ] [String
"[ EXPR ]"] ((String -> REPL ()) -> CommandBody
ExprArg String -> REPL ()
safeCmd)
String
"Use an external solver to prove that an expression is safe\n(does not encounter run-time errors) for all inputs."
String
""
, [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":debug_specialize" ] [String
"EXPR"]((String -> REPL ()) -> CommandBody
ExprArg String -> REPL ()
specializeCmd)
String
"Do type specialization on a closed expression."
String
""
, [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":eval" ] [String
"EXPR"] ((String -> REPL ()) -> CommandBody
ExprArg String -> REPL ()
refEvalCmd)
String
"Evaluate an expression with the reference evaluator."
String
""
, [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":ast" ] [String
"EXPR"] ((String -> REPL ()) -> CommandBody
ExprArg String -> REPL ()
astOfCmd)
String
"Print out the pre-typechecked AST of a given term."
String
""
, [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":extract-coq" ] [] (REPL () -> CommandBody
NoArg REPL ()
allTerms)
String
"Print out the post-typechecked AST of all currently defined terms,\nin a Coq-parseable format."
String
""
]
commandList :: [CommandDescr]
commandList :: [CommandDescr]
commandList =
[CommandDescr]
nbCommandList [CommandDescr] -> [CommandDescr] -> [CommandDescr]
forall a. [a] -> [a] -> [a]
++
[ [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":q", String
":quit" ] [] (REPL () -> CommandBody
NoArg REPL ()
quitCmd)
String
"Exit the REPL."
String
""
, [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":l", String
":load" ] [String
"FILE"] ((String -> REPL ()) -> CommandBody
FilenameArg String -> REPL ()
loadCmd)
String
"Load a module by filename."
String
""
, [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":r", String
":reload" ] [] (REPL () -> CommandBody
NoArg REPL ()
reloadCmd)
String
"Reload the currently loaded module."
String
""
, [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":e", String
":edit" ] [String
"[ FILE ]"] ((String -> REPL ()) -> CommandBody
FilenameArg String -> REPL ()
editCmd)
String
"Edit FILE or the currently loaded module."
String
""
, [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":!" ] [String
"COMMAND"] ((String -> REPL ()) -> CommandBody
ShellArg String -> REPL ()
runShellCmd)
String
"Execute a command in the shell."
String
""
, [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":cd" ] [String
"DIR"] ((String -> REPL ()) -> CommandBody
FilenameArg String -> REPL ()
cdCmd)
String
"Set the current working directory."
String
""
, [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":m", String
":module" ] [String
"[ MODULE ]"] ((String -> REPL ()) -> CommandBody
FilenameArg String -> REPL ()
moduleCmd)
String
"Load a module by its name."
String
""
, [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":w", String
":writeByteArray" ] [String
"FILE", String
"EXPR"] ((String -> String -> REPL ()) -> CommandBody
FileExprArg String -> String -> REPL ()
writeFileCmd)
String
"Write data of type 'fin n => [n][8]' to a file."
String
""
, [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":readByteArray" ] [String
"FILE"] ((String -> REPL ()) -> CommandBody
FilenameArg String -> REPL ()
readFileCmd)
String
"Read data from a file as type 'fin n => [n][8]', binding\nthe value to variable 'it'."
String
""
, [String]
-> [String] -> CommandBody -> String -> String -> CommandDescr
CommandDescr [ String
":dumptests" ] [String
"FILE", String
"EXPR"] ((String -> String -> REPL ()) -> CommandBody
FileExprArg String -> String -> REPL ()
dumpTestsCmd)
([String] -> String
unlines [ String
"Dump a tab-separated collection of tests for the given"
, String
"expression into a file. The first column in each line is"
, String
"the expected output, and the remainder are the inputs. The"
, String
"number of tests is determined by the \"tests\" option."
])
String
""
]
genHelp :: [CommandDescr] -> [String]
genHelp :: [CommandDescr] -> [String]
genHelp [CommandDescr]
cs = (CommandDescr -> String) -> [CommandDescr] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map CommandDescr -> String
cmdHelp [CommandDescr]
cs
where
cmdHelp :: CommandDescr -> String
cmdHelp CommandDescr
cmd = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [ String
" ", CommandDescr -> String
cmdNames CommandDescr
cmd, ShowS
forall (t :: * -> *) a. Foldable t => t a -> String
pad (CommandDescr -> String
cmdNames CommandDescr
cmd),
String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate (String
"\n " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [Any] -> String
forall (t :: * -> *) a. Foldable t => t a -> String
pad []) (String -> [String]
lines (CommandDescr -> String
cHelp CommandDescr
cmd)) ]
cmdNames :: CommandDescr -> String
cmdNames CommandDescr
cmd = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " (CommandDescr -> [String]
cNames CommandDescr
cmd)
padding :: Int
padding = Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ((CommandDescr -> Int) -> [CommandDescr] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (String -> Int) -> (CommandDescr -> String) -> CommandDescr -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CommandDescr -> String
cmdNames) [CommandDescr]
cs)
pad :: t a -> String
pad t a
n = Int -> Char -> String
forall a. Int -> a -> [a]
replicate (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int
padding Int -> Int -> Int
forall a. Num a => a -> a -> a
- t a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length t a
n)) Char
' '
runCommand :: Command -> REPL CommandExitCode
runCommand :: Command -> REPL CommandExitCode
runCommand Command
c = case Command
c of
Command REPL ()
cmd -> (REPL ()
cmd REPL () -> REPL CommandExitCode -> REPL CommandExitCode
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CommandExitCode -> REPL CommandExitCode
forall (m :: * -> *) a. Monad m => a -> m a
return CommandExitCode
CommandOk) REPL CommandExitCode
-> (REPLException -> REPL CommandExitCode) -> REPL CommandExitCode
forall a. REPL a -> (REPLException -> REPL a) -> REPL a
`Cryptol.REPL.Monad.catch` REPLException -> REPL CommandExitCode
forall a. PP a => a -> REPL CommandExitCode
handler
where
handler :: a -> REPL CommandExitCode
handler a
re = String -> REPL ()
rPutStrLn String
"" REPL () -> REPL () -> REPL ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Doc -> REPL ()
forall a. Show a => a -> REPL ()
rPrint (a -> Doc
forall a. PP a => a -> Doc
pp a
re) REPL () -> REPL CommandExitCode -> REPL CommandExitCode
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CommandExitCode -> REPL CommandExitCode
forall (m :: * -> *) a. Monad m => a -> m a
return CommandExitCode
CommandError
Unknown String
cmd -> do String -> REPL ()
rPutStrLn (String
"Unknown command: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
cmd)
CommandExitCode -> REPL CommandExitCode
forall (m :: * -> *) a. Monad m => a -> m a
return CommandExitCode
CommandError
Ambiguous String
cmd [String]
cmds -> do
String -> REPL ()
rPutStrLn (String
cmd String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" is ambiguous, it could mean one of:")
String -> REPL ()
rPutStrLn (String
"\t" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String]
cmds)
CommandExitCode -> REPL CommandExitCode
forall (m :: * -> *) a. Monad m => a -> m a
return CommandExitCode
CommandError
getPPValOpts :: REPL E.PPOpts
getPPValOpts :: REPL PPOpts
getPPValOpts =
do Int
base <- String -> REPL Int
forall a. IsEnvVal a => String -> REPL a
getKnownUser String
"base"
Bool
ascii <- String -> REPL Bool
forall a. IsEnvVal a => String -> REPL a
getKnownUser String
"ascii"
Int
infLength <- String -> REPL Int
forall a. IsEnvVal a => String -> REPL a
getKnownUser String
"infLength"
Int
fpBase <- String -> REPL Int
forall a. IsEnvVal a => String -> REPL a
getKnownUser String
"fp-base"
String
fpFmtTxt <- String -> REPL String
forall a. IsEnvVal a => String -> REPL a
getKnownUser String
"fp-format"
let fpFmt :: PPFloatFormat
fpFmt = case String -> Maybe PPFloatFormat
parsePPFloatFormat String
fpFmtTxt of
Just PPFloatFormat
f -> PPFloatFormat
f
Maybe PPFloatFormat
Nothing -> String -> [String] -> PPFloatFormat
forall a. HasCallStack => String -> [String] -> a
panic String
"getPPValOpts"
[ String
"Failed to parse fp-format" ]
PPOpts -> REPL PPOpts
forall (m :: * -> *) a. Monad m => a -> m a
return PPOpts :: Bool -> Int -> Int -> Int -> PPFloatFormat -> PPOpts
E.PPOpts { useBase :: Int
E.useBase = Int
base
, useAscii :: Bool
E.useAscii = Bool
ascii
, useInfLength :: Int
E.useInfLength = Int
infLength
, useFPBase :: Int
E.useFPBase = Int
fpBase
, useFPFormat :: PPFloatFormat
E.useFPFormat = PPFloatFormat
fpFmt
}
getEvalOpts :: REPL E.EvalOpts
getEvalOpts :: REPL EvalOpts
getEvalOpts =
do PPOpts
ppOpts <- REPL PPOpts
getPPValOpts
Logger
l <- REPL Logger
getLogger
EvalOpts -> REPL EvalOpts
forall (m :: * -> *) a. Monad m => a -> m a
return EvalOpts :: Logger -> PPOpts -> EvalOpts
E.EvalOpts { evalPPOpts :: PPOpts
E.evalPPOpts = PPOpts
ppOpts, evalLogger :: Logger
E.evalLogger = Logger
l }
evalCmd :: String -> REPL ()
evalCmd :: String -> REPL ()
evalCmd String
str = do
ReplInput PName
ri <- String -> REPL (ReplInput PName)
replParseInput String
str
case ReplInput PName
ri of
P.ExprInput Expr PName
expr -> do
(Value
val,Type
_ty) <- Expr PName -> REPL (Value, Type)
replEvalExpr Expr PName
expr
PPOpts
ppOpts <- REPL PPOpts
getPPValOpts
Doc
valDoc <- Eval Doc -> REPL Doc
forall a. Eval a -> REPL a
rEvalRethrow (Concrete -> PPOpts -> Value -> SEval Concrete Doc
forall sym.
Backend sym =>
sym -> PPOpts -> GenValue sym -> SEval sym Doc
E.ppValue Concrete
Concrete PPOpts
ppOpts Value
val)
String -> REPL ()
rPutStrLn (Doc -> String
forall a. Show a => a -> String
show Doc
valDoc)
P.LetInput Decl PName
decl -> do
Decl PName -> REPL ()
replEvalDecl Decl PName
decl
ReplInput PName
P.EmptyInput ->
() -> REPL ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
printCounterexample :: CounterExampleType -> P.Expr P.PName -> [Concrete.Value] -> REPL ()
printCounterexample :: CounterExampleType -> Expr PName -> [Value] -> REPL ()
printCounterexample CounterExampleType
cexTy Expr PName
pexpr [Value]
vs =
do PPOpts
ppOpts <- REPL PPOpts
getPPValOpts
[Doc]
docs <- (Value -> REPL Doc) -> [Value] -> REPL [Doc]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Eval Doc -> REPL Doc
forall a. Eval a -> REPL a
rEval (Eval Doc -> REPL Doc) -> (Value -> Eval Doc) -> Value -> REPL Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Concrete -> PPOpts -> Value -> SEval Concrete Doc
forall sym.
Backend sym =>
sym -> PPOpts -> GenValue sym -> SEval sym Doc
E.ppValue Concrete
Concrete PPOpts
ppOpts) [Value]
vs
let doc :: Doc
doc = Int -> Expr PName -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
3 Expr PName
pexpr
Doc -> REPL ()
forall a. Show a => a -> REPL ()
rPrint (Doc -> REPL ()) -> Doc -> REPL ()
forall a b. (a -> b) -> a -> b
$ Doc -> Int -> Doc -> Doc
hang Doc
doc Int
2 ([Doc] -> Doc
sep [Doc]
docs) Doc -> Doc -> Doc
<+>
case CounterExampleType
cexTy of
CounterExampleType
SafetyViolation -> String -> Doc
text String
"~> ERROR"
CounterExampleType
PredicateFalsified -> String -> Doc
text String
"= False"
printSatisfyingModel :: P.Expr P.PName -> [Concrete.Value] -> REPL ()
printSatisfyingModel :: Expr PName -> [Value] -> REPL ()
printSatisfyingModel Expr PName
pexpr [Value]
vs =
do PPOpts
ppOpts <- REPL PPOpts
getPPValOpts
[Doc]
docs <- (Value -> REPL Doc) -> [Value] -> REPL [Doc]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Eval Doc -> REPL Doc
forall a. Eval a -> REPL a
rEval (Eval Doc -> REPL Doc) -> (Value -> Eval Doc) -> Value -> REPL Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Concrete -> PPOpts -> Value -> SEval Concrete Doc
forall sym.
Backend sym =>
sym -> PPOpts -> GenValue sym -> SEval sym Doc
E.ppValue Concrete
Concrete PPOpts
ppOpts) [Value]
vs
let doc :: Doc
doc = Int -> Expr PName -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
3 Expr PName
pexpr
Doc -> REPL ()
forall a. Show a => a -> REPL ()
rPrint (Doc -> REPL ()) -> Doc -> REPL ()
forall a b. (a -> b) -> a -> b
$ Doc -> Int -> Doc -> Doc
hang Doc
doc Int
2 ([Doc] -> Doc
sep [Doc]
docs) Doc -> Doc -> Doc
<+> String -> Doc
text (String
"= True")
dumpTestsCmd :: FilePath -> String -> REPL ()
dumpTestsCmd :: String -> String -> REPL ()
dumpTestsCmd String
outFile String
str =
do Expr PName
expr <- String -> REPL (Expr PName)
replParseExpr String
str
(Value
val, Type
ty) <- Expr PName -> REPL (Value, Type)
replEvalExpr Expr PName
expr
PPOpts
ppopts <- REPL PPOpts
getPPValOpts
Int
testNum <- String -> REPL Int
forall a. IsEnvVal a => String -> REPL a
getKnownUser String
"tests" :: REPL Int
TFGen
g <- IO TFGen -> REPL TFGen
forall a. IO a -> REPL a
io IO TFGen
newTFGen
TypeEnv
tenv <- GenEvalEnv Concrete -> TypeEnv
forall sym. GenEvalEnv sym -> TypeEnv
E.envTypes (GenEvalEnv Concrete -> TypeEnv)
-> (DynamicEnv -> GenEvalEnv Concrete) -> DynamicEnv -> TypeEnv
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DynamicEnv -> GenEvalEnv Concrete
M.deEnv (DynamicEnv -> TypeEnv) -> REPL DynamicEnv -> REPL TypeEnv
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> REPL DynamicEnv
getDynEnv
let tyv :: TValue
tyv = TypeEnv -> Type -> TValue
E.evalValType TypeEnv
tenv Type
ty
[Integer -> TFGen -> (Eval Value, TFGen)]
gens <-
case TValue -> Maybe [Gen TFGen Concrete]
forall g. RandomGen g => TValue -> Maybe [Gen g Concrete]
TestR.dumpableType TValue
tyv of
Maybe [Gen TFGen Concrete]
Nothing -> REPLException -> REPL [Integer -> TFGen -> (Eval Value, TFGen)]
forall a. REPLException -> REPL a
raise (Type -> REPLException
TypeNotTestable Type
ty)
Just [Gen TFGen Concrete]
gens -> [Integer -> TFGen -> (Eval Value, TFGen)]
-> REPL [Integer -> TFGen -> (Eval Value, TFGen)]
forall (m :: * -> *) a. Monad m => a -> m a
return [Integer -> TFGen -> (Eval Value, TFGen)]
[Gen TFGen Concrete]
gens
[([Value], Value)]
tests <- IO [([Value], Value)] -> REPL [([Value], Value)]
forall a. IO a -> REPL a
io (IO [([Value], Value)] -> REPL [([Value], Value)])
-> IO [([Value], Value)] -> REPL [([Value], Value)]
forall a b. (a -> b) -> a -> b
$ TFGen
-> [Gen TFGen Concrete] -> Value -> Int -> IO [([Value], Value)]
forall g.
RandomGen g =>
g -> [Gen g Concrete] -> Value -> Int -> IO [([Value], Value)]
TestR.returnTests TFGen
g [Integer -> TFGen -> (Eval Value, TFGen)]
[Gen TFGen Concrete]
gens Value
val Int
testNum
[String]
out <- [([Value], Value)]
-> (([Value], Value) -> REPL String) -> REPL [String]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [([Value], Value)]
tests ((([Value], Value) -> REPL String) -> REPL [String])
-> (([Value], Value) -> REPL String) -> REPL [String]
forall a b. (a -> b) -> a -> b
$
\([Value]
args, Value
x) ->
do [Doc]
argOut <- (Value -> REPL Doc) -> [Value] -> REPL [Doc]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Eval Doc -> REPL Doc
forall a. Eval a -> REPL a
rEval (Eval Doc -> REPL Doc) -> (Value -> Eval Doc) -> Value -> REPL Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Concrete -> PPOpts -> Value -> SEval Concrete Doc
forall sym.
Backend sym =>
sym -> PPOpts -> GenValue sym -> SEval sym Doc
E.ppValue Concrete
Concrete PPOpts
ppopts) [Value]
args
Doc
resOut <- Eval Doc -> REPL Doc
forall a. Eval a -> REPL a
rEval (Concrete -> PPOpts -> Value -> SEval Concrete Doc
forall sym.
Backend sym =>
sym -> PPOpts -> GenValue sym -> SEval sym Doc
E.ppValue Concrete
Concrete PPOpts
ppopts Value
x)
String -> REPL String
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc -> String
renderOneLine Doc
resOut String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\t" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\t" ((Doc -> String) -> [Doc] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Doc -> String
renderOneLine [Doc]
argOut) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\n")
IO () -> REPL ()
forall a. IO a -> REPL a
io (IO () -> REPL ()) -> IO () -> REPL ()
forall a b. (a -> b) -> a -> b
$ String -> String -> IO ()
writeFile String
outFile ([String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String]
out) IO () -> (SomeException -> IO ()) -> IO ()
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`X.catch` SomeException -> IO ()
handler
where
handler :: X.SomeException -> IO ()
handler :: SomeException -> IO ()
handler SomeException
e = String -> IO ()
putStrLn (SomeException -> String
forall e. Exception e => e -> String
X.displayException SomeException
e)
data QCMode = QCRandom | QCExhaust deriving (QCMode -> QCMode -> Bool
(QCMode -> QCMode -> Bool)
-> (QCMode -> QCMode -> Bool) -> Eq QCMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QCMode -> QCMode -> Bool
$c/= :: QCMode -> QCMode -> Bool
== :: QCMode -> QCMode -> Bool
$c== :: QCMode -> QCMode -> Bool
Eq, Int -> QCMode -> ShowS
[QCMode] -> ShowS
QCMode -> String
(Int -> QCMode -> ShowS)
-> (QCMode -> String) -> ([QCMode] -> ShowS) -> Show QCMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QCMode] -> ShowS
$cshowList :: [QCMode] -> ShowS
show :: QCMode -> String
$cshow :: QCMode -> String
showsPrec :: Int -> QCMode -> ShowS
$cshowsPrec :: Int -> QCMode -> ShowS
Show)
qcCmd :: QCMode -> String -> REPL [TestReport]
qcCmd :: QCMode -> String -> REPL [TestReport]
qcCmd QCMode
qcMode String
"" =
do ([Name]
xs,NameDisp
disp) <- REPL ([Name], NameDisp)
getPropertyNames
let nameStr :: a -> String
nameStr a
x = Doc -> String
forall a. Show a => a -> String
show (NameDisp -> Doc -> Doc
fixNameDisp NameDisp
disp (a -> Doc
forall a. PP a => a -> Doc
pp a
x))
if [Name] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Name]
xs
then String -> REPL ()
rPutStrLn String
"There are no properties in scope." REPL () -> REPL [TestReport] -> REPL [TestReport]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> [TestReport] -> REPL [TestReport]
forall (m :: * -> *) a. Monad m => a -> m a
return []
else [[TestReport]] -> [TestReport]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[TestReport]] -> [TestReport])
-> REPL [[TestReport]] -> REPL [TestReport]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([Name] -> (Name -> REPL [TestReport]) -> REPL [[TestReport]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [Name]
xs ((Name -> REPL [TestReport]) -> REPL [[TestReport]])
-> (Name -> REPL [TestReport]) -> REPL [[TestReport]]
forall a b. (a -> b) -> a -> b
$ \Name
x ->
do let str :: String
str = Name -> String
forall a. PP a => a -> String
nameStr Name
x
String -> REPL ()
rPutStr (String -> REPL ()) -> String -> REPL ()
forall a b. (a -> b) -> a -> b
$ String
"property " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
str String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" "
QCMode -> String -> REPL [TestReport]
qcCmd QCMode
qcMode String
str)
qcCmd QCMode
qcMode String
str =
do Expr PName
expr <- String -> REPL (Expr PName)
replParseExpr String
str
(Value
val,Type
ty) <- Expr PName -> REPL (Value, Type)
replEvalExpr Expr PName
expr
Integer
testNum <- (Int -> Integer
forall a. Integral a => a -> Integer
toInteger :: Int -> Integer) (Int -> Integer) -> REPL Int -> REPL Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> REPL Int
forall a. IsEnvVal a => String -> REPL a
getKnownUser String
"tests"
TypeEnv
tenv <- GenEvalEnv Concrete -> TypeEnv
forall sym. GenEvalEnv sym -> TypeEnv
E.envTypes (GenEvalEnv Concrete -> TypeEnv)
-> (DynamicEnv -> GenEvalEnv Concrete) -> DynamicEnv -> TypeEnv
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DynamicEnv -> GenEvalEnv Concrete
M.deEnv (DynamicEnv -> TypeEnv) -> REPL DynamicEnv -> REPL TypeEnv
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> REPL DynamicEnv
getDynEnv
let tyv :: TValue
tyv = TypeEnv -> Type -> TValue
E.evalValType TypeEnv
tenv Type
ty
IORef (Maybe String)
percentRef <- IO (IORef (Maybe String)) -> REPL (IORef (Maybe String))
forall a. IO a -> REPL a
io (IO (IORef (Maybe String)) -> REPL (IORef (Maybe String)))
-> IO (IORef (Maybe String)) -> REPL (IORef (Maybe String))
forall a b. (a -> b) -> a -> b
$ Maybe String -> IO (IORef (Maybe String))
forall a. a -> IO (IORef a)
newIORef Maybe String
forall a. Maybe a
Nothing
IORef Integer
testsRef <- IO (IORef Integer) -> REPL (IORef Integer)
forall a. IO a -> REPL a
io (IO (IORef Integer) -> REPL (IORef Integer))
-> IO (IORef Integer) -> REPL (IORef Integer)
forall a b. (a -> b) -> a -> b
$ Integer -> IO (IORef Integer)
forall a. a -> IO (IORef a)
newIORef Integer
0
case TValue
-> Maybe (Maybe Integer, [TValue], [[Value]], [Gen TFGen Concrete])
forall g.
RandomGen g =>
TValue
-> Maybe (Maybe Integer, [TValue], [[Value]], [Gen g Concrete])
testableType TValue
tyv of
Just (Just Integer
sz,[TValue]
tys,[[Value]]
vss,[Gen TFGen Concrete]
_gens) | QCMode
qcMode QCMode -> QCMode -> Bool
forall a. Eq a => a -> a -> Bool
== QCMode
QCExhaust Bool -> Bool -> Bool
|| Integer
sz Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
testNum -> do
String -> REPL ()
rPutStrLn String
"Using exhaustive testing."
String -> REPL ()
prt String
testingMsg
(TestResult
res,Integer
num) <-
REPL (TestResult, Integer)
-> (SomeException -> REPL (TestResult, Integer))
-> REPL (TestResult, Integer)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
Ex.catch ((Integer -> REPL ())
-> Value -> [[Value]] -> REPL (TestResult, Integer)
forall (m :: * -> *).
MonadIO m =>
(Integer -> m ()) -> Value -> [[Value]] -> m (TestResult, Integer)
exhaustiveTests (\Integer
n -> IORef (Maybe String)
-> IORef Integer -> Integer -> Integer -> REPL ()
forall a.
(Show a, Integral a) =>
IORef (Maybe String) -> IORef a -> a -> a -> REPL ()
ppProgress IORef (Maybe String)
percentRef IORef Integer
testsRef Integer
n Integer
sz)
Value
val [[Value]]
vss)
(\SomeException
ex -> do String -> REPL ()
rPutStrLn String
"\nTest interrupted..."
Integer
num <- IO Integer -> REPL Integer
forall a. IO a -> REPL a
io (IO Integer -> REPL Integer) -> IO Integer -> REPL Integer
forall a b. (a -> b) -> a -> b
$ IORef Integer -> IO Integer
forall a. IORef a -> IO a
readIORef IORef Integer
testsRef
let report :: TestReport
report = TestResult -> String -> Integer -> Maybe Integer -> TestReport
TestReport TestResult
Pass String
str Integer
num (Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
sz)
[Type] -> Expr PName -> Bool -> TestReport -> REPL ()
ppReport ((TValue -> Type) -> [TValue] -> [Type]
forall a b. (a -> b) -> [a] -> [b]
map TValue -> Type
E.tValTy [TValue]
tys) Expr PName
expr Bool
False TestReport
report
String -> REPL ()
rPutStrLn (String -> REPL ()) -> String -> REPL ()
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> String
interruptedExhaust Integer
num Integer
sz
SomeException -> REPL (TestResult, Integer)
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Ex.throwM (SomeException
ex :: Ex.SomeException))
let report :: TestReport
report = TestResult -> String -> Integer -> Maybe Integer -> TestReport
TestReport TestResult
res String
str Integer
num (Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
sz)
REPL ()
delProgress
REPL ()
delTesting
[Type] -> Expr PName -> Bool -> TestReport -> REPL ()
ppReport ((TValue -> Type) -> [TValue] -> [Type]
forall a b. (a -> b) -> [a] -> [b]
map TValue -> Type
E.tValTy [TValue]
tys) Expr PName
expr Bool
True TestReport
report
[TestReport] -> REPL [TestReport]
forall (m :: * -> *) a. Monad m => a -> m a
return [TestReport
report]
Just (Maybe Integer
sz,[TValue]
tys,[[Value]]
_,[Gen TFGen Concrete]
gens) | QCMode
qcMode QCMode -> QCMode -> Bool
forall a. Eq a => a -> a -> Bool
== QCMode
QCRandom -> do
String -> REPL ()
rPutStrLn String
"Using random testing."
String -> REPL ()
prt String
testingMsg
TFGen
g <- IO TFGen -> REPL TFGen
forall a. IO a -> REPL a
io IO TFGen
newTFGen
(TestResult
res,Integer
num) <-
REPL (TestResult, Integer)
-> (SomeException -> REPL (TestResult, Integer))
-> REPL (TestResult, Integer)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
Ex.catch ((Integer -> REPL ())
-> Integer
-> Value
-> [Gen TFGen Concrete]
-> TFGen
-> REPL (TestResult, Integer)
forall (m :: * -> *) g.
(MonadIO m, RandomGen g) =>
(Integer -> m ())
-> Integer
-> Value
-> [Gen g Concrete]
-> g
-> m (TestResult, Integer)
randomTests (\Integer
n -> IORef (Maybe String)
-> IORef Integer -> Integer -> Integer -> REPL ()
forall a.
(Show a, Integral a) =>
IORef (Maybe String) -> IORef a -> a -> a -> REPL ()
ppProgress IORef (Maybe String)
percentRef IORef Integer
testsRef Integer
n Integer
testNum)
Integer
testNum Value
val [Gen TFGen Concrete]
gens TFGen
g)
(\SomeException
ex -> do String -> REPL ()
rPutStrLn String
"\nTest interrupted..."
Integer
num <- IO Integer -> REPL Integer
forall a. IO a -> REPL a
io (IO Integer -> REPL Integer) -> IO Integer -> REPL Integer
forall a b. (a -> b) -> a -> b
$ IORef Integer -> IO Integer
forall a. IORef a -> IO a
readIORef IORef Integer
testsRef
let report :: TestReport
report = TestResult -> String -> Integer -> Maybe Integer -> TestReport
TestReport TestResult
Pass String
str Integer
num Maybe Integer
sz
[Type] -> Expr PName -> Bool -> TestReport -> REPL ()
ppReport ((TValue -> Type) -> [TValue] -> [Type]
forall a b. (a -> b) -> [a] -> [b]
map TValue -> Type
E.tValTy [TValue]
tys) Expr PName
expr Bool
False TestReport
report
case Maybe Integer
sz of
Just Integer
n -> String -> REPL ()
rPutStrLn (String -> REPL ()) -> String -> REPL ()
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> String
coverageString Integer
num Integer
n
Maybe Integer
_ -> () -> REPL ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
SomeException -> REPL (TestResult, Integer)
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Ex.throwM (SomeException
ex :: Ex.SomeException))
let report :: TestReport
report = TestResult -> String -> Integer -> Maybe Integer -> TestReport
TestReport TestResult
res String
str Integer
num Maybe Integer
sz
REPL ()
delProgress
REPL ()
delTesting
[Type] -> Expr PName -> Bool -> TestReport -> REPL ()
ppReport ((TValue -> Type) -> [TValue] -> [Type]
forall a b. (a -> b) -> [a] -> [b]
map TValue -> Type
E.tValTy [TValue]
tys) Expr PName
expr Bool
False TestReport
report
case Maybe Integer
sz of
Just Integer
n | TestResult -> Bool
isPass TestResult
res -> String -> REPL ()
rPutStrLn (String -> REPL ()) -> String -> REPL ()
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> String
coverageString Integer
testNum Integer
n
Maybe Integer
_ -> () -> REPL ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
[TestReport] -> REPL [TestReport]
forall (m :: * -> *) a. Monad m => a -> m a
return [TestReport
report]
Maybe (Maybe Integer, [TValue], [[Value]], [Gen TFGen Concrete])
_ -> REPLException -> REPL [TestReport]
forall a. REPLException -> REPL a
raise (Type -> REPLException
TypeNotTestable Type
ty)
where
testingMsg :: String
testingMsg = String
"Testing... "
interruptedExhaust :: Integer -> Integer -> String
interruptedExhaust Integer
testNum Integer
sz =
let percent :: Double
percent = (Double
100.0 :: Double) Double -> Double -> Double
forall a. Num a => a -> a -> a
* (Integer -> Double
forall a. Num a => Integer -> a
fromInteger Integer
testNum) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Integer -> Double
forall a. Num a => Integer -> a
fromInteger Integer
sz
showValNum :: String
showValNum
| Integer
sz Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
2 Integer -> Integer -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ (Integer
20::Integer) =
String
"2^^" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show (Integer -> Integer
lg2 Integer
sz)
| Bool
otherwise = Integer -> String
forall a. Show a => a -> String
show Integer
sz
in String
"Test coverage: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ Maybe Int -> Double -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
2) Double
percent String
"% ("
String -> ShowS
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
testNum String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" of "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
showValNum
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" values)"
coverageString :: Integer -> Integer -> String
coverageString Integer
testNum Integer
sz =
let (Double
percent, Double
expectedUnique) = Integer -> Integer -> (Double, Double)
expectedCoverage Integer
testNum Integer
sz
showValNum :: String
showValNum
| Integer
sz Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
2 Integer -> Integer -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ (Integer
20::Integer) =
String
"2^^" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show (Integer -> Integer
lg2 Integer
sz)
| Bool
otherwise = Integer -> String
forall a. Show a => a -> String
show Integer
sz
in String
"Expected test coverage: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ Maybe Int -> Double -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
2) Double
percent String
"% ("
String -> ShowS
forall a. [a] -> [a] -> [a]
++ Maybe Int -> Double -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0) Double
expectedUnique String
" of "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
showValNum
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" values)"
totProgressWidth :: Int
totProgressWidth = Int
4
lg2 :: Integer -> Integer
lg2 :: Integer -> Integer
lg2 Integer
x | Integer
x Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
2Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^(Int
1024::Int) = Integer
1024 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer -> Integer
lg2 (Integer
x Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`div` Integer
2Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^(Int
1024::Int))
| Integer
x Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
0 = Integer
0
| Bool
otherwise = let valNumD :: Double
valNumD = Integer -> Double
forall a. Num a => Integer -> a
fromInteger Integer
x :: Double
in Double -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
round (Double -> Integer) -> Double -> Integer
forall a b. (a -> b) -> a -> b
$ Double -> Double -> Double
forall a. Floating a => a -> a -> a
logBase Double
2 Double
valNumD :: Integer
prt :: String -> REPL ()
prt String
msg = String -> REPL ()
rPutStr String
msg REPL () -> REPL () -> REPL ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO () -> REPL ()
forall a. IO a -> REPL a
io (Handle -> IO ()
hFlush Handle
stdout)
prtLn :: String -> REPL ()
prtLn String
msg = String -> REPL ()
rPutStrLn String
msg REPL () -> REPL () -> REPL ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO () -> REPL ()
forall a. IO a -> REPL a
io (Handle -> IO ()
hFlush Handle
stdout)
ppProgress :: IORef (Maybe String) -> IORef a -> a -> a -> REPL ()
ppProgress IORef (Maybe String)
percentRef IORef a
testsRef a
this a
tot =
do IO () -> REPL ()
forall a. IO a -> REPL a
io (IO () -> REPL ()) -> IO () -> REPL ()
forall a b. (a -> b) -> a -> b
$ IORef a -> a -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef a
testsRef a
this
let percent :: String
percent = a -> String
forall a. Show a => a -> String
show (a -> a -> a
forall a. Integral a => a -> a -> a
div (a
100 a -> a -> a
forall a. Num a => a -> a -> a
* a
this) a
tot) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"%"
width :: Int
width = String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
percent
pad :: String
pad = Int -> Char -> String
forall a. Int -> a -> [a]
replicate (Int
totProgressWidth Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
width) Char
' '
REPL () -> REPL ()
unlessBatch (REPL () -> REPL ()) -> REPL () -> REPL ()
forall a b. (a -> b) -> a -> b
$
do Maybe String
oldPercent <- IO (Maybe String) -> REPL (Maybe String)
forall a. IO a -> REPL a
io (IO (Maybe String) -> REPL (Maybe String))
-> IO (Maybe String) -> REPL (Maybe String)
forall a b. (a -> b) -> a -> b
$ IORef (Maybe String) -> IO (Maybe String)
forall a. IORef a -> IO a
readIORef IORef (Maybe String)
percentRef
case Maybe String
oldPercent of
Maybe String
Nothing ->
do IO () -> REPL ()
forall a. IO a -> REPL a
io (IO () -> REPL ()) -> IO () -> REPL ()
forall a b. (a -> b) -> a -> b
$ IORef (Maybe String) -> Maybe String -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Maybe String)
percentRef (String -> Maybe String
forall a. a -> Maybe a
Just String
percent)
String -> REPL ()
prt (String
pad String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
percent)
Just String
p | String
p String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
percent ->
do IO () -> REPL ()
forall a. IO a -> REPL a
io (IO () -> REPL ()) -> IO () -> REPL ()
forall a b. (a -> b) -> a -> b
$ IORef (Maybe String) -> Maybe String -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Maybe String)
percentRef (String -> Maybe String
forall a. a -> Maybe a
Just String
percent)
REPL ()
delProgress
String -> REPL ()
prt (String
pad String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
percent)
Maybe String
_ -> () -> REPL ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
del :: Int -> REPL ()
del Int
n = REPL () -> REPL ()
unlessBatch
(REPL () -> REPL ()) -> REPL () -> REPL ()
forall a b. (a -> b) -> a -> b
$ String -> REPL ()
prt (Int -> Char -> String
forall a. Int -> a -> [a]
replicate Int
n Char
'\BS' String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> Char -> String
forall a. Int -> a -> [a]
replicate Int
n Char
' ' String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> Char -> String
forall a. Int -> a -> [a]
replicate Int
n Char
'\BS')
delTesting :: REPL ()
delTesting = Int -> REPL ()
del (String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
testingMsg)
delProgress :: REPL ()
delProgress = Int -> REPL ()
del Int
totProgressWidth
ppReport :: [Type] -> Expr PName -> Bool -> TestReport -> REPL ()
ppReport [Type]
_tys Expr PName
_expr Bool
isExhaustive (TestReport TestResult
Pass String
_str Integer
testNum Maybe Integer
_testPossible) =
do String -> REPL ()
prtLn (String -> REPL ()) -> String -> REPL ()
forall a b. (a -> b) -> a -> b
$ String
"Passed " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
testNum String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" tests."
Bool -> REPL () -> REPL ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
isExhaustive (String -> REPL ()
rPutStrLn String
"Q.E.D.")
ppReport [Type]
tys Expr PName
expr Bool
_ (TestReport TestResult
failure String
_str Integer
_testNum Maybe Integer
_testPossible) =
[Type] -> Expr PName -> TestResult -> REPL ()
ppFailure [Type]
tys Expr PName
expr TestResult
failure
ppFailure :: [Type] -> Expr PName -> TestResult -> REPL ()
ppFailure [Type]
tys Expr PName
pexpr TestResult
failure = do
PPOpts
opts <- REPL PPOpts
getPPValOpts
case TestResult
failure of
FailFalse [Value]
vs -> do
CounterExampleType -> Expr PName -> [Value] -> REPL ()
printCounterexample CounterExampleType
PredicateFalsified Expr PName
pexpr [Value]
vs
case ([Type]
tys,[Value]
vs) of
([Type
t],[Value
v]) -> Type -> Value -> REPL ()
bindItVariableVal Type
t Value
v
([Type], [Value])
_ -> let fs :: [Ident]
fs = [ String -> Ident
M.packIdent (String
"arg" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (Int
i::Int)) | Int
i <- [ Int
1 .. ] ]
t :: Type
t = RecordMap Ident Type -> Type
T.TRec ([(Ident, Type)] -> RecordMap Ident Type
forall a b. (Show a, Ord a) => [(a, b)] -> RecordMap a b
recordFromFields ([Ident] -> [Type] -> [(Ident, Type)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Ident]
fs [Type]
tys))
v :: Value
v = RecordMap Ident (SEval Concrete Value) -> Value
forall sym.
RecordMap Ident (SEval sym (GenValue sym)) -> GenValue sym
E.VRecord ([(Ident, Eval Value)] -> RecordMap Ident (Eval Value)
forall a b. (Show a, Ord a) => [(a, b)] -> RecordMap a b
recordFromFields ([Ident] -> [Eval Value] -> [(Ident, Eval Value)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Ident]
fs ((Value -> Eval Value) -> [Value] -> [Eval Value]
forall a b. (a -> b) -> [a] -> [b]
map Value -> Eval Value
forall (m :: * -> *) a. Monad m => a -> m a
return [Value]
vs)))
in Type -> Value -> REPL ()
bindItVariableVal Type
t Value
v
FailError EvalError
err [] -> do
String -> REPL ()
prtLn String
"ERROR"
Doc -> REPL ()
forall a. Show a => a -> REPL ()
rPrint (EvalError -> Doc
forall a. PP a => a -> Doc
pp EvalError
err)
FailError EvalError
err [Value]
vs -> do
String -> REPL ()
prtLn String
"ERROR for the following inputs:"
(Value -> REPL ()) -> [Value] -> REPL ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\Value
v -> Doc -> REPL ()
forall a. Show a => a -> REPL ()
rPrint (Doc -> REPL ()) -> REPL Doc -> REPL ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (Eval Doc -> REPL Doc
forall a. Eval a -> REPL a
rEval (Eval Doc -> REPL Doc) -> Eval Doc -> REPL Doc
forall a b. (a -> b) -> a -> b
$ Concrete -> PPOpts -> Value -> SEval Concrete Doc
forall sym.
Backend sym =>
sym -> PPOpts -> GenValue sym -> SEval sym Doc
E.ppValue Concrete
Concrete PPOpts
opts Value
v)) [Value]
vs
Doc -> REPL ()
forall a. Show a => a -> REPL ()
rPrint (EvalError -> Doc
forall a. PP a => a -> Doc
pp EvalError
err)
TestResult
Pass -> String -> [String] -> REPL ()
forall a. HasCallStack => String -> [String] -> a
panic String
"Cryptol.REPL.Command" [String
"unexpected Test.Pass"]
expectedCoverage :: Integer -> Integer -> (Double, Double)
expectedCoverage :: Integer -> Integer -> (Double, Double)
expectedCoverage Integer
testNum Integer
sz =
if Integer
testNum Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0 Bool -> Bool -> Bool
&& Double
proportion Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
0 then
(Double
100.0 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
proportion, Double
szD Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
proportion)
else
(Double
100.0 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
naiveProportion, Double
numD)
where
szD :: Double
szD :: Double
szD = Integer -> Double
forall a. Num a => Integer -> a
fromInteger Integer
sz
numD :: Double
numD :: Double
numD = Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
testNum
naiveProportion :: Double
naiveProportion = Double
numD Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
szD
proportion :: Double
proportion = Double -> Double
forall a. Num a => a -> a
negate (Double -> Double
forall a. Floating a => a -> a
expm1 (Double
numD Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double -> Double
forall a. Floating a => a -> a
log1p (Double -> Double
forall a. Num a => a -> a
negate (Double -> Double
forall a. Fractional a => a -> a
recip Double
szD))))
satCmd, proveCmd :: String -> REPL ()
satCmd :: String -> REPL ()
satCmd = Bool -> String -> REPL ()
cmdProveSat Bool
True
proveCmd :: String -> REPL ()
proveCmd = Bool -> String -> REPL ()
cmdProveSat Bool
False
showProverStats :: Maybe String -> ProverStats -> REPL ()
showProverStats :: Maybe String -> ProverStats -> REPL ()
showProverStats Maybe String
mprover ProverStats
stat = String -> REPL ()
rPutStrLn String
msg
where
msg :: String
msg = String
"(Total Elapsed Time: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ProverStats -> String
SBV.showTDiff ProverStats
stat String -> ShowS
forall a. [a] -> [a] -> [a]
++
String -> ShowS -> Maybe String -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"" (\String
p -> String
", using " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show String
p) Maybe String
mprover String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"
rethrowErrorCall :: REPL a -> REPL a
rethrowErrorCall :: REPL a -> REPL a
rethrowErrorCall REPL a
m = (IORef RW -> IO a) -> REPL a
forall a. (IORef RW -> IO a) -> REPL a
REPL (\IORef RW
r -> REPL a -> IORef RW -> IO a
forall a. REPL a -> IORef RW -> IO a
unREPL REPL a
m IORef RW
r IO a -> [Handler a] -> IO a
forall a. IO a -> [Handler a] -> IO a
`X.catches` [Handler a]
forall a. [Handler a]
hs)
where
hs :: [Handler a]
hs =
[ (ErrorCall -> IO a) -> Handler a
forall a e. Exception e => (e -> IO a) -> Handler a
X.Handler ((ErrorCall -> IO a) -> Handler a)
-> (ErrorCall -> IO a) -> Handler a
forall a b. (a -> b) -> a -> b
$ \ (X.ErrorCallWithLocation String
s String
_) -> REPLException -> IO a
forall e a. Exception e => e -> IO a
X.throwIO (String -> REPLException
SBVError String
s)
, (SBVException -> IO a) -> Handler a
forall a e. Exception e => (e -> IO a) -> Handler a
X.Handler ((SBVException -> IO a) -> Handler a)
-> (SBVException -> IO a) -> Handler a
forall a b. (a -> b) -> a -> b
$ \ SBVException
e -> REPLException -> IO a
forall e a. Exception e => e -> IO a
X.throwIO (SBVException -> REPLException
SBVException SBVException
e)
, (SBVPortfolioException -> IO a) -> Handler a
forall a e. Exception e => (e -> IO a) -> Handler a
X.Handler ((SBVPortfolioException -> IO a) -> Handler a)
-> (SBVPortfolioException -> IO a) -> Handler a
forall a b. (a -> b) -> a -> b
$ \ SBVPortfolioException
e -> REPLException -> IO a
forall e a. Exception e => e -> IO a
X.throwIO (SBVPortfolioException -> REPLException
SBVPortfolioException SBVPortfolioException
e)
, (W4Exception -> IO a) -> Handler a
forall a e. Exception e => (e -> IO a) -> Handler a
X.Handler ((W4Exception -> IO a) -> Handler a)
-> (W4Exception -> IO a) -> Handler a
forall a b. (a -> b) -> a -> b
$ \ W4Exception
e -> REPLException -> IO a
forall e a. Exception e => e -> IO a
X.throwIO (W4Exception -> REPLException
W4Exception W4Exception
e)
]
safeCmd :: String -> REPL ()
safeCmd :: String -> REPL ()
safeCmd String
str = do
String
proverName <- String -> REPL String
forall a. IsEnvVal a => String -> REPL a
getKnownUser String
"prover"
String
fileName <- String -> REPL String
forall a. IsEnvVal a => String -> REPL a
getKnownUser String
"smtfile"
let mfile :: Maybe String
mfile = if String
fileName String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"-" then Maybe String
forall a. Maybe a
Nothing else String -> Maybe String
forall a. a -> Maybe a
Just String
fileName
if String
proverName String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
"offline",String
"sbv-offline",String
"w4-offline"] then
String -> QueryType -> String -> Maybe String -> REPL ()
offlineProveSat String
proverName QueryType
SafetyQuery String
str Maybe String
mfile
else
do (Maybe String
firstProver,ProverResult
result,ProverStats
stats) <- REPL (Maybe String, ProverResult, ProverStats)
-> REPL (Maybe String, ProverResult, ProverStats)
forall a. REPL a -> REPL a
rethrowErrorCall (String
-> QueryType
-> String
-> Maybe String
-> REPL (Maybe String, ProverResult, ProverStats)
onlineProveSat String
proverName QueryType
SafetyQuery String
str Maybe String
mfile)
case ProverResult
result of
ProverResult
EmptyResult ->
String -> [String] -> REPL ()
forall a. HasCallStack => String -> [String] -> a
panic String
"REPL.Command" [ String
"got EmptyResult for online prover query" ]
ProverError String
msg -> String -> REPL ()
rPutStrLn String
msg
ThmResult [Type]
_ts -> String -> REPL ()
rPutStrLn String
"Safe"
CounterExample CounterExampleType
cexType SatResult
tevs -> do
String -> REPL ()
rPutStrLn String
"Counterexample"
let tes :: [(Type, Expr)]
tes = ((Type, Expr, Value) -> (Type, Expr))
-> SatResult -> [(Type, Expr)]
forall a b. (a -> b) -> [a] -> [b]
map ( \(Type
t,Expr
e,Value
_) -> (Type
t,Expr
e)) SatResult
tevs
vs :: [Value]
vs = ((Type, Expr, Value) -> Value) -> SatResult -> [Value]
forall a b. (a -> b) -> [a] -> [b]
map ( \(Type
_,Expr
_,Value
v) -> Value
v) SatResult
tevs
(Type
t,Expr
e) <- String -> Bool -> Either [Type] [(Type, Expr)] -> REPL (Type, Expr)
mkSolverResult String
"counterexample" Bool
False ([(Type, Expr)] -> Either [Type] [(Type, Expr)]
forall a b. b -> Either a b
Right [(Type, Expr)]
tes)
Expr PName
pexpr <- String -> REPL (Expr PName)
replParseExpr String
str
~(EnvBool Bool
yes) <- String -> REPL EnvVal
getUser String
"show-examples"
Bool -> REPL () -> REPL ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
yes (REPL () -> REPL ()) -> REPL () -> REPL ()
forall a b. (a -> b) -> a -> b
$ CounterExampleType -> Expr PName -> [Value] -> REPL ()
printCounterexample CounterExampleType
cexType Expr PName
pexpr [Value]
vs
REPL Name -> REPL ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (REPL Name -> REPL ()) -> REPL Name -> REPL ()
forall a b. (a -> b) -> a -> b
$ Type -> Expr -> REPL Name
bindItVariable Type
t Expr
e
AllSatResult [SatResult]
_ -> do
String -> [String] -> REPL ()
forall a. HasCallStack => String -> [String] -> a
panic String
"REPL.Command" [String
"Unexpected AllSAtResult for ':safe' call"]
Bool
seeStats <- REPL Bool
getUserShowProverStats
Bool -> REPL () -> REPL ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
seeStats (Maybe String -> ProverStats -> REPL ()
showProverStats Maybe String
firstProver ProverStats
stats)
cmdProveSat :: Bool -> String -> REPL ()
cmdProveSat :: Bool -> String -> REPL ()
cmdProveSat Bool
isSat String
"" =
do ([Name]
xs,NameDisp
disp) <- REPL ([Name], NameDisp)
getPropertyNames
let nameStr :: a -> String
nameStr a
x = Doc -> String
forall a. Show a => a -> String
show (NameDisp -> Doc -> Doc
fixNameDisp NameDisp
disp (a -> Doc
forall a. PP a => a -> Doc
pp a
x))
if [Name] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Name]
xs
then String -> REPL ()
rPutStrLn String
"There are no properties in scope."
else [Name] -> (Name -> REPL ()) -> REPL ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Name]
xs ((Name -> REPL ()) -> REPL ()) -> (Name -> REPL ()) -> REPL ()
forall a b. (a -> b) -> a -> b
$ \Name
x ->
do let str :: String
str = Name -> String
forall a. PP a => a -> String
nameStr Name
x
if Bool
isSat
then String -> REPL ()
rPutStr (String -> REPL ()) -> String -> REPL ()
forall a b. (a -> b) -> a -> b
$ String
":sat " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
str String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\n\t"
else String -> REPL ()
rPutStr (String -> REPL ()) -> String -> REPL ()
forall a b. (a -> b) -> a -> b
$ String
":prove " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
str String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\n\t"
Bool -> String -> REPL ()
cmdProveSat Bool
isSat String
str
cmdProveSat Bool
isSat String
str = do
let cexStr :: String
cexStr | Bool
isSat = String
"satisfying assignment"
| Bool
otherwise = String
"counterexample"
QueryType
qtype <- if Bool
isSat then SatNum -> QueryType
SatQuery (SatNum -> QueryType) -> REPL SatNum -> REPL QueryType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> REPL SatNum
getUserSatNum else QueryType -> REPL QueryType
forall (f :: * -> *) a. Applicative f => a -> f a
pure QueryType
ProveQuery
String
proverName <- String -> REPL String
forall a. IsEnvVal a => String -> REPL a
getKnownUser String
"prover"
String
fileName <- String -> REPL String
forall a. IsEnvVal a => String -> REPL a
getKnownUser String
"smtfile"
let mfile :: Maybe String
mfile = if String
fileName String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"-" then Maybe String
forall a. Maybe a
Nothing else String -> Maybe String
forall a. a -> Maybe a
Just String
fileName
if String
proverName String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
"offline",String
"sbv-offline",String
"w4-offline"] then
String -> QueryType -> String -> Maybe String -> REPL ()
offlineProveSat String
proverName QueryType
qtype String
str Maybe String
mfile
else
do (Maybe String
firstProver,ProverResult
result,ProverStats
stats) <- REPL (Maybe String, ProverResult, ProverStats)
-> REPL (Maybe String, ProverResult, ProverStats)
forall a. REPL a -> REPL a
rethrowErrorCall (String
-> QueryType
-> String
-> Maybe String
-> REPL (Maybe String, ProverResult, ProverStats)
onlineProveSat String
proverName QueryType
qtype String
str Maybe String
mfile)
case ProverResult
result of
ProverResult
EmptyResult ->
String -> [String] -> REPL ()
forall a. HasCallStack => String -> [String] -> a
panic String
"REPL.Command" [ String
"got EmptyResult for online prover query" ]
ProverError String
msg -> String -> REPL ()
rPutStrLn String
msg
ThmResult [Type]
ts -> do
String -> REPL ()
rPutStrLn (if Bool
isSat then String
"Unsatisfiable" else String
"Q.E.D.")
(Type
t, Expr
e) <- String -> Bool -> Either [Type] [(Type, Expr)] -> REPL (Type, Expr)
mkSolverResult String
cexStr (Bool -> Bool
not Bool
isSat) ([Type] -> Either [Type] [(Type, Expr)]
forall a b. a -> Either a b
Left [Type]
ts)
REPL Name -> REPL ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (REPL Name -> REPL ()) -> REPL Name -> REPL ()
forall a b. (a -> b) -> a -> b
$ Type -> Expr -> REPL Name
bindItVariable Type
t Expr
e
CounterExample CounterExampleType
cexType SatResult
tevs -> do
String -> REPL ()
rPutStrLn String
"Counterexample"
let tes :: [(Type, Expr)]
tes = ((Type, Expr, Value) -> (Type, Expr))
-> SatResult -> [(Type, Expr)]
forall a b. (a -> b) -> [a] -> [b]
map ( \(Type
t,Expr
e,Value
_) -> (Type
t,Expr
e)) SatResult
tevs
vs :: [Value]
vs = ((Type, Expr, Value) -> Value) -> SatResult -> [Value]
forall a b. (a -> b) -> [a] -> [b]
map ( \(Type
_,Expr
_,Value
v) -> Value
v) SatResult
tevs
(Type
t,Expr
e) <- String -> Bool -> Either [Type] [(Type, Expr)] -> REPL (Type, Expr)
mkSolverResult String
cexStr Bool
isSat ([(Type, Expr)] -> Either [Type] [(Type, Expr)]
forall a b. b -> Either a b
Right [(Type, Expr)]
tes)
Expr PName
pexpr <- String -> REPL (Expr PName)
replParseExpr String
str
~(EnvBool Bool
yes) <- String -> REPL EnvVal
getUser String
"show-examples"
Bool -> REPL () -> REPL ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
yes (REPL () -> REPL ()) -> REPL () -> REPL ()
forall a b. (a -> b) -> a -> b
$ CounterExampleType -> Expr PName -> [Value] -> REPL ()
printCounterexample CounterExampleType
cexType Expr PName
pexpr [Value]
vs
REPL Name -> REPL ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (REPL Name -> REPL ()) -> REPL Name -> REPL ()
forall a b. (a -> b) -> a -> b
$ Type -> Expr -> REPL Name
bindItVariable Type
t Expr
e
AllSatResult [SatResult]
tevss -> do
String -> REPL ()
rPutStrLn String
"Satisfiable"
let tess :: [[(Type, Expr)]]
tess = (SatResult -> [(Type, Expr)]) -> [SatResult] -> [[(Type, Expr)]]
forall a b. (a -> b) -> [a] -> [b]
map (((Type, Expr, Value) -> (Type, Expr))
-> SatResult -> [(Type, Expr)]
forall a b. (a -> b) -> [a] -> [b]
map (((Type, Expr, Value) -> (Type, Expr))
-> SatResult -> [(Type, Expr)])
-> ((Type, Expr, Value) -> (Type, Expr))
-> SatResult
-> [(Type, Expr)]
forall a b. (a -> b) -> a -> b
$ \(Type
t,Expr
e,Value
_) -> (Type
t,Expr
e)) [SatResult]
tevss
vss :: [[Value]]
vss = (SatResult -> [Value]) -> [SatResult] -> [[Value]]
forall a b. (a -> b) -> [a] -> [b]
map (((Type, Expr, Value) -> Value) -> SatResult -> [Value]
forall a b. (a -> b) -> [a] -> [b]
map (((Type, Expr, Value) -> Value) -> SatResult -> [Value])
-> ((Type, Expr, Value) -> Value) -> SatResult -> [Value]
forall a b. (a -> b) -> a -> b
$ \(Type
_,Expr
_,Value
v) -> Value
v) [SatResult]
tevss
[(Type, Expr)]
resultRecs <- ([(Type, Expr)] -> REPL (Type, Expr))
-> [[(Type, Expr)]] -> REPL [(Type, Expr)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (String -> Bool -> Either [Type] [(Type, Expr)] -> REPL (Type, Expr)
mkSolverResult String
cexStr Bool
isSat (Either [Type] [(Type, Expr)] -> REPL (Type, Expr))
-> ([(Type, Expr)] -> Either [Type] [(Type, Expr)])
-> [(Type, Expr)]
-> REPL (Type, Expr)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Type, Expr)] -> Either [Type] [(Type, Expr)]
forall a b. b -> Either a b
Right) [[(Type, Expr)]]
tess
let collectTes :: [(a, b)] -> (a, [b])
collectTes [(a, b)]
tes = (a
t, [b]
es)
where
([a]
ts, [b]
es) = [(a, b)] -> ([a], [b])
forall a b. [(a, b)] -> ([a], [b])
unzip [(a, b)]
tes
t :: a
t = case [a] -> [a]
forall a. Eq a => [a] -> [a]
nub [a]
ts of
[a
t'] -> a
t'
[a]
_ -> String -> [String] -> a
forall a. HasCallStack => String -> [String] -> a
panic String
"REPL.Command.onlineProveSat"
[ String
"satisfying assignments with different types" ]
(Type
ty, [Expr]
exprs) =
case [(Type, Expr)]
resultRecs of
[] -> String -> [String] -> (Type, [Expr])
forall a. HasCallStack => String -> [String] -> a
panic String
"REPL.Command.onlineProveSat"
[ String
"no satisfying assignments after mkSolverResult" ]
[(Type
t, Expr
e)] -> (Type
t, [Expr
e])
[(Type, Expr)]
_ -> [(Type, Expr)] -> (Type, [Expr])
forall a b. Eq a => [(a, b)] -> (a, [b])
collectTes [(Type, Expr)]
resultRecs
Expr PName
pexpr <- String -> REPL (Expr PName)
replParseExpr String
str
~(EnvBool Bool
yes) <- String -> REPL EnvVal
getUser String
"show-examples"
Bool -> REPL () -> REPL ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
yes (REPL () -> REPL ()) -> REPL () -> REPL ()
forall a b. (a -> b) -> a -> b
$ [[Value]] -> ([Value] -> REPL ()) -> REPL ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [[Value]]
vss (Expr PName -> [Value] -> REPL ()
printSatisfyingModel Expr PName
pexpr)
case (Type
ty, [Expr]
exprs) of
(Type
t, [Expr
e]) -> REPL Name -> REPL ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (REPL Name -> REPL ()) -> REPL Name -> REPL ()
forall a b. (a -> b) -> a -> b
$ Type -> Expr -> REPL Name
bindItVariable Type
t Expr
e
(Type
t, [Expr]
es ) -> Type -> [Expr] -> REPL ()
bindItVariables Type
t [Expr]
es
Bool
seeStats <- REPL Bool
getUserShowProverStats
Bool -> REPL () -> REPL ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
seeStats (Maybe String -> ProverStats -> REPL ()
showProverStats Maybe String
firstProver ProverStats
stats)
onlineProveSat :: String
-> QueryType
-> String -> Maybe FilePath
-> REPL (Maybe String,ProverResult,ProverStats)
onlineProveSat :: String
-> QueryType
-> String
-> Maybe String
-> REPL (Maybe String, ProverResult, ProverStats)
onlineProveSat String
proverName QueryType
qtype String
str Maybe String
mfile = do
Bool
verbose <- String -> REPL Bool
forall a. IsEnvVal a => String -> REPL a
getKnownUser String
"debug"
Bool
modelValidate <- REPL Bool
getUserProverValidate
Expr PName
parseExpr <- String -> REPL (Expr PName)
replParseExpr String
str
(Expr Name
_, Expr
expr, Schema
schema) <- Expr PName -> REPL (Expr Name, Expr, Schema)
replCheckExpr Expr PName
parseExpr
Expr -> REPL ()
forall a. FreeVars a => a -> REPL ()
validEvalContext Expr
expr
Schema -> REPL ()
forall a. FreeVars a => a -> REPL ()
validEvalContext Schema
schema
[DeclGroup]
decls <- (DynamicEnv -> [DeclGroup]) -> REPL DynamicEnv -> REPL [DeclGroup]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap DynamicEnv -> [DeclGroup]
M.deDecls REPL DynamicEnv
getDynEnv
IORef ProverStats
timing <- IO (IORef ProverStats) -> REPL (IORef ProverStats)
forall a. IO a -> REPL a
io (ProverStats -> IO (IORef ProverStats)
forall a. a -> IO (IORef a)
newIORef ProverStats
0)
~(EnvBool Bool
ignoreSafety) <- String -> REPL EnvVal
getUser String
"ignore-safety"
let cmd :: ProverCommand
cmd = ProverCommand :: QueryType
-> String
-> Bool
-> Bool
-> IORef ProverStats
-> [DeclGroup]
-> Maybe String
-> Expr
-> Schema
-> Bool
-> ProverCommand
ProverCommand {
pcQueryType :: QueryType
pcQueryType = QueryType
qtype
, pcProverName :: String
pcProverName = String
proverName
, pcVerbose :: Bool
pcVerbose = Bool
verbose
, pcValidate :: Bool
pcValidate = Bool
modelValidate
, pcProverStats :: IORef ProverStats
pcProverStats = IORef ProverStats
timing
, pcExtraDecls :: [DeclGroup]
pcExtraDecls = [DeclGroup]
decls
, pcSmtFile :: Maybe String
pcSmtFile = Maybe String
mfile
, pcExpr :: Expr
pcExpr = Expr
expr
, pcSchema :: Schema
pcSchema = Schema
schema
, pcIgnoreSafety :: Bool
pcIgnoreSafety = Bool
ignoreSafety
}
(Maybe String
firstProver, ProverResult
res) <- REPL (Either SBVProverConfig W4ProverConfig)
getProverConfig REPL (Either SBVProverConfig W4ProverConfig)
-> (Either SBVProverConfig W4ProverConfig
-> REPL (Maybe String, ProverResult))
-> REPL (Maybe String, ProverResult)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Left SBVProverConfig
sbvCfg -> ModuleCmd (Maybe String, ProverResult)
-> REPL (Maybe String, ProverResult)
forall a. ModuleCmd a -> REPL a
liftModuleCmd (ModuleCmd (Maybe String, ProverResult)
-> REPL (Maybe String, ProverResult))
-> ModuleCmd (Maybe String, ProverResult)
-> REPL (Maybe String, ProverResult)
forall a b. (a -> b) -> a -> b
$ SBVProverConfig
-> ProverCommand -> ModuleCmd (Maybe String, ProverResult)
SBV.satProve SBVProverConfig
sbvCfg ProverCommand
cmd
Right W4ProverConfig
w4Cfg ->
do ~(EnvBool Bool
hashConsing) <- String -> REPL EnvVal
getUser String
"hash-consing"
~(EnvBool Bool
warnUninterp) <- String -> REPL EnvVal
getUser String
"warnUninterp"
ModuleCmd (Maybe String, ProverResult)
-> REPL (Maybe String, ProverResult)
forall a. ModuleCmd a -> REPL a
liftModuleCmd (ModuleCmd (Maybe String, ProverResult)
-> REPL (Maybe String, ProverResult))
-> ModuleCmd (Maybe String, ProverResult)
-> REPL (Maybe String, ProverResult)
forall a b. (a -> b) -> a -> b
$ W4ProverConfig
-> Bool
-> Bool
-> ProverCommand
-> ModuleCmd (Maybe String, ProverResult)
W4.satProve W4ProverConfig
w4Cfg Bool
hashConsing Bool
warnUninterp ProverCommand
cmd
ProverStats
stas <- IO ProverStats -> REPL ProverStats
forall a. IO a -> REPL a
io (IORef ProverStats -> IO ProverStats
forall a. IORef a -> IO a
readIORef IORef ProverStats
timing)
(Maybe String, ProverResult, ProverStats)
-> REPL (Maybe String, ProverResult, ProverStats)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe String
firstProver,ProverResult
res,ProverStats
stas)
offlineProveSat :: String -> QueryType -> String -> Maybe FilePath -> REPL ()
offlineProveSat :: String -> QueryType -> String -> Maybe String -> REPL ()
offlineProveSat String
proverName QueryType
qtype String
str Maybe String
mfile = do
Bool
verbose <- String -> REPL Bool
forall a. IsEnvVal a => String -> REPL a
getKnownUser String
"debug"
Bool
modelValidate <- REPL Bool
getUserProverValidate
Expr PName
parseExpr <- String -> REPL (Expr PName)
replParseExpr String
str
(Expr Name
_, Expr
expr, Schema
schema) <- Expr PName -> REPL (Expr Name, Expr, Schema)
replCheckExpr Expr PName
parseExpr
[DeclGroup]
decls <- (DynamicEnv -> [DeclGroup]) -> REPL DynamicEnv -> REPL [DeclGroup]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap DynamicEnv -> [DeclGroup]
M.deDecls REPL DynamicEnv
getDynEnv
IORef ProverStats
timing <- IO (IORef ProverStats) -> REPL (IORef ProverStats)
forall a. IO a -> REPL a
io (ProverStats -> IO (IORef ProverStats)
forall a. a -> IO (IORef a)
newIORef ProverStats
0)
~(EnvBool Bool
ignoreSafety) <- String -> REPL EnvVal
getUser String
"ignore-safety"
let cmd :: ProverCommand
cmd = ProverCommand :: QueryType
-> String
-> Bool
-> Bool
-> IORef ProverStats
-> [DeclGroup]
-> Maybe String
-> Expr
-> Schema
-> Bool
-> ProverCommand
ProverCommand {
pcQueryType :: QueryType
pcQueryType = QueryType
qtype
, pcProverName :: String
pcProverName = String
proverName
, pcVerbose :: Bool
pcVerbose = Bool
verbose
, pcValidate :: Bool
pcValidate = Bool
modelValidate
, pcProverStats :: IORef ProverStats
pcProverStats = IORef ProverStats
timing
, pcExtraDecls :: [DeclGroup]
pcExtraDecls = [DeclGroup]
decls
, pcSmtFile :: Maybe String
pcSmtFile = Maybe String
mfile
, pcExpr :: Expr
pcExpr = Expr
expr
, pcSchema :: Schema
pcSchema = Schema
schema
, pcIgnoreSafety :: Bool
pcIgnoreSafety = Bool
ignoreSafety
}
String -> IO ()
put <- REPL (String -> IO ())
getPutStr
let putLn :: String -> IO ()
putLn String
x = String -> IO ()
put (String
x String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\n")
let displayMsg :: IO ()
displayMsg =
do let filename :: String
filename = String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"standard output" Maybe String
mfile
let satWord :: String
satWord = case QueryType
qtype of
SatQuery SatNum
_ -> String
"satisfiability"
QueryType
ProveQuery -> String
"validity"
QueryType
SafetyQuery -> String
"safety"
String -> IO ()
putLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$
String
"Writing to SMT-Lib file " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
filename String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"..."
String -> IO ()
putLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$
String
"To determine the " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
satWord String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
" of the expression, use an external SMT solver."
REPL (Either SBVProverConfig W4ProverConfig)
getProverConfig REPL (Either SBVProverConfig W4ProverConfig)
-> (Either SBVProverConfig W4ProverConfig -> REPL ()) -> REPL ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Left SBVProverConfig
sbvCfg ->
do Either String String
result <- ModuleCmd (Either String String) -> REPL (Either String String)
forall a. ModuleCmd a -> REPL a
liftModuleCmd (ModuleCmd (Either String String) -> REPL (Either String String))
-> ModuleCmd (Either String String) -> REPL (Either String String)
forall a b. (a -> b) -> a -> b
$ SBVProverConfig
-> ProverCommand -> ModuleCmd (Either String String)
SBV.satProveOffline SBVProverConfig
sbvCfg ProverCommand
cmd
case Either String String
result of
Left String
msg -> String -> REPL ()
rPutStrLn String
msg
Right String
smtlib -> do
IO () -> REPL ()
forall a. IO a -> REPL a
io (IO () -> REPL ()) -> IO () -> REPL ()
forall a b. (a -> b) -> a -> b
$ IO ()
displayMsg
case Maybe String
mfile of
Just String
path -> IO () -> REPL ()
forall a. IO a -> REPL a
io (IO () -> REPL ()) -> IO () -> REPL ()
forall a b. (a -> b) -> a -> b
$ String -> String -> IO ()
writeFile String
path String
smtlib
Maybe String
Nothing -> String -> REPL ()
rPutStr String
smtlib
Right W4ProverConfig
w4Cfg ->
do ~(EnvBool Bool
hashConsing) <- String -> REPL EnvVal
getUser String
"hash-consing"
~(EnvBool Bool
warnUninterp) <- String -> REPL EnvVal
getUser String
"warnUninterp"
Maybe String
result <- ModuleCmd (Maybe String) -> REPL (Maybe String)
forall a. ModuleCmd a -> REPL a
liftModuleCmd (ModuleCmd (Maybe String) -> REPL (Maybe String))
-> ModuleCmd (Maybe String) -> REPL (Maybe String)
forall a b. (a -> b) -> a -> b
$ W4ProverConfig
-> Bool
-> Bool
-> ProverCommand
-> ((Handle -> IO ()) -> IO ())
-> ModuleCmd (Maybe String)
W4.satProveOffline W4ProverConfig
w4Cfg Bool
hashConsing Bool
warnUninterp ProverCommand
cmd (((Handle -> IO ()) -> IO ()) -> ModuleCmd (Maybe String))
-> ((Handle -> IO ()) -> IO ()) -> ModuleCmd (Maybe String)
forall a b. (a -> b) -> a -> b
$ \Handle -> IO ()
f ->
do IO ()
displayMsg
case Maybe String
mfile of
Just String
path ->
IO Handle -> (Handle -> IO ()) -> (Handle -> IO ()) -> IO ()
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
X.bracket (String -> IOMode -> IO Handle
openFile String
path IOMode
WriteMode) Handle -> IO ()
hClose Handle -> IO ()
f
Maybe String
Nothing ->
String -> (Handle -> IO ()) -> IO ()
forall a. String -> (Handle -> IO a) -> IO a
withRWTempFile String
"smtOutput.tmp" ((Handle -> IO ()) -> IO ()) -> (Handle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Handle
h ->
do Handle -> IO ()
f Handle
h
Handle -> SeekMode -> Integer -> IO ()
hSeek Handle
h SeekMode
AbsoluteSeek Integer
0
Handle -> IO String
hGetContents Handle
h IO String -> (String -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> IO ()
put
case Maybe String
result of
Just String
msg -> String -> REPL ()
rPutStrLn String
msg
Maybe String
Nothing -> () -> REPL ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
rIdent :: M.Ident
rIdent :: Ident
rIdent = String -> Ident
M.packIdent String
"result"
mkSolverResult :: String
-> Bool
-> Either [T.Type] [(T.Type, T.Expr)]
-> REPL (T.Type, T.Expr)
mkSolverResult :: String -> Bool -> Either [Type] [(Type, Expr)] -> REPL (Type, Expr)
mkSolverResult String
thing Bool
result Either [Type] [(Type, Expr)]
earg =
do PrimMap
prims <- REPL PrimMap
getPrimMap
let addError :: Type -> (Type, Expr)
addError Type
t = (Type
t, PrimMap -> Type -> String -> Expr
T.eError PrimMap
prims Type
t (String
"no " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
thing String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" available"))
argF :: [((Ident, Type), (Ident, Expr))]
argF = case Either [Type] [(Type, Expr)]
earg of
Left [Type]
ts -> [(Type, Expr)] -> [((Ident, Type), (Ident, Expr))]
forall b b. [(b, b)] -> [((Ident, b), (Ident, b))]
mkArgs ((Type -> (Type, Expr)) -> [Type] -> [(Type, Expr)]
forall a b. (a -> b) -> [a] -> [b]
map Type -> (Type, Expr)
addError [Type]
ts)
Right [(Type, Expr)]
tes -> [(Type, Expr)] -> [((Ident, Type), (Ident, Expr))]
forall b b. [(b, b)] -> [((Ident, b), (Ident, b))]
mkArgs [(Type, Expr)]
tes
eTrue :: Expr
eTrue = PrimMap -> PrimIdent -> Expr
T.ePrim PrimMap
prims (Text -> PrimIdent
M.prelPrim Text
"True")
eFalse :: Expr
eFalse = PrimMap -> PrimIdent -> Expr
T.ePrim PrimMap
prims (Text -> PrimIdent
M.prelPrim Text
"False")
resultE :: Expr
resultE = if Bool
result then Expr
eTrue else Expr
eFalse
rty :: Type
rty = RecordMap Ident Type -> Type
T.TRec ([(Ident, Type)] -> RecordMap Ident Type
forall a b. (Show a, Ord a) => [(a, b)] -> RecordMap a b
recordFromFields ([(Ident, Type)] -> RecordMap Ident Type)
-> [(Ident, Type)] -> RecordMap Ident Type
forall a b. (a -> b) -> a -> b
$ [(Ident
rIdent, Type
T.tBit )] [(Ident, Type)] -> [(Ident, Type)] -> [(Ident, Type)]
forall a. [a] -> [a] -> [a]
++ (((Ident, Type), (Ident, Expr)) -> (Ident, Type))
-> [((Ident, Type), (Ident, Expr))] -> [(Ident, Type)]
forall a b. (a -> b) -> [a] -> [b]
map ((Ident, Type), (Ident, Expr)) -> (Ident, Type)
forall a b. (a, b) -> a
fst [((Ident, Type), (Ident, Expr))]
argF)
re :: Expr
re = RecordMap Ident Expr -> Expr
T.ERec ([(Ident, Expr)] -> RecordMap Ident Expr
forall a b. (Show a, Ord a) => [(a, b)] -> RecordMap a b
recordFromFields ([(Ident, Expr)] -> RecordMap Ident Expr)
-> [(Ident, Expr)] -> RecordMap Ident Expr
forall a b. (a -> b) -> a -> b
$ [(Ident
rIdent, Expr
resultE)] [(Ident, Expr)] -> [(Ident, Expr)] -> [(Ident, Expr)]
forall a. [a] -> [a] -> [a]
++ (((Ident, Type), (Ident, Expr)) -> (Ident, Expr))
-> [((Ident, Type), (Ident, Expr))] -> [(Ident, Expr)]
forall a b. (a -> b) -> [a] -> [b]
map ((Ident, Type), (Ident, Expr)) -> (Ident, Expr)
forall a b. (a, b) -> b
snd [((Ident, Type), (Ident, Expr))]
argF)
(Type, Expr) -> REPL (Type, Expr)
forall (m :: * -> *) a. Monad m => a -> m a
return (Type
rty, Expr
re)
where
mkArgs :: [(b, b)] -> [((Ident, b), (Ident, b))]
mkArgs [(b, b)]
tes = (Int -> (b, b) -> ((Ident, b), (Ident, b)))
-> [Int] -> [(b, b)] -> [((Ident, b), (Ident, b))]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int -> (b, b) -> ((Ident, b), (Ident, b))
forall a b b. Show a => a -> (b, b) -> ((Ident, b), (Ident, b))
mkArg [Int
1 :: Int ..] [(b, b)]
tes
where
mkArg :: a -> (b, b) -> ((Ident, b), (Ident, b))
mkArg a
n (b
t,b
e) =
let argName :: Ident
argName = String -> Ident
M.packIdent (String
"arg" String -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
n)
in ((Ident
argName,b
t),(Ident
argName,b
e))
specializeCmd :: String -> REPL ()
specializeCmd :: String -> REPL ()
specializeCmd String
str = do
Expr PName
parseExpr <- String -> REPL (Expr PName)
replParseExpr String
str
(Expr Name
_, Expr
expr, Schema
schema) <- Expr PName -> REPL (Expr Name, Expr, Schema)
replCheckExpr Expr PName
parseExpr
Expr
spexpr <- Expr -> REPL Expr
replSpecExpr Expr
expr
String -> REPL ()
rPutStrLn String
"Expression type:"
Doc -> REPL ()
forall a. Show a => a -> REPL ()
rPrint (Doc -> REPL ()) -> Doc -> REPL ()
forall a b. (a -> b) -> a -> b
$ Schema -> Doc
forall a. PP a => a -> Doc
pp Schema
schema
String -> REPL ()
rPutStrLn String
"Original expression:"
String -> REPL ()
rPutStrLn (String -> REPL ()) -> String -> REPL ()
forall a b. (a -> b) -> a -> b
$ Expr -> String
forall a. PP (WithNames a) => a -> String
dump Expr
expr
String -> REPL ()
rPutStrLn String
"Specialized expression:"
String -> REPL ()
rPutStrLn (String -> REPL ()) -> String -> REPL ()
forall a b. (a -> b) -> a -> b
$ Expr -> String
forall a. PP (WithNames a) => a -> String
dump Expr
spexpr
refEvalCmd :: String -> REPL ()
refEvalCmd :: String -> REPL ()
refEvalCmd String
str = do
Expr PName
parseExpr <- String -> REPL (Expr PName)
replParseExpr String
str
(Expr Name
_, Expr
expr, Schema
schema) <- Expr PName -> REPL (Expr Name, Expr, Schema)
replCheckExpr Expr PName
parseExpr
Expr -> REPL ()
forall a. FreeVars a => a -> REPL ()
validEvalContext Expr
expr
Schema -> REPL ()
forall a. FreeVars a => a -> REPL ()
validEvalContext Schema
schema
E Value
val <- ModuleCmd (E Value) -> REPL (E Value)
forall a. ModuleCmd a -> REPL a
liftModuleCmd (IO (ModuleRes (E Value)) -> IO (ModuleRes (E Value))
forall a. IO a -> IO a
rethrowEvalError (IO (ModuleRes (E Value)) -> IO (ModuleRes (E Value)))
-> ModuleCmd (E Value) -> ModuleCmd (E Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> ModuleCmd (E Value)
R.evaluate Expr
expr)
PPOpts
opts <- REPL PPOpts
getPPValOpts
Doc -> REPL ()
forall a. Show a => a -> REPL ()
rPrint (Doc -> REPL ()) -> Doc -> REPL ()
forall a b. (a -> b) -> a -> b
$ PPOpts -> E Value -> Doc
R.ppEValue PPOpts
opts E Value
val
astOfCmd :: String -> REPL ()
astOfCmd :: String -> REPL ()
astOfCmd String
str = do
Expr PName
expr <- String -> REPL (Expr PName)
replParseExpr String
str
(Expr Name
re,Expr
_,Schema
_) <- Expr PName -> REPL (Expr Name, Expr, Schema)
replCheckExpr (Expr PName -> Expr PName
forall t. NoPos t => t -> t
P.noPos Expr PName
expr)
Expr Int -> REPL ()
forall a. Show a => a -> REPL ()
rPrint ((Name -> Int) -> Expr Name -> Expr Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Name -> Int
M.nameUnique Expr Name
re)
allTerms :: REPL ()
allTerms :: REPL ()
allTerms = do
ModuleEnv
me <- REPL ModuleEnv
getModuleEnv
Doc -> REPL ()
forall a. Show a => a -> REPL ()
rPrint (Doc -> REPL ()) -> Doc -> REPL ()
forall a b. (a -> b) -> a -> b
$ [DeclGroup] -> Doc
forall t. ShowParseable t => t -> Doc
T.showParseable ([DeclGroup] -> Doc) -> [DeclGroup] -> Doc
forall a b. (a -> b) -> a -> b
$ (Module -> [DeclGroup]) -> [Module] -> [DeclGroup]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Module -> [DeclGroup]
T.mDecls ([Module] -> [DeclGroup]) -> [Module] -> [DeclGroup]
forall a b. (a -> b) -> a -> b
$ ModuleEnv -> [Module]
M.loadedModules ModuleEnv
me
typeOfCmd :: String -> REPL ()
typeOfCmd :: String -> REPL ()
typeOfCmd String
str = do
Expr PName
expr <- String -> REPL (Expr PName)
replParseExpr String
str
(Expr Name
_re,Expr
def,Schema
sig) <- Expr PName -> REPL (Expr Name, Expr, Schema)
replCheckExpr Expr PName
expr
REPL () -> REPL ()
whenDebug (String -> REPL ()
rPutStrLn (Expr -> String
forall a. PP (WithNames a) => a -> String
dump Expr
def))
NameDisp
fDisp <- ModContext -> NameDisp
M.mctxNameDisp (ModContext -> NameDisp) -> REPL ModContext -> REPL NameDisp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> REPL ModContext
getFocusedEnv
Doc -> REPL ()
forall a. Show a => a -> REPL ()
rPrint (Doc -> REPL ()) -> Doc -> REPL ()
forall a b. (a -> b) -> a -> b
$ NameDisp -> Doc -> Doc
runDoc NameDisp
fDisp (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Int -> Expr PName -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
2 Expr PName
expr Doc -> Doc -> Doc
<+> String -> Doc
text String
":" Doc -> Doc -> Doc
<+> Schema -> Doc
forall a. PP a => a -> Doc
pp Schema
sig
readFileCmd :: FilePath -> REPL ()
readFileCmd :: String -> REPL ()
readFileCmd String
fp = do
Maybe ByteString
bytes <- String
-> (SomeException -> REPL (Maybe ByteString))
-> REPL (Maybe ByteString)
replReadFile String
fp (\SomeException
err -> String -> REPL ()
rPutStrLn (SomeException -> String
forall a. Show a => a -> String
show SomeException
err) REPL () -> REPL (Maybe ByteString) -> REPL (Maybe ByteString)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Maybe ByteString -> REPL (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing)
case Maybe ByteString
bytes of
Maybe ByteString
Nothing -> () -> REPL ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just ByteString
bs ->
do PrimMap
pm <- REPL PrimMap
getPrimMap
let val :: Integer
val = ByteString -> Integer
byteStringToInteger ByteString
bs
let len :: Int
len = ByteString -> Int
BS.length ByteString
bs
let split :: Expr
split = PrimMap -> PrimIdent -> Expr
T.ePrim PrimMap
pm (Text -> PrimIdent
M.prelPrim Text
"split")
let number :: Expr
number = PrimMap -> PrimIdent -> Expr
T.ePrim PrimMap
pm (Text -> PrimIdent
M.prelPrim Text
"number")
let f :: Expr
f = Expr -> Expr
T.EProofApp ((Expr -> Type -> Expr) -> Expr -> [Type] -> Expr
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl Expr -> Type -> Expr
T.ETApp Expr
split [Int -> Type
forall a. Integral a => a -> Type
T.tNum Int
len, Integer -> Type
forall a. Integral a => a -> Type
T.tNum (Integer
8::Integer), Type
T.tBit])
let t :: Type
t = Type -> Type
T.tWord (Integer -> Type
forall a. Integral a => a -> Type
T.tNum (Int -> Integer
forall a. Integral a => a -> Integer
toInteger Int
len Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
8))
let x :: Expr
x = Expr -> Expr
T.EProofApp (Expr -> Type -> Expr
T.ETApp (Expr -> Type -> Expr
T.ETApp Expr
number (Integer -> Type
forall a. Integral a => a -> Type
T.tNum Integer
val)) Type
t)
let expr :: Expr
expr = Expr -> Expr -> Expr
T.EApp Expr
f Expr
x
REPL Name -> REPL ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (REPL Name -> REPL ()) -> REPL Name -> REPL ()
forall a b. (a -> b) -> a -> b
$ Type -> Expr -> REPL Name
bindItVariable (Int -> Type
T.tString Int
len) Expr
expr
byteStringToInteger :: BS.ByteString -> Integer
byteStringToInteger :: ByteString -> Integer
byteStringToInteger ByteString
bs
| Int
l Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = Integer
0
| Int
l Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = Word8 -> Integer
forall a. Integral a => a -> Integer
toInteger (ByteString -> Word8
BS.head ByteString
bs)
| Bool
otherwise = Integer
x1 Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftL` (Int
l2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8) Integer -> Integer -> Integer
forall a. Bits a => a -> a -> a
.|. Integer
x2
where
l :: Int
l = ByteString -> Int
BS.length ByteString
bs
l1 :: Int
l1 = Int
l Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2
l2 :: Int
l2 = Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
l1
(ByteString
bs1, ByteString
bs2) = Int -> ByteString -> (ByteString, ByteString)
BS.splitAt Int
l1 ByteString
bs
x1 :: Integer
x1 = ByteString -> Integer
byteStringToInteger ByteString
bs1
x2 :: Integer
x2 = ByteString -> Integer
byteStringToInteger ByteString
bs2
writeFileCmd :: FilePath -> String -> REPL ()
writeFileCmd :: String -> String -> REPL ()
writeFileCmd String
file String
str = do
Expr PName
expr <- String -> REPL (Expr PName)
replParseExpr String
str
(Value
val,Type
ty) <- Expr PName -> REPL (Value, Type)
replEvalExpr Expr PName
expr
if Bool -> Bool
not (Type -> Bool
tIsByteSeq Type
ty)
then Doc -> REPL ()
forall a. Show a => a -> REPL ()
rPrint (Doc -> REPL ()) -> Doc -> REPL ()
forall a b. (a -> b) -> a -> b
$ Doc
"Cannot write expression of types other than [n][8]."
Doc -> Doc -> Doc
<+> Doc
"Type was: " Doc -> Doc -> Doc
<+> Type -> Doc
forall a. PP a => a -> Doc
pp Type
ty
else String -> ByteString -> REPL ()
wf String
file (ByteString -> REPL ()) -> REPL ByteString -> REPL ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Value -> REPL ByteString
serializeValue Value
val
where
wf :: String -> ByteString -> REPL ()
wf String
fp ByteString
bytes = String -> ByteString -> (SomeException -> REPL ()) -> REPL ()
replWriteFile String
fp ByteString
bytes (String -> REPL ()
rPutStrLn (String -> REPL ())
-> (SomeException -> String) -> SomeException -> REPL ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeException -> String
forall a. Show a => a -> String
show)
tIsByteSeq :: Type -> Bool
tIsByteSeq Type
x = Bool -> ((Type, Type) -> Bool) -> Maybe (Type, Type) -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False
(Type -> Bool
tIsByte (Type -> Bool) -> ((Type, Type) -> Type) -> (Type, Type) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Type, Type) -> Type
forall a b. (a, b) -> b
snd)
(Type -> Maybe (Type, Type)
T.tIsSeq Type
x)
tIsByte :: Type -> Bool
tIsByte Type
x = Bool -> ((Type, Type) -> Bool) -> Maybe (Type, Type) -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False
(\(Type
n,Type
b) -> Type -> Bool
T.tIsBit Type
b Bool -> Bool -> Bool
&& Type -> Maybe Integer
T.tIsNum Type
n Maybe Integer -> Maybe Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
8)
(Type -> Maybe (Type, Type)
T.tIsSeq Type
x)
serializeValue :: Value -> REPL ByteString
serializeValue (E.VSeq Integer
n SeqMap Concrete
vs) = do
[BV]
ws <- Eval [BV] -> REPL [BV]
forall a. Eval a -> REPL a
rEval
((Eval Value -> Eval BV) -> [Eval Value] -> Eval [BV]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Eval Value -> (Value -> Eval BV) -> Eval BV
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Concrete -> String -> Value -> SEval Concrete (SWord Concrete)
forall sym.
Backend sym =>
sym -> String -> GenValue sym -> SEval sym (SWord sym)
E.fromVWord Concrete
Concrete String
"serializeValue") ([Eval Value] -> Eval [BV]) -> [Eval Value] -> Eval [BV]
forall a b. (a -> b) -> a -> b
$ Integer -> SeqMap Concrete -> [SEval Concrete Value]
forall n sym.
Integral n =>
n -> SeqMap sym -> [SEval sym (GenValue sym)]
E.enumerateSeqMap Integer
n SeqMap Concrete
vs)
ByteString -> REPL ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> REPL ByteString) -> ByteString -> REPL ByteString
forall a b. (a -> b) -> a -> b
$ [Word8] -> ByteString
BS.pack ([Word8] -> ByteString) -> [Word8] -> ByteString
forall a b. (a -> b) -> a -> b
$ (BV -> Word8) -> [BV] -> [Word8]
forall a b. (a -> b) -> [a] -> [b]
map BV -> Word8
forall b. Num b => BV -> b
serializeByte [BV]
ws
serializeValue Value
_ =
String -> [String] -> REPL ByteString
forall a. HasCallStack => String -> [String] -> a
panic String
"Cryptol.REPL.Command.writeFileCmd"
[String
"Impossible: Non-VSeq value of type [n][8]."]
serializeByte :: BV -> b
serializeByte (Concrete.BV Integer
_ Integer
v) = Integer -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer
v Integer -> Integer -> Integer
forall a. Bits a => a -> a -> a
.&. Integer
0xFF)
rEval :: E.Eval a -> REPL a
rEval :: Eval a -> REPL a
rEval Eval a
m = IO a -> REPL a
forall a. IO a -> REPL a
io (Eval a -> IO a
forall a. Eval a -> IO a
E.runEval Eval a
m)
rEvalRethrow :: E.Eval a -> REPL a
rEvalRethrow :: Eval a -> REPL a
rEvalRethrow Eval a
m = IO a -> REPL a
forall a. IO a -> REPL a
io (IO a -> REPL a) -> IO a -> REPL a
forall a b. (a -> b) -> a -> b
$ IO a -> IO a
forall a. IO a -> IO a
rethrowEvalError (IO a -> IO a) -> IO a -> IO a
forall a b. (a -> b) -> a -> b
$ Eval a -> IO a
forall a. Eval a -> IO a
E.runEval Eval a
m
reloadCmd :: REPL ()
reloadCmd :: REPL ()
reloadCmd = do
Maybe LoadedModule
mb <- REPL (Maybe LoadedModule)
getLoadedMod
case Maybe LoadedModule
mb of
Just LoadedModule
lm ->
case LoadedModule -> Maybe ModName
lName LoadedModule
lm of
Just ModName
m | ModName -> Bool
M.isParamInstModName ModName
m -> ModuleCmd (ModulePath, Module) -> REPL ()
loadHelper (ModName -> ModuleCmd (ModulePath, Module)
M.loadModuleByName ModName
m)
Maybe ModName
_ -> case LoadedModule -> ModulePath
lPath LoadedModule
lm of
M.InFile String
f -> String -> REPL ()
loadCmd String
f
ModulePath
_ -> () -> REPL ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Maybe LoadedModule
Nothing -> () -> REPL ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
editCmd :: String -> REPL ()
editCmd :: String -> REPL ()
editCmd String
path =
do Maybe String
mbE <- REPL (Maybe String)
getEditPath
Maybe LoadedModule
mbL <- REPL (Maybe LoadedModule)
getLoadedMod
if Bool -> Bool
not (String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
path)
then do Bool -> REPL () -> REPL ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Maybe LoadedModule -> Bool
forall a. Maybe a -> Bool
isNothing Maybe LoadedModule
mbL)
(REPL () -> REPL ()) -> REPL () -> REPL ()
forall a b. (a -> b) -> a -> b
$ LoadedModule -> REPL ()
setLoadedMod LoadedModule :: Maybe ModName -> ModulePath -> LoadedModule
LoadedModule { lName :: Maybe ModName
lName = Maybe ModName
forall a. Maybe a
Nothing
, lPath :: ModulePath
lPath = String -> ModulePath
M.InFile String
path }
String -> REPL ()
doEdit String
path
else case [Maybe ModulePath] -> Maybe ModulePath
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum [ String -> ModulePath
M.InFile (String -> ModulePath) -> Maybe String -> Maybe ModulePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String
mbE, LoadedModule -> ModulePath
lPath (LoadedModule -> ModulePath)
-> Maybe LoadedModule -> Maybe ModulePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe LoadedModule
mbL ] of
Maybe ModulePath
Nothing -> String -> REPL ()
rPutStrLn String
"No filed to edit."
Just ModulePath
p ->
case ModulePath
p of
M.InFile String
f -> String -> REPL ()
doEdit String
f
M.InMem String
l ByteString
bs -> String -> ByteString -> (String -> REPL Bool) -> REPL Bool
forall a. String -> ByteString -> (String -> REPL a) -> REPL a
withROTempFile String
l ByteString
bs String -> REPL Bool
replEdit REPL Bool -> REPL () -> REPL ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> REPL ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
where
doEdit :: String -> REPL ()
doEdit String
p =
do String -> REPL ()
setEditPath String
p
Bool
_ <- String -> REPL Bool
replEdit String
p
REPL ()
reloadCmd
withRWTempFile :: String -> (Handle -> IO a) -> IO a
withRWTempFile :: String -> (Handle -> IO a) -> IO a
withRWTempFile String
name Handle -> IO a
k =
IO (String, Handle)
-> ((String, Handle) -> IO ())
-> ((String, Handle) -> IO a)
-> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
X.bracket
(do String
tmp <- IO String
getTemporaryDirectory
let esc :: Char -> Char
esc Char
c = if Char -> Bool
isAscii Char
c Bool -> Bool -> Bool
&& Char -> Bool
isAlphaNum Char
c then Char
c else Char
'_'
String -> String -> IO (String, Handle)
openTempFile String
tmp ((Char -> Char) -> ShowS
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
esc String
name))
(\(String
nm,Handle
h) -> Handle -> IO ()
hClose Handle
h IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO ()
removeFile String
nm)
(Handle -> IO a
k (Handle -> IO a)
-> ((String, Handle) -> Handle) -> (String, Handle) -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, Handle) -> Handle
forall a b. (a, b) -> b
snd)
withROTempFile :: String -> ByteString -> (FilePath -> REPL a) -> REPL a
withROTempFile :: String -> ByteString -> (String -> REPL a) -> REPL a
withROTempFile String
name ByteString
cnt String -> REPL a
k =
do (String
path,Handle
h) <- REPL (String, Handle)
mkTmp
do String -> Handle -> REPL ()
forall (m :: * -> *). MonadIO m => String -> Handle -> m ()
mkFile String
path Handle
h
String -> REPL a
k String
path
REPL a -> REPL () -> REPL a
forall a b. REPL a -> REPL b -> REPL a
`finally` IO () -> REPL ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (do Handle -> IO ()
hClose Handle
h
String -> IO ()
removeFile String
path)
where
mkTmp :: REPL (String, Handle)
mkTmp =
IO (String, Handle) -> REPL (String, Handle)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (String, Handle) -> REPL (String, Handle))
-> IO (String, Handle) -> REPL (String, Handle)
forall a b. (a -> b) -> a -> b
$
do String
tmp <- IO String
getTemporaryDirectory
let esc :: Char -> Char
esc Char
c = if Char -> Bool
isAscii Char
c Bool -> Bool -> Bool
&& Char -> Bool
isAlphaNum Char
c then Char
c else Char
'_'
String -> String -> IO (String, Handle)
openTempFile String
tmp ((Char -> Char) -> ShowS
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
esc String
name String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
".cry")
mkFile :: String -> Handle -> m ()
mkFile String
path Handle
h =
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$
do Handle -> ByteString -> IO ()
BS8.hPutStrLn Handle
h ByteString
cnt
Handle -> IO ()
hFlush Handle
h
String -> Permissions -> IO ()
setPermissions String
path (Bool -> Permissions -> Permissions
setOwnerReadable Bool
True Permissions
emptyPermissions)
moduleCmd :: String -> REPL ()
moduleCmd :: String -> REPL ()
moduleCmd String
modString
| String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
modString = () -> REPL ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = do
case String -> Maybe ModName
parseModName String
modString of
Just ModName
m -> ModuleCmd (ModulePath, Module) -> REPL ()
loadHelper (ModName -> ModuleCmd (ModulePath, Module)
M.loadModuleByName ModName
m)
Maybe ModName
Nothing -> String -> REPL ()
rPutStrLn String
"Invalid module name."
loadPrelude :: REPL ()
loadPrelude :: REPL ()
loadPrelude = String -> REPL ()
moduleCmd (String -> REPL ()) -> String -> REPL ()
forall a b. (a -> b) -> a -> b
$ Doc -> String
forall a. Show a => a -> String
show (Doc -> String) -> Doc -> String
forall a b. (a -> b) -> a -> b
$ ModName -> Doc
forall a. PP a => a -> Doc
pp ModName
M.preludeName
loadCmd :: FilePath -> REPL ()
loadCmd :: String -> REPL ()
loadCmd String
path
| String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
path = () -> REPL ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = do String -> REPL ()
setEditPath String
path
LoadedModule -> REPL ()
setLoadedMod LoadedModule :: Maybe ModName -> ModulePath -> LoadedModule
LoadedModule { lName :: Maybe ModName
lName = Maybe ModName
forall a. Maybe a
Nothing
, lPath :: ModulePath
lPath = String -> ModulePath
M.InFile String
path
}
ModuleCmd (ModulePath, Module) -> REPL ()
loadHelper (String -> ModuleCmd (ModulePath, Module)
M.loadModuleByPath String
path)
loadHelper :: M.ModuleCmd (M.ModulePath,T.Module) -> REPL ()
loadHelper :: ModuleCmd (ModulePath, Module) -> REPL ()
loadHelper ModuleCmd (ModulePath, Module)
how =
do REPL ()
clearLoadedMod
(ModulePath
path,Module
m) <- ModuleCmd (ModulePath, Module) -> REPL (ModulePath, Module)
forall a. ModuleCmd a -> REPL a
liftModuleCmd ModuleCmd (ModulePath, Module)
how
REPL () -> REPL ()
whenDebug (String -> REPL ()
rPutStrLn (Module -> String
forall a. PP (WithNames a) => a -> String
dump Module
m))
LoadedModule -> REPL ()
setLoadedMod LoadedModule :: Maybe ModName -> ModulePath -> LoadedModule
LoadedModule
{ lName :: Maybe ModName
lName = ModName -> Maybe ModName
forall a. a -> Maybe a
Just (Module -> ModName
T.mName Module
m)
, lPath :: ModulePath
lPath = ModulePath
path
}
case ModulePath
path of
M.InFile String
f -> String -> REPL ()
setEditPath String
f
M.InMem {} -> REPL ()
clearEditPath
DynamicEnv -> REPL ()
setDynEnv DynamicEnv
forall a. Monoid a => a
mempty
versionCmd :: REPL ()
versionCmd :: REPL ()
versionCmd = (String -> REPL ()) -> REPL ()
forall (m :: * -> *). Monad m => (String -> m ()) -> m ()
displayVersion String -> REPL ()
rPutStrLn
quitCmd :: REPL ()
quitCmd :: REPL ()
quitCmd = REPL ()
stop
browseCmd :: String -> REPL ()
browseCmd :: String -> REPL ()
browseCmd String
input = do
let mnames :: [ModName]
mnames = (String -> ModName) -> [String] -> [ModName]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> ModName
M.textToModName (Text -> ModName) -> (String -> Text) -> String -> ModName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack) (String -> [String]
words String
input)
[ModName]
validModNames <- (:) ModName
M.interactiveName ([ModName] -> [ModName]) -> REPL [ModName] -> REPL [ModName]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> REPL [ModName]
getModNames
let checkModName :: ModName -> REPL ()
checkModName ModName
m =
Bool -> REPL () -> REPL ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (ModName
m ModName -> [ModName] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ModName]
validModNames) (REPL () -> REPL ()) -> REPL () -> REPL ()
forall a b. (a -> b) -> a -> b
$
String -> REPL ()
rPutStrLn (String
"error: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ModName -> String
forall a. Show a => a -> String
show ModName
m String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" is not a loaded module.")
(ModName -> REPL ()) -> [ModName] -> REPL ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ModName -> REPL ()
checkModName [ModName]
mnames
ModContext
fe <- REPL ModContext
getFocusedEnv
let params :: IfaceParams
params = ModContext -> IfaceParams
M.mctxParams ModContext
fe
iface :: IfaceDecls
iface = ModContext -> IfaceDecls
M.mctxDecls ModContext
fe
names :: NamingEnv
names = ModContext -> NamingEnv
M.mctxNames ModContext
fe
disp :: NameDisp
disp = ModContext -> NameDisp
M.mctxNameDisp ModContext
fe
provV :: Map Name DeclProvenance
provV = ModContext -> Map Name DeclProvenance
M.mctxValueProvenance ModContext
fe
provT :: Map Name DeclProvenance
provT = ModContext -> Map Name DeclProvenance
M.mctxTypeProvenace ModContext
fe
let t -> Bool
f &&& :: (t -> Bool) -> (t -> Bool) -> t -> Bool
&&& t -> Bool
g = \t
x -> t -> Bool
f t
x Bool -> Bool -> Bool
&& t -> Bool
g t
x
isUser :: Name -> Bool
isUser Name
x = case Name -> NameInfo
M.nameInfo Name
x of
M.Declared ModName
_ NameSource
M.SystemName -> Bool
False
NameInfo
_ -> Bool
True
inSet :: Set a -> a -> Bool
inSet Set a
s a
x = a
x a -> Set a -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set a
s
let (Set Name
visibleTypes,Set Name
visibleDecls) = NamingEnv -> (Set Name, Set Name)
M.visibleNames NamingEnv
names
restricted :: Name -> Bool
restricted = if [ModName] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ModName]
mnames then Bool -> Name -> Bool
forall a b. a -> b -> a
const Bool
True else [ModName] -> Name -> Bool
hasAnyModName [ModName]
mnames
visibleType :: Name -> Bool
visibleType = Name -> Bool
isUser (Name -> Bool) -> (Name -> Bool) -> Name -> Bool
forall t. (t -> Bool) -> (t -> Bool) -> t -> Bool
&&& Name -> Bool
restricted (Name -> Bool) -> (Name -> Bool) -> Name -> Bool
forall t. (t -> Bool) -> (t -> Bool) -> t -> Bool
&&& Set Name -> Name -> Bool
forall a. Ord a => Set a -> a -> Bool
inSet Set Name
visibleTypes
visibleDecl :: Name -> Bool
visibleDecl = Name -> Bool
isUser (Name -> Bool) -> (Name -> Bool) -> Name -> Bool
forall t. (t -> Bool) -> (t -> Bool) -> t -> Bool
&&& Name -> Bool
restricted (Name -> Bool) -> (Name -> Bool) -> Name -> Bool
forall t. (t -> Bool) -> (t -> Bool) -> t -> Bool
&&& Set Name -> Name -> Bool
forall a. Ord a => Set a -> a -> Bool
inSet Set Name
visibleDecls
(Name -> Bool)
-> (Name -> Bool) -> IfaceParams -> NameDisp -> REPL ()
browseMParams Name -> Bool
visibleType Name -> Bool
visibleDecl IfaceParams
params NameDisp
disp
(Name -> Bool)
-> Map Name DeclProvenance -> IfaceDecls -> NameDisp -> REPL ()
browseTSyns Name -> Bool
visibleType Map Name DeclProvenance
provT IfaceDecls
iface NameDisp
disp
(Name -> Bool)
-> Map Name DeclProvenance -> IfaceDecls -> NameDisp -> REPL ()
browsePrimTys Name -> Bool
visibleType Map Name DeclProvenance
provT IfaceDecls
iface NameDisp
disp
(Name -> Bool)
-> Map Name DeclProvenance -> IfaceDecls -> NameDisp -> REPL ()
browseNewtypes Name -> Bool
visibleType Map Name DeclProvenance
provT IfaceDecls
iface NameDisp
disp
(Name -> Bool)
-> Map Name DeclProvenance -> IfaceDecls -> NameDisp -> REPL ()
browseVars Name -> Bool
visibleDecl Map Name DeclProvenance
provV IfaceDecls
iface NameDisp
disp
browseMParams :: (M.Name -> Bool) -> (M.Name -> Bool) ->
M.IfaceParams -> NameDisp -> REPL ()
browseMParams :: (Name -> Bool)
-> (Name -> Bool) -> IfaceParams -> NameDisp -> REPL ()
browseMParams Name -> Bool
visT Name -> Bool
visD M.IfaceParams { [Located Type]
Map Name ModVParam
Map Name ModTParam
ifParamFuns :: IfaceParams -> Map Name ModVParam
ifParamConstraints :: IfaceParams -> [Located Type]
ifParamTypes :: IfaceParams -> Map Name ModTParam
ifParamFuns :: Map Name ModVParam
ifParamConstraints :: [Located Type]
ifParamTypes :: Map Name ModTParam
.. } NameDisp
names =
do NameDisp -> (ModTParam -> Doc) -> String -> [ModTParam] -> REPL ()
forall a. NameDisp -> (a -> Doc) -> String -> [a] -> REPL ()
ppBlock NameDisp
names ModTParam -> Doc
ppParamTy String
"Type Parameters"
((Name -> Bool)
-> (ModTParam -> Name) -> Map Name ModTParam -> [ModTParam]
forall a k. (Name -> Bool) -> (a -> Name) -> Map k a -> [a]
sorted Name -> Bool
visT ModTParam -> Name
T.mtpName Map Name ModTParam
ifParamTypes)
NameDisp -> (ModVParam -> Doc) -> String -> [ModVParam] -> REPL ()
forall a. NameDisp -> (a -> Doc) -> String -> [a] -> REPL ()
ppBlock NameDisp
names ModVParam -> Doc
ppParamFu String
"Value Parameters"
((Name -> Bool)
-> (ModVParam -> Name) -> Map Name ModVParam -> [ModVParam]
forall a k. (Name -> Bool) -> (a -> Name) -> Map k a -> [a]
sorted Name -> Bool
visD ModVParam -> Name
T.mvpName Map Name ModVParam
ifParamFuns)
where
ppParamTy :: ModTParam -> Doc
ppParamTy T.ModTParam { Int
Maybe Text
Name
Kind
mtpDoc :: ModTParam -> Maybe Text
mtpNumber :: ModTParam -> Int
mtpKind :: ModTParam -> Kind
mtpDoc :: Maybe Text
mtpNumber :: Int
mtpKind :: Kind
mtpName :: Name
mtpName :: ModTParam -> Name
.. } = Doc -> Int -> Doc -> Doc
hang (Doc
"type" Doc -> Doc -> Doc
<+> Name -> Doc
forall a. PP a => a -> Doc
pp Name
mtpName Doc -> Doc -> Doc
<+> Doc
":")
Int
2 (Kind -> Doc
forall a. PP a => a -> Doc
pp Kind
mtpKind)
ppParamFu :: ModVParam -> Doc
ppParamFu T.ModVParam { Maybe Text
Maybe Fixity
Name
Schema
mvpFixity :: ModVParam -> Maybe Fixity
mvpDoc :: ModVParam -> Maybe Text
mvpType :: ModVParam -> Schema
mvpFixity :: Maybe Fixity
mvpDoc :: Maybe Text
mvpType :: Schema
mvpName :: Name
mvpName :: ModVParam -> Name
.. } = Doc -> Int -> Doc -> Doc
hang (Name -> Doc
forall a. PP a => a -> Doc
pp Name
mvpName Doc -> Doc -> Doc
<+> Doc
":") Int
2 (Schema -> Doc
forall a. PP a => a -> Doc
pp Schema
mvpType)
sorted :: (Name -> Bool) -> (a -> Name) -> Map k a -> [a]
sorted Name -> Bool
vis a -> Name
nm Map k a
mp = (a -> a -> Ordering) -> [a] -> [a]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (NameDisp -> Name -> Name -> Ordering
M.cmpNameDisplay NameDisp
names (Name -> Name -> Ordering) -> (a -> Name) -> a -> a -> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` a -> Name
nm)
([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
filter (Name -> Bool
vis (Name -> Bool) -> (a -> Name) -> a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Name
nm) ([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ Map k a -> [a]
forall k a. Map k a -> [a]
Map.elems Map k a
mp
type Prov = Map M.Name M.DeclProvenance
browsePrimTys :: (M.Name -> Bool) -> Prov -> M.IfaceDecls -> NameDisp -> REPL ()
browsePrimTys :: (Name -> Bool)
-> Map Name DeclProvenance -> IfaceDecls -> NameDisp -> REPL ()
browsePrimTys Name -> Bool
isVisible Map Name DeclProvenance
prov M.IfaceDecls { Map Name IfaceAbstractType
Map Name IfaceNewtype
Map Name IfaceTySyn
Map Name IfaceDecl
ifDecls :: IfaceDecls -> Map Name IfaceDecl
ifAbstractTypes :: IfaceDecls -> Map Name IfaceAbstractType
ifNewtypes :: IfaceDecls -> Map Name IfaceNewtype
ifTySyns :: IfaceDecls -> Map Name IfaceTySyn
ifDecls :: Map Name IfaceDecl
ifAbstractTypes :: Map Name IfaceAbstractType
ifNewtypes :: Map Name IfaceNewtype
ifTySyns :: Map Name IfaceTySyn
.. } NameDisp
names =
[IfaceAbstractType] -> Section IfaceAbstractType -> REPL ()
forall a. [a] -> Section a -> REPL ()
ppSection (Map Name IfaceAbstractType -> [IfaceAbstractType]
forall k a. Map k a -> [a]
Map.elems Map Name IfaceAbstractType
ifAbstractTypes)
Section :: forall a.
String
-> (a -> Name)
-> (Name -> Bool)
-> Map Name DeclProvenance
-> NameDisp
-> (a -> Doc)
-> Section a
Section { secName :: String
secName = String
"Primitive Types"
, secEntryName :: IfaceAbstractType -> Name
secEntryName = IfaceAbstractType -> Name
T.atName
, secProvenance :: Map Name DeclProvenance
secProvenance = Map Name DeclProvenance
prov
, secDisp :: NameDisp
secDisp = NameDisp
names
, secPP :: IfaceAbstractType -> Doc
secPP = IfaceAbstractType -> Doc
ppA
, secVisible :: Name -> Bool
secVisible = Name -> Bool
isVisible
}
where
ppA :: IfaceAbstractType -> Doc
ppA IfaceAbstractType
a = Name -> Doc
forall a. PP a => a -> Doc
pp (IfaceAbstractType -> Name
T.atName IfaceAbstractType
a) Doc -> Doc -> Doc
<+> Doc
":" Doc -> Doc -> Doc
<+> Kind -> Doc
forall a. PP a => a -> Doc
pp (IfaceAbstractType -> Kind
T.atKind IfaceAbstractType
a)
browseTSyns :: (M.Name -> Bool) -> Prov -> M.IfaceDecls -> NameDisp -> REPL ()
browseTSyns :: (Name -> Bool)
-> Map Name DeclProvenance -> IfaceDecls -> NameDisp -> REPL ()
browseTSyns Name -> Bool
isVisible Map Name DeclProvenance
prov M.IfaceDecls { Map Name IfaceAbstractType
Map Name IfaceNewtype
Map Name IfaceTySyn
Map Name IfaceDecl
ifDecls :: Map Name IfaceDecl
ifAbstractTypes :: Map Name IfaceAbstractType
ifNewtypes :: Map Name IfaceNewtype
ifTySyns :: Map Name IfaceTySyn
ifDecls :: IfaceDecls -> Map Name IfaceDecl
ifAbstractTypes :: IfaceDecls -> Map Name IfaceAbstractType
ifNewtypes :: IfaceDecls -> Map Name IfaceNewtype
ifTySyns :: IfaceDecls -> Map Name IfaceTySyn
.. } NameDisp
names =
do [IfaceTySyn] -> Section IfaceTySyn -> REPL ()
forall a. [a] -> Section a -> REPL ()
ppSection [IfaceTySyn]
tss
Section :: forall a.
String
-> (a -> Name)
-> (Name -> Bool)
-> Map Name DeclProvenance
-> NameDisp
-> (a -> Doc)
-> Section a
Section { secName :: String
secName = String
"Type Synonyms"
, secEntryName :: IfaceTySyn -> Name
secEntryName = IfaceTySyn -> Name
T.tsName
, secProvenance :: Map Name DeclProvenance
secProvenance = Map Name DeclProvenance
prov
, secDisp :: NameDisp
secDisp = NameDisp
names
, secVisible :: Name -> Bool
secVisible = Name -> Bool
isVisible
, secPP :: IfaceTySyn -> Doc
secPP = IfaceTySyn -> Doc
forall a. PP a => a -> Doc
pp
}
[IfaceTySyn] -> Section IfaceTySyn -> REPL ()
forall a. [a] -> Section a -> REPL ()
ppSection [IfaceTySyn]
cts
Section :: forall a.
String
-> (a -> Name)
-> (Name -> Bool)
-> Map Name DeclProvenance
-> NameDisp
-> (a -> Doc)
-> Section a
Section { secName :: String
secName = String
"Constraint Synonyms"
, secEntryName :: IfaceTySyn -> Name
secEntryName = IfaceTySyn -> Name
T.tsName
, secProvenance :: Map Name DeclProvenance
secProvenance = Map Name DeclProvenance
prov
, secDisp :: NameDisp
secDisp = NameDisp
names
, secVisible :: Name -> Bool
secVisible = Name -> Bool
isVisible
, secPP :: IfaceTySyn -> Doc
secPP = IfaceTySyn -> Doc
forall a. PP a => a -> Doc
pp
}
where
([IfaceTySyn]
cts,[IfaceTySyn]
tss) = (IfaceTySyn -> Bool)
-> [IfaceTySyn] -> ([IfaceTySyn], [IfaceTySyn])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition IfaceTySyn -> Bool
isCtrait (Map Name IfaceTySyn -> [IfaceTySyn]
forall k a. Map k a -> [a]
Map.elems Map Name IfaceTySyn
ifTySyns)
isCtrait :: IfaceTySyn -> Bool
isCtrait IfaceTySyn
t = Kind -> Kind
T.kindResult (Type -> Kind
forall t. HasKind t => t -> Kind
T.kindOf (IfaceTySyn -> Type
T.tsDef IfaceTySyn
t)) Kind -> Kind -> Bool
forall a. Eq a => a -> a -> Bool
== Kind
T.KProp
browseNewtypes ::
(M.Name -> Bool) -> Prov -> M.IfaceDecls -> NameDisp -> REPL ()
browseNewtypes :: (Name -> Bool)
-> Map Name DeclProvenance -> IfaceDecls -> NameDisp -> REPL ()
browseNewtypes Name -> Bool
isVisible Map Name DeclProvenance
prov M.IfaceDecls { Map Name IfaceAbstractType
Map Name IfaceNewtype
Map Name IfaceTySyn
Map Name IfaceDecl
ifDecls :: Map Name IfaceDecl
ifAbstractTypes :: Map Name IfaceAbstractType
ifNewtypes :: Map Name IfaceNewtype
ifTySyns :: Map Name IfaceTySyn
ifDecls :: IfaceDecls -> Map Name IfaceDecl
ifAbstractTypes :: IfaceDecls -> Map Name IfaceAbstractType
ifNewtypes :: IfaceDecls -> Map Name IfaceNewtype
ifTySyns :: IfaceDecls -> Map Name IfaceTySyn
.. } NameDisp
names =
[IfaceNewtype] -> Section IfaceNewtype -> REPL ()
forall a. [a] -> Section a -> REPL ()
ppSection (Map Name IfaceNewtype -> [IfaceNewtype]
forall k a. Map k a -> [a]
Map.elems Map Name IfaceNewtype
ifNewtypes)
Section :: forall a.
String
-> (a -> Name)
-> (Name -> Bool)
-> Map Name DeclProvenance
-> NameDisp
-> (a -> Doc)
-> Section a
Section { secName :: String
secName = String
"Newtypes"
, secEntryName :: IfaceNewtype -> Name
secEntryName = IfaceNewtype -> Name
T.ntName
, secVisible :: Name -> Bool
secVisible = Name -> Bool
isVisible
, secProvenance :: Map Name DeclProvenance
secProvenance = Map Name DeclProvenance
prov
, secDisp :: NameDisp
secDisp = NameDisp
names
, secPP :: IfaceNewtype -> Doc
secPP = IfaceNewtype -> Doc
T.ppNewtypeShort
}
browseVars :: (M.Name -> Bool) -> Prov -> M.IfaceDecls -> NameDisp -> REPL ()
browseVars :: (Name -> Bool)
-> Map Name DeclProvenance -> IfaceDecls -> NameDisp -> REPL ()
browseVars Name -> Bool
isVisible Map Name DeclProvenance
prov M.IfaceDecls { Map Name IfaceAbstractType
Map Name IfaceNewtype
Map Name IfaceTySyn
Map Name IfaceDecl
ifDecls :: Map Name IfaceDecl
ifAbstractTypes :: Map Name IfaceAbstractType
ifNewtypes :: Map Name IfaceNewtype
ifTySyns :: Map Name IfaceTySyn
ifDecls :: IfaceDecls -> Map Name IfaceDecl
ifAbstractTypes :: IfaceDecls -> Map Name IfaceAbstractType
ifNewtypes :: IfaceDecls -> Map Name IfaceNewtype
ifTySyns :: IfaceDecls -> Map Name IfaceTySyn
.. } NameDisp
names =
do [IfaceDecl] -> Section IfaceDecl -> REPL ()
forall a. [a] -> Section a -> REPL ()
ppSection [IfaceDecl]
props Section :: forall a.
String
-> (a -> Name)
-> (Name -> Bool)
-> Map Name DeclProvenance
-> NameDisp
-> (a -> Doc)
-> Section a
Section { secName :: String
secName = String
"Properties"
, secEntryName :: IfaceDecl -> Name
secEntryName = IfaceDecl -> Name
M.ifDeclName
, secVisible :: Name -> Bool
secVisible = Name -> Bool
isVisible
, secProvenance :: Map Name DeclProvenance
secProvenance = Map Name DeclProvenance
prov
, secDisp :: NameDisp
secDisp = NameDisp
names
, secPP :: IfaceDecl -> Doc
secPP = IfaceDecl -> Doc
ppVar
}
[IfaceDecl] -> Section IfaceDecl -> REPL ()
forall a. [a] -> Section a -> REPL ()
ppSection [IfaceDecl]
syms Section :: forall a.
String
-> (a -> Name)
-> (Name -> Bool)
-> Map Name DeclProvenance
-> NameDisp
-> (a -> Doc)
-> Section a
Section { secName :: String
secName = String
"Symbols"
, secEntryName :: IfaceDecl -> Name
secEntryName = IfaceDecl -> Name
M.ifDeclName
, secVisible :: Name -> Bool
secVisible = Name -> Bool
isVisible
, secProvenance :: Map Name DeclProvenance
secProvenance = Map Name DeclProvenance
prov
, secDisp :: NameDisp
secDisp = NameDisp
names
, secPP :: IfaceDecl -> Doc
secPP = IfaceDecl -> Doc
ppVar
}
where
isProp :: IfaceDecl -> Bool
isProp IfaceDecl
p = Pragma
T.PragmaProperty Pragma -> [Pragma] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (IfaceDecl -> [Pragma]
M.ifDeclPragmas IfaceDecl
p)
([IfaceDecl]
props,[IfaceDecl]
syms) = (IfaceDecl -> Bool) -> [IfaceDecl] -> ([IfaceDecl], [IfaceDecl])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition IfaceDecl -> Bool
isProp (Map Name IfaceDecl -> [IfaceDecl]
forall k a. Map k a -> [a]
Map.elems Map Name IfaceDecl
ifDecls)
ppVar :: IfaceDecl -> Doc
ppVar M.IfaceDecl { Bool
[Pragma]
Maybe Text
Maybe Fixity
Name
Schema
ifDeclDoc :: IfaceDecl -> Maybe Text
ifDeclFixity :: IfaceDecl -> Maybe Fixity
ifDeclInfix :: IfaceDecl -> Bool
ifDeclSig :: IfaceDecl -> Schema
ifDeclDoc :: Maybe Text
ifDeclFixity :: Maybe Fixity
ifDeclInfix :: Bool
ifDeclPragmas :: [Pragma]
ifDeclSig :: Schema
ifDeclName :: Name
ifDeclPragmas :: IfaceDecl -> [Pragma]
ifDeclName :: IfaceDecl -> Name
.. } = Doc -> Int -> Doc -> Doc
hang (Name -> Doc
forall a. PP a => a -> Doc
pp Name
ifDeclName Doc -> Doc -> Doc
<+> Char -> Doc
char Char
':') Int
2 (Schema -> Doc
forall a. PP a => a -> Doc
pp Schema
ifDeclSig)
data Section a = Section
{ Section a -> String
secName :: String
, Section a -> a -> Name
secEntryName :: a -> M.Name
, Section a -> Name -> Bool
secVisible :: M.Name -> Bool
, Section a -> Map Name DeclProvenance
secProvenance :: Map M.Name M.DeclProvenance
, Section a -> NameDisp
secDisp :: NameDisp
, Section a -> a -> Doc
secPP :: a -> Doc
}
ppSection :: [a] -> Section a -> REPL ()
ppSection :: [a] -> Section a -> REPL ()
ppSection [a]
things Section a
s
| [(DeclProvenance, [a])] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(DeclProvenance, [a])]
grouped = () -> REPL ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
| Bool
otherwise =
do let heading :: String
heading = Section a -> String
forall a. Section a -> String
secName Section a
s
String -> REPL ()
rPutStrLn String
heading
String -> REPL ()
rPutStrLn ((Char -> Char) -> ShowS
forall a b. (a -> b) -> [a] -> [b]
map (Char -> Char -> Char
forall a b. a -> b -> a
const Char
'=') String
heading)
String -> REPL ()
rPutStrLn String
""
((DeclProvenance, [a]) -> REPL ())
-> [(DeclProvenance, [a])] -> REPL ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (DeclProvenance, [a]) -> REPL ()
ppSub [(DeclProvenance, [a])]
grouped
where
ppSub :: (DeclProvenance, [a]) -> REPL ()
ppSub (DeclProvenance
p,[a]
ts) =
do let heading :: String
heading = DeclProvenance -> String
provHeading DeclProvenance
p
String -> REPL ()
rPutStrLn (String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
heading)
String -> REPL ()
rPutStrLn (String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Char -> Char) -> ShowS
forall a b. (a -> b) -> [a] -> [b]
map (Char -> Char -> Char
forall a b. a -> b -> a
const Char
'-') String
heading)
String -> REPL ()
rPutStrLn String
""
String -> REPL ()
rPutStrLn (String -> REPL ()) -> String -> REPL ()
forall a b. (a -> b) -> a -> b
$ Doc -> String
forall a. Show a => a -> String
show (Doc -> String) -> Doc -> String
forall a b. (a -> b) -> a -> b
$ NameDisp -> Doc -> Doc
runDoc (Section a -> NameDisp
forall a. Section a -> NameDisp
secDisp Section a
s) (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Int -> Doc -> Doc
nest Int
4 (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ (a -> Doc) -> [a] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Section a -> a -> Doc
forall a. Section a -> a -> Doc
secPP Section a
s) [a]
ts
String -> REPL ()
rPutStrLn String
""
grouped :: [(DeclProvenance, [a])]
grouped = ([(Name, DeclProvenance, a)] -> (DeclProvenance, [a]))
-> [[(Name, DeclProvenance, a)]] -> [(DeclProvenance, [a])]
forall a b. (a -> b) -> [a] -> [b]
map [(Name, DeclProvenance, a)] -> (DeclProvenance, [a])
forall a a c. [(a, a, c)] -> (a, [c])
rearrange ([[(Name, DeclProvenance, a)]] -> [(DeclProvenance, [a])])
-> [[(Name, DeclProvenance, a)]] -> [(DeclProvenance, [a])]
forall a b. (a -> b) -> a -> b
$
((Name, DeclProvenance, a) -> (Name, DeclProvenance, a) -> Bool)
-> [(Name, DeclProvenance, a)] -> [[(Name, DeclProvenance, a)]]
forall a. (a -> a -> Bool) -> [a] -> [[a]]
groupBy (Name, DeclProvenance, a) -> (Name, DeclProvenance, a) -> Bool
forall a c a c.
(a, DeclProvenance, c) -> (a, DeclProvenance, c) -> Bool
sameProv ([(Name, DeclProvenance, a)] -> [[(Name, DeclProvenance, a)]])
-> [(Name, DeclProvenance, a)] -> [[(Name, DeclProvenance, a)]]
forall a b. (a -> b) -> a -> b
$
((Name, DeclProvenance, a)
-> (Name, DeclProvenance, a) -> Ordering)
-> [(Name, DeclProvenance, a)] -> [(Name, DeclProvenance, a)]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (Name, DeclProvenance, a) -> (Name, DeclProvenance, a) -> Ordering
forall c c.
(Name, DeclProvenance, c) -> (Name, DeclProvenance, c) -> Ordering
cmpThings
[ (Name
n,DeclProvenance
p,a
t) | a
t <- [a]
things,
let n :: Name
n = Section a -> a -> Name
forall a. Section a -> a -> Name
secEntryName Section a
s a
t,
Section a -> Name -> Bool
forall a. Section a -> Name -> Bool
secVisible Section a
s Name
n,
let p :: DeclProvenance
p = case Name -> Map Name DeclProvenance -> Maybe DeclProvenance
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name
n (Section a -> Map Name DeclProvenance
forall a. Section a -> Map Name DeclProvenance
secProvenance Section a
s) of
Just DeclProvenance
i -> DeclProvenance
i
Maybe DeclProvenance
Nothing -> String -> [String] -> DeclProvenance
forall a. HasCallStack => String -> [String] -> a
panic String
"ppSection"
[ String
"Name with no provenance"
, Name -> String
forall a. Show a => a -> String
show Name
n ]
]
rearrange :: [(a, a, c)] -> (a, [c])
rearrange [(a, a, c)]
xs = (a
p, [ c
a | (a
_,a
_,c
a) <- [(a, a, c)]
xs ])
where (a
_,a
p,c
_) : [(a, a, c)]
_ = [(a, a, c)]
xs
cmpThings :: (Name, DeclProvenance, c) -> (Name, DeclProvenance, c) -> Ordering
cmpThings (Name
n1, DeclProvenance
p1, c
_) (Name
n2, DeclProvenance
p2, c
_) =
case DeclProvenance -> DeclProvenance -> Ordering
cmpProv DeclProvenance
p1 DeclProvenance
p2 of
Ordering
EQ -> NameDisp -> Name -> Name -> Ordering
M.cmpNameDisplay (Section a -> NameDisp
forall a. Section a -> NameDisp
secDisp Section a
s) Name
n1 Name
n2
Ordering
r -> Ordering
r
sameProv :: (a, DeclProvenance, c) -> (a, DeclProvenance, c) -> Bool
sameProv (a
_,DeclProvenance
p1,c
_) (a
_,DeclProvenance
p2,c
_) = DeclProvenance -> Either Int ModName
provOrd DeclProvenance
p1 Either Int ModName -> Either Int ModName -> Bool
forall a. Eq a => a -> a -> Bool
== DeclProvenance -> Either Int ModName
provOrd DeclProvenance
p2
provOrd :: DeclProvenance -> Either Int ModName
provOrd DeclProvenance
p =
case DeclProvenance
p of
DeclProvenance
M.NameIsParameter -> Int -> Either Int ModName
forall a b. a -> Either a b
Left Int
1 :: Either Int P.ModName
DeclProvenance
M.NameIsDynamicDecl -> Int -> Either Int ModName
forall a b. a -> Either a b
Left Int
2
DeclProvenance
M.NameIsLocalPublic -> Int -> Either Int ModName
forall a b. a -> Either a b
Left Int
3
DeclProvenance
M.NameIsLocalPrivate -> Int -> Either Int ModName
forall a b. a -> Either a b
Left Int
4
M.NameIsImportedFrom ModName
x -> ModName -> Either Int ModName
forall a b. b -> Either a b
Right ModName
x
cmpProv :: DeclProvenance -> DeclProvenance -> Ordering
cmpProv DeclProvenance
p1 DeclProvenance
p2 = Either Int ModName -> Either Int ModName -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (DeclProvenance -> Either Int ModName
provOrd DeclProvenance
p1) (DeclProvenance -> Either Int ModName
provOrd DeclProvenance
p2)
provHeading :: DeclProvenance -> String
provHeading DeclProvenance
p =
case DeclProvenance
p of
DeclProvenance
M.NameIsParameter -> String
"Parameters"
DeclProvenance
M.NameIsDynamicDecl -> String
"REPL"
DeclProvenance
M.NameIsLocalPublic -> String
"Public"
DeclProvenance
M.NameIsLocalPrivate -> String
"Private"
M.NameIsImportedFrom ModName
m -> String
"From " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Doc -> String
forall a. Show a => a -> String
show (ModName -> Doc
forall a. PP a => a -> Doc
pp ModName
m)
ppBlock :: NameDisp -> (a -> Doc) -> String -> [a] -> REPL ()
ppBlock :: NameDisp -> (a -> Doc) -> String -> [a] -> REPL ()
ppBlock NameDisp
names a -> Doc
ppFun String
name [a]
xs = Bool -> REPL () -> REPL ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
xs) (REPL () -> REPL ()) -> REPL () -> REPL ()
forall a b. (a -> b) -> a -> b
$
do String -> REPL ()
rPutStrLn String
name
String -> REPL ()
rPutStrLn (Int -> Char -> String
forall a. Int -> a -> [a]
replicate (String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
name) Char
'=')
Doc -> REPL ()
forall a. Show a => a -> REPL ()
rPrint (NameDisp -> Doc -> Doc
runDoc NameDisp
names (Int -> Doc -> Doc
nest Int
4 ([Doc] -> Doc
vcat ((a -> Doc) -> [a] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map a -> Doc
ppFun [a]
xs))))
String -> REPL ()
rPutStrLn String
""
setOptionCmd :: String -> REPL ()
setOptionCmd :: String -> REPL ()
setOptionCmd String
str
| Just String
value <- Maybe String
mbValue = String -> String -> REPL ()
setUser String
key String
value
| String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
key = (OptionDescr -> REPL ()) -> [OptionDescr] -> REPL ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (String -> REPL ()
describe (String -> REPL ())
-> (OptionDescr -> String) -> OptionDescr -> REPL ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OptionDescr -> String
optName) (Trie OptionDescr -> [OptionDescr]
forall a. Trie a -> [a]
leaves Trie OptionDescr
userOptions)
| Bool
otherwise = String -> REPL ()
describe String
key
where
(String
before,String
after) = (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'=') String
str
key :: String
key = ShowS
trim String
before
mbValue :: Maybe String
mbValue = case String
after of
Char
_ : String
stuff -> String -> Maybe String
forall a. a -> Maybe a
Just (ShowS
trim String
stuff)
String
_ -> Maybe String
forall a. Maybe a
Nothing
describe :: String -> REPL ()
describe String
k = do
Maybe EnvVal
ev <- String -> REPL (Maybe EnvVal)
tryGetUser String
k
case Maybe EnvVal
ev of
Just EnvVal
v -> String -> REPL ()
rPutStrLn (String
k String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ EnvVal -> String
showEnvVal EnvVal
v)
Maybe EnvVal
Nothing -> do String -> REPL ()
rPutStrLn (String
"Unknown user option: `" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
k String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"`")
Bool -> REPL () -> REPL ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ((Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Char -> Bool
isSpace String
k) (REPL () -> REPL ()) -> REPL () -> REPL ()
forall a b. (a -> b) -> a -> b
$ do
let (String
k1, String
k2) = (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isSpace String
k
String -> REPL ()
rPutStrLn (String
"Did you mean: `:set " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
k1 String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" =" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
k2 String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"`?")
showEnvVal :: EnvVal -> String
showEnvVal :: EnvVal -> String
showEnvVal EnvVal
ev =
case EnvVal
ev of
EnvString String
s -> String
s
EnvProg String
p [String]
as -> String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
" " (String
pString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
as)
EnvNum Int
n -> Int -> String
forall a. Show a => a -> String
show Int
n
EnvBool Bool
True -> String
"on"
EnvBool Bool
False -> String
"off"
helpCmd :: String -> REPL ()
helpCmd :: String -> REPL ()
helpCmd String
cmd
| String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
cmd = (String -> REPL ()) -> [String] -> REPL ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ String -> REPL ()
rPutStrLn ([CommandDescr] -> [String]
genHelp [CommandDescr]
commandList)
| String
cmd0 : [String]
args <- String -> [String]
words String
cmd, String
":" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
cmd0 =
case String -> [CommandDescr]
findCommandExact String
cmd0 of
[] -> REPL CommandExitCode -> REPL ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (REPL CommandExitCode -> REPL ())
-> REPL CommandExitCode -> REPL ()
forall a b. (a -> b) -> a -> b
$ Command -> REPL CommandExitCode
runCommand (String -> Command
Unknown String
cmd0)
[CommandDescr
c] -> CommandDescr -> [String] -> REPL ()
showCmdHelp CommandDescr
c [String]
args
[CommandDescr]
cs -> REPL CommandExitCode -> REPL ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (REPL CommandExitCode -> REPL ())
-> REPL CommandExitCode -> REPL ()
forall a b. (a -> b) -> a -> b
$ Command -> REPL CommandExitCode
runCommand (String -> [String] -> Command
Ambiguous String
cmd0 ((CommandDescr -> [String]) -> [CommandDescr] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap CommandDescr -> [String]
cNames [CommandDescr]
cs))
| Bool
otherwise =
case String -> Maybe PName
parseHelpName String
cmd of
Just PName
qname ->
do ModContext
fe <- REPL ModContext
getFocusedEnv
let params :: IfaceParams
params = ModContext -> IfaceParams
M.mctxParams ModContext
fe
env :: IfaceDecls
env = ModContext -> IfaceDecls
M.mctxDecls ModContext
fe
rnEnv :: NamingEnv
rnEnv = ModContext -> NamingEnv
M.mctxNames ModContext
fe
disp :: NameDisp
disp = ModContext -> NameDisp
M.mctxNameDisp ModContext
fe
vNames :: [Name]
vNames = PName -> NamingEnv -> [Name]
M.lookupValNames PName
qname NamingEnv
rnEnv
tNames :: [Name]
tNames = PName -> NamingEnv -> [Name]
M.lookupTypeNames PName
qname NamingEnv
rnEnv
let helps :: [REPL ()]
helps = (Name -> REPL ()) -> [Name] -> [REPL ()]
forall a b. (a -> b) -> [a] -> [b]
map (IfaceParams -> IfaceDecls -> NameDisp -> Name -> REPL ()
showTypeHelp IfaceParams
params IfaceDecls
env NameDisp
disp) [Name]
tNames [REPL ()] -> [REPL ()] -> [REPL ()]
forall a. [a] -> [a] -> [a]
++
(Name -> REPL ()) -> [Name] -> [REPL ()]
forall a b. (a -> b) -> [a] -> [b]
map (IfaceParams -> IfaceDecls -> NameDisp -> PName -> Name -> REPL ()
forall a.
PP a =>
IfaceParams -> IfaceDecls -> NameDisp -> a -> Name -> REPL ()
showValHelp IfaceParams
params IfaceDecls
env NameDisp
disp PName
qname) [Name]
vNames
separ :: REPL ()
separ = String -> REPL ()
rPutStrLn String
" ---------"
[REPL ()] -> REPL ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ (REPL () -> [REPL ()] -> [REPL ()]
forall a. a -> [a] -> [a]
intersperse REPL ()
separ [REPL ()]
helps)
Bool -> REPL () -> REPL ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([Name] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([Name]
vNames [Name] -> [Name] -> [Name]
forall a. [a] -> [a] -> [a]
++ [Name]
tNames)) (REPL () -> REPL ()) -> REPL () -> REPL ()
forall a b. (a -> b) -> a -> b
$
Doc -> REPL ()
forall a. Show a => a -> REPL ()
rPrint (Doc -> REPL ()) -> Doc -> REPL ()
forall a b. (a -> b) -> a -> b
$ Doc
"Undefined name:" Doc -> Doc -> Doc
<+> PName -> Doc
forall a. PP a => a -> Doc
pp PName
qname
Maybe PName
Nothing ->
String -> REPL ()
rPutStrLn (String
"Unable to parse name: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
cmd)
where
noInfo :: NameDisp -> Name -> REPL ()
noInfo NameDisp
nameEnv Name
name =
case Name -> NameInfo
M.nameInfo Name
name of
M.Declared ModName
m NameSource
_ ->
Doc -> REPL ()
forall a. Show a => a -> REPL ()
rPrint (Doc -> REPL ()) -> Doc -> REPL ()
forall a b. (a -> b) -> a -> b
$NameDisp -> Doc -> Doc
runDoc NameDisp
nameEnv (Doc
"Name defined in module" Doc -> Doc -> Doc
<+> ModName -> Doc
forall a. PP a => a -> Doc
pp ModName
m)
NameInfo
M.Parameter -> String -> REPL ()
rPutStrLn String
"// No documentation is available."
showTypeHelp :: IfaceParams -> IfaceDecls -> NameDisp -> Name -> REPL ()
showTypeHelp IfaceParams
params IfaceDecls
env NameDisp
nameEnv Name
name =
REPL () -> Maybe (REPL ()) -> REPL ()
forall a. a -> Maybe a -> a
fromMaybe (NameDisp -> Name -> REPL ()
noInfo NameDisp
nameEnv Name
name) (Maybe (REPL ()) -> REPL ()) -> Maybe (REPL ()) -> REPL ()
forall a b. (a -> b) -> a -> b
$
[Maybe (REPL ())] -> Maybe (REPL ())
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum [ Maybe (REPL ())
fromTySyn, Maybe (REPL ())
fromPrimType, Maybe (REPL ())
fromNewtype, Maybe (REPL ())
fromTyParam ]
where
fromTySyn :: Maybe (REPL ())
fromTySyn =
do IfaceTySyn
ts <- Name -> Map Name IfaceTySyn -> Maybe IfaceTySyn
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name
name (IfaceDecls -> Map Name IfaceTySyn
M.ifTySyns IfaceDecls
env)
REPL () -> Maybe (REPL ())
forall (m :: * -> *) a. Monad m => a -> m a
return (NameDisp -> Doc -> Maybe Text -> REPL ()
doShowTyHelp NameDisp
nameEnv (IfaceTySyn -> Doc
forall a. PP a => a -> Doc
pp IfaceTySyn
ts) (IfaceTySyn -> Maybe Text
T.tsDoc IfaceTySyn
ts))
fromNewtype :: Maybe (REPL ())
fromNewtype =
do IfaceNewtype
nt <- Name -> Map Name IfaceNewtype -> Maybe IfaceNewtype
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name
name (IfaceDecls -> Map Name IfaceNewtype
M.ifNewtypes IfaceDecls
env)
let decl :: Doc
decl = IfaceNewtype -> Doc
forall a. PP a => a -> Doc
pp IfaceNewtype
nt Doc -> Doc -> Doc
$$ (Name -> Doc
forall a. PP a => a -> Doc
pp Name
name Doc -> Doc -> Doc
<+> String -> Doc
text String
":" Doc -> Doc -> Doc
<+> Schema -> Doc
forall a. PP a => a -> Doc
pp (IfaceNewtype -> Schema
T.newtypeConType IfaceNewtype
nt))
REPL () -> Maybe (REPL ())
forall (m :: * -> *) a. Monad m => a -> m a
return (REPL () -> Maybe (REPL ())) -> REPL () -> Maybe (REPL ())
forall a b. (a -> b) -> a -> b
$ NameDisp -> Doc -> Maybe Text -> REPL ()
doShowTyHelp NameDisp
nameEnv Doc
decl (IfaceNewtype -> Maybe Text
T.ntDoc IfaceNewtype
nt)
fromPrimType :: Maybe (REPL ())
fromPrimType =
do IfaceAbstractType
a <- Name -> Map Name IfaceAbstractType -> Maybe IfaceAbstractType
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name
name (IfaceDecls -> Map Name IfaceAbstractType
M.ifAbstractTypes IfaceDecls
env)
REPL () -> Maybe (REPL ())
forall (f :: * -> *) a. Applicative f => a -> f a
pure (REPL () -> Maybe (REPL ())) -> REPL () -> Maybe (REPL ())
forall a b. (a -> b) -> a -> b
$ do String -> REPL ()
rPutStrLn String
""
Doc -> REPL ()
forall a. Show a => a -> REPL ()
rPrint (Doc -> REPL ()) -> Doc -> REPL ()
forall a b. (a -> b) -> a -> b
$ NameDisp -> Doc -> Doc
runDoc NameDisp
nameEnv (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Int -> Doc -> Doc
nest Int
4
(Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Doc
"primitive type" Doc -> Doc -> Doc
<+> Name -> Doc
forall a. PP a => a -> Doc
pp (IfaceAbstractType -> Name
T.atName IfaceAbstractType
a)
Doc -> Doc -> Doc
<+> Doc
":" Doc -> Doc -> Doc
<+> Kind -> Doc
forall a. PP a => a -> Doc
pp (IfaceAbstractType -> Kind
T.atKind IfaceAbstractType
a)
let ([TParam]
vs,[Type]
cs) = IfaceAbstractType -> ([TParam], [Type])
T.atCtrs IfaceAbstractType
a
Bool -> REPL () -> REPL ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([Type] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Type]
cs) (REPL () -> REPL ()) -> REPL () -> REPL ()
forall a b. (a -> b) -> a -> b
$
do let example :: Type
example = TCon -> [Type] -> Type
T.TCon (IfaceAbstractType -> TCon
T.abstractTypeTC IfaceAbstractType
a)
((TParam -> Type) -> [TParam] -> [Type]
forall a b. (a -> b) -> [a] -> [b]
map (TVar -> Type
T.TVar (TVar -> Type) -> (TParam -> TVar) -> TParam -> Type
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TParam -> TVar
T.tpVar) [TParam]
vs)
ns :: NameMap
ns = [TParam] -> NameMap -> NameMap
T.addTNames [TParam]
vs NameMap
emptyNameMap
rs :: [Doc]
rs = [ Doc
"•" Doc -> Doc -> Doc
<+> NameMap -> Type -> Doc
forall a. PP (WithNames a) => NameMap -> a -> Doc
ppWithNames NameMap
ns Type
c | Type
c <- [Type]
cs ]
String -> REPL ()
rPutStrLn String
""
Doc -> REPL ()
forall a. Show a => a -> REPL ()
rPrint (Doc -> REPL ()) -> Doc -> REPL ()
forall a b. (a -> b) -> a -> b
$ NameDisp -> Doc -> Doc
runDoc NameDisp
nameEnv (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Int -> Doc -> Doc
nest Int
4 (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$
Doc -> Doc
backticks (NameMap -> Type -> Doc
forall a. PP (WithNames a) => NameMap -> a -> Doc
ppWithNames NameMap
ns Type
example) Doc -> Doc -> Doc
<+>
Doc
"requires:" Doc -> Doc -> Doc
$$ Int -> Doc -> Doc
nest Int
2 ([Doc] -> Doc
vcat [Doc]
rs)
Maybe Fixity -> REPL ()
doShowFix (IfaceAbstractType -> Maybe Fixity
T.atFixitiy IfaceAbstractType
a)
Maybe Text -> REPL ()
doShowDocString (IfaceAbstractType -> Maybe Text
T.atDoc IfaceAbstractType
a)
fromTyParam :: Maybe (REPL ())
fromTyParam =
do ModTParam
p <- Name -> Map Name ModTParam -> Maybe ModTParam
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name
name (IfaceParams -> Map Name ModTParam
M.ifParamTypes IfaceParams
params)
let uses :: t -> Bool
uses t
c = TParam -> TVar
T.TVBound (ModTParam -> TParam
T.mtpParam ModTParam
p) TVar -> Set TVar -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` t -> Set TVar
forall t. FVS t => t -> Set TVar
T.fvs t
c
ctrs :: [Type]
ctrs = (Type -> Bool) -> [Type] -> [Type]
forall a. (a -> Bool) -> [a] -> [a]
filter Type -> Bool
forall t. FVS t => t -> Bool
uses ((Located Type -> Type) -> [Located Type] -> [Type]
forall a b. (a -> b) -> [a] -> [b]
map Located Type -> Type
forall a. Located a -> a
P.thing (IfaceParams -> [Located Type]
M.ifParamConstraints IfaceParams
params))
ctrDoc :: Doc
ctrDoc = case [Type]
ctrs of
[] -> Doc
empty
[Type
x] -> Type -> Doc
forall a. PP a => a -> Doc
pp Type
x
[Type]
xs -> Doc -> Doc
parens (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
hsep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ Doc -> [Doc] -> [Doc]
punctuate Doc
comma ([Doc] -> [Doc]) -> [Doc] -> [Doc]
forall a b. (a -> b) -> a -> b
$ (Type -> Doc) -> [Type] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Type -> Doc
forall a. PP a => a -> Doc
pp [Type]
xs
decl :: Doc
decl = String -> Doc
text String
"parameter" Doc -> Doc -> Doc
<+> Name -> Doc
forall a. PP a => a -> Doc
pp Name
name Doc -> Doc -> Doc
<+> String -> Doc
text String
":"
Doc -> Doc -> Doc
<+> Kind -> Doc
forall a. PP a => a -> Doc
pp (ModTParam -> Kind
T.mtpKind ModTParam
p)
Doc -> Doc -> Doc
$$ Doc
ctrDoc
REPL () -> Maybe (REPL ())
forall (m :: * -> *) a. Monad m => a -> m a
return (REPL () -> Maybe (REPL ())) -> REPL () -> Maybe (REPL ())
forall a b. (a -> b) -> a -> b
$ NameDisp -> Doc -> Maybe Text -> REPL ()
doShowTyHelp NameDisp
nameEnv Doc
decl (ModTParam -> Maybe Text
T.mtpDoc ModTParam
p)
doShowTyHelp :: NameDisp -> Doc -> Maybe Text -> REPL ()
doShowTyHelp NameDisp
nameEnv Doc
decl Maybe Text
doc =
do String -> REPL ()
rPutStrLn String
""
Doc -> REPL ()
forall a. Show a => a -> REPL ()
rPrint (NameDisp -> Doc -> Doc
runDoc NameDisp
nameEnv (Int -> Doc -> Doc
nest Int
4 Doc
decl))
Maybe Text -> REPL ()
doShowDocString Maybe Text
doc
doShowFix :: Maybe Fixity -> REPL ()
doShowFix Maybe Fixity
fx =
case Maybe Fixity
fx of
Just Fixity
f ->
let msg :: String
msg = String
"Precedence " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (Fixity -> Int
P.fLevel Fixity
f) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", " String -> ShowS
forall a. [a] -> [a] -> [a]
++
(case Fixity -> Assoc
P.fAssoc Fixity
f of
Assoc
P.LeftAssoc -> String
"associates to the left."
Assoc
P.RightAssoc -> String
"associates to the right."
Assoc
P.NonAssoc -> String
"does not associate.")
in String -> REPL ()
rPutStrLn (Char
'\n' Char -> ShowS
forall a. a -> [a] -> [a]
: String
msg)
Maybe Fixity
Nothing -> () -> REPL ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
showValHelp :: IfaceParams -> IfaceDecls -> NameDisp -> a -> Name -> REPL ()
showValHelp IfaceParams
params IfaceDecls
env NameDisp
nameEnv a
qname Name
name =
REPL () -> Maybe (REPL ()) -> REPL ()
forall a. a -> Maybe a -> a
fromMaybe (NameDisp -> Name -> REPL ()
noInfo NameDisp
nameEnv Name
name)
([Maybe (REPL ())] -> Maybe (REPL ())
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum [ Maybe (REPL ())
fromDecl, Maybe (REPL ())
fromNewtype, Maybe (REPL ())
fromParameter ])
where
fromDecl :: Maybe (REPL ())
fromDecl =
do M.IfaceDecl { Bool
[Pragma]
Maybe Text
Maybe Fixity
Name
Schema
ifDeclDoc :: Maybe Text
ifDeclFixity :: Maybe Fixity
ifDeclInfix :: Bool
ifDeclPragmas :: [Pragma]
ifDeclSig :: Schema
ifDeclName :: Name
ifDeclDoc :: IfaceDecl -> Maybe Text
ifDeclFixity :: IfaceDecl -> Maybe Fixity
ifDeclInfix :: IfaceDecl -> Bool
ifDeclSig :: IfaceDecl -> Schema
ifDeclPragmas :: IfaceDecl -> [Pragma]
ifDeclName :: IfaceDecl -> Name
.. } <- Name -> Map Name IfaceDecl -> Maybe IfaceDecl
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name
name (IfaceDecls -> Map Name IfaceDecl
M.ifDecls IfaceDecls
env)
REPL () -> Maybe (REPL ())
forall (m :: * -> *) a. Monad m => a -> m a
return (REPL () -> Maybe (REPL ())) -> REPL () -> Maybe (REPL ())
forall a b. (a -> b) -> a -> b
$
do String -> REPL ()
rPutStrLn String
""
let property :: Doc
property
| Pragma
P.PragmaProperty Pragma -> [Pragma] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Pragma]
ifDeclPragmas = String -> Doc
text String
"property"
| Bool
otherwise = Doc
empty
Doc -> REPL ()
forall a. Show a => a -> REPL ()
rPrint (Doc -> REPL ()) -> Doc -> REPL ()
forall a b. (a -> b) -> a -> b
$ NameDisp -> Doc -> Doc
runDoc NameDisp
nameEnv
(Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Int -> Doc -> Doc
nest Int
4
(Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Doc
property
Doc -> Doc -> Doc
<+> a -> Doc
forall a. PP a => a -> Doc
pp a
qname
Doc -> Doc -> Doc
<+> Doc
colon
Doc -> Doc -> Doc
<+> Schema -> Doc
forall a. PP a => a -> Doc
pp (Schema
ifDeclSig)
Maybe Fixity -> REPL ()
doShowFix (Maybe Fixity -> REPL ()) -> Maybe Fixity -> REPL ()
forall a b. (a -> b) -> a -> b
$ Maybe Fixity
ifDeclFixity Maybe Fixity -> Maybe Fixity -> Maybe Fixity
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus`
(Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard Bool
ifDeclInfix Maybe () -> Maybe Fixity -> Maybe Fixity
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Fixity -> Maybe Fixity
forall (m :: * -> *) a. Monad m => a -> m a
return Fixity
P.defaultFixity)
Maybe Text -> REPL ()
doShowDocString Maybe Text
ifDeclDoc
fromNewtype :: Maybe (REPL ())
fromNewtype =
do IfaceNewtype
_ <- Name -> Map Name IfaceNewtype -> Maybe IfaceNewtype
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name
name (IfaceDecls -> Map Name IfaceNewtype
M.ifNewtypes IfaceDecls
env)
REPL () -> Maybe (REPL ())
forall (m :: * -> *) a. Monad m => a -> m a
return (REPL () -> Maybe (REPL ())) -> REPL () -> Maybe (REPL ())
forall a b. (a -> b) -> a -> b
$ () -> REPL ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
fromParameter :: Maybe (REPL ())
fromParameter =
do ModVParam
p <- Name -> Map Name ModVParam -> Maybe ModVParam
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name
name (IfaceParams -> Map Name ModVParam
M.ifParamFuns IfaceParams
params)
REPL () -> Maybe (REPL ())
forall (m :: * -> *) a. Monad m => a -> m a
return (REPL () -> Maybe (REPL ())) -> REPL () -> Maybe (REPL ())
forall a b. (a -> b) -> a -> b
$
do String -> REPL ()
rPutStrLn String
""
Doc -> REPL ()
forall a. Show a => a -> REPL ()
rPrint (Doc -> REPL ()) -> Doc -> REPL ()
forall a b. (a -> b) -> a -> b
$ NameDisp -> Doc -> Doc
runDoc NameDisp
nameEnv
(Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Int -> Doc -> Doc
nest Int
4
(Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ String -> Doc
text String
"parameter" Doc -> Doc -> Doc
<+> a -> Doc
forall a. PP a => a -> Doc
pp a
qname
Doc -> Doc -> Doc
<+> Doc
colon
Doc -> Doc -> Doc
<+> Schema -> Doc
forall a. PP a => a -> Doc
pp (ModVParam -> Schema
T.mvpType ModVParam
p)
Maybe Fixity -> REPL ()
doShowFix (ModVParam -> Maybe Fixity
T.mvpFixity ModVParam
p)
Maybe Text -> REPL ()
doShowDocString (ModVParam -> Maybe Text
T.mvpDoc ModVParam
p)
doShowDocString :: Maybe Text -> REPL ()
doShowDocString Maybe Text
doc =
case Maybe Text
doc of
Maybe Text
Nothing -> () -> REPL ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Just Text
d -> String -> REPL ()
rPutStrLn (Char
'\n' Char -> ShowS
forall a. a -> [a] -> [a]
: Text -> String
T.unpack Text
d)
showCmdHelp :: CommandDescr -> [String] -> REPL ()
showCmdHelp CommandDescr
c [String
arg] | String
":set" String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` CommandDescr -> [String]
cNames CommandDescr
c = String -> REPL ()
showOptionHelp String
arg
showCmdHelp CommandDescr
c [String]
_args =
do String -> REPL ()
rPutStrLn (String
"\n " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " (CommandDescr -> [String]
cNames CommandDescr
c) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
" " (CommandDescr -> [String]
cArgs CommandDescr
c))
String -> REPL ()
rPutStrLn String
""
String -> REPL ()
rPutStrLn (CommandDescr -> String
cHelp CommandDescr
c)
String -> REPL ()
rPutStrLn String
""
Bool -> REPL () -> REPL ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not (String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (CommandDescr -> String
cLongHelp CommandDescr
c))) (REPL () -> REPL ()) -> REPL () -> REPL ()
forall a b. (a -> b) -> a -> b
$ do
String -> REPL ()
rPutStrLn (CommandDescr -> String
cLongHelp CommandDescr
c)
String -> REPL ()
rPutStrLn String
""
showOptionHelp :: String -> REPL ()
showOptionHelp String
arg =
case String -> Trie OptionDescr -> [OptionDescr]
forall a. String -> Trie a -> [a]
lookupTrieExact String
arg Trie OptionDescr
userOptions of
[OptionDescr
opt] ->
do let k :: String
k = OptionDescr -> String
optName OptionDescr
opt
Maybe EnvVal
ev <- String -> REPL (Maybe EnvVal)
tryGetUser String
k
String -> REPL ()
rPutStrLn (String -> REPL ()) -> String -> REPL ()
forall a b. (a -> b) -> a -> b
$ String
"\n " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
k String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> (EnvVal -> String) -> Maybe EnvVal -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"???" EnvVal -> String
showEnvVal Maybe EnvVal
ev
String -> REPL ()
rPutStrLn String
""
String -> REPL ()
rPutStrLn (String
"Default value: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ EnvVal -> String
showEnvVal (OptionDescr -> EnvVal
optDefault OptionDescr
opt))
String -> REPL ()
rPutStrLn String
""
String -> REPL ()
rPutStrLn (OptionDescr -> String
optHelp OptionDescr
opt)
String -> REPL ()
rPutStrLn String
""
[] -> String -> REPL ()
rPutStrLn (String
"Unknown setting name `" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
arg String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"`")
[OptionDescr]
_ -> String -> REPL ()
rPutStrLn (String
"Ambiguous setting name `" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
arg String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"`")
runShellCmd :: String -> REPL ()
runShellCmd :: String -> REPL ()
runShellCmd String
cmd
= IO () -> REPL ()
forall a. IO a -> REPL a
io (IO () -> REPL ()) -> IO () -> REPL ()
forall a b. (a -> b) -> a -> b
$ do ProcessHandle
h <- String -> IO ProcessHandle
Process.runCommand String
cmd
ExitCode
_ <- ProcessHandle -> IO ExitCode
waitForProcess ProcessHandle
h
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
cdCmd :: FilePath -> REPL ()
cdCmd :: String -> REPL ()
cdCmd String
f | String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
f = String -> REPL ()
rPutStrLn (String -> REPL ()) -> String -> REPL ()
forall a b. (a -> b) -> a -> b
$ String
"[error] :cd requires a path argument"
| Bool
otherwise = do
Bool
exists <- IO Bool -> REPL Bool
forall a. IO a -> REPL a
io (IO Bool -> REPL Bool) -> IO Bool -> REPL Bool
forall a b. (a -> b) -> a -> b
$ String -> IO Bool
doesDirectoryExist String
f
if Bool
exists
then IO () -> REPL ()
forall a. IO a -> REPL a
io (IO () -> REPL ()) -> IO () -> REPL ()
forall a b. (a -> b) -> a -> b
$ String -> IO ()
setCurrentDirectory String
f
else REPLException -> REPL ()
forall a. REPLException -> REPL a
raise (REPLException -> REPL ()) -> REPLException -> REPL ()
forall a b. (a -> b) -> a -> b
$ String -> REPLException
DirectoryNotFound String
f
handleCtrlC :: a -> REPL a
handleCtrlC :: a -> REPL a
handleCtrlC a
a = do String -> REPL ()
rPutStrLn String
"Ctrl-C"
a -> REPL a
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
hasAnyModName :: [M.ModName] -> M.Name -> Bool
hasAnyModName :: [ModName] -> Name -> Bool
hasAnyModName [ModName]
mnames Name
n =
case Name -> NameInfo
M.nameInfo Name
n of
M.Declared ModName
m NameSource
_ -> ModName
m ModName -> [ModName] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ModName]
mnames
NameInfo
M.Parameter -> Bool
False
replParse :: (String -> Either ParseError a) -> String -> REPL a
replParse :: (String -> Either ParseError a) -> String -> REPL a
replParse String -> Either ParseError a
parse String
str = case String -> Either ParseError a
parse String
str of
Right a
a -> a -> REPL a
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
Left ParseError
e -> REPLException -> REPL a
forall a. REPLException -> REPL a
raise (ParseError -> REPLException
ParseError ParseError
e)
replParseInput :: String -> REPL (P.ReplInput P.PName)
replParseInput :: String -> REPL (ReplInput PName)
replParseInput = (String -> Either ParseError (ReplInput PName))
-> String -> REPL (ReplInput PName)
forall a. (String -> Either ParseError a) -> String -> REPL a
replParse (Config -> Text -> Either ParseError (ReplInput PName)
parseReplWith Config
interactiveConfig (Text -> Either ParseError (ReplInput PName))
-> (String -> Text)
-> String
-> Either ParseError (ReplInput PName)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack)
replParseExpr :: String -> REPL (P.Expr P.PName)
replParseExpr :: String -> REPL (Expr PName)
replParseExpr = (String -> Either ParseError (Expr PName))
-> String -> REPL (Expr PName)
forall a. (String -> Either ParseError a) -> String -> REPL a
replParse (Config -> Text -> Either ParseError (Expr PName)
parseExprWith Config
interactiveConfig (Text -> Either ParseError (Expr PName))
-> (String -> Text) -> String -> Either ParseError (Expr PName)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack)
interactiveConfig :: Config
interactiveConfig :: Config
interactiveConfig = Config
defaultConfig { cfgSource :: String
cfgSource = String
"<interactive>" }
getPrimMap :: REPL M.PrimMap
getPrimMap :: REPL PrimMap
getPrimMap = ModuleCmd PrimMap -> REPL PrimMap
forall a. ModuleCmd a -> REPL a
liftModuleCmd ModuleCmd PrimMap
M.getPrimMap
liftModuleCmd :: M.ModuleCmd a -> REPL a
liftModuleCmd :: ModuleCmd a -> REPL a
liftModuleCmd ModuleCmd a
cmd =
do EvalOpts
evo <- REPL EvalOpts
getEvalOpts
ModuleEnv
env <- REPL ModuleEnv
getModuleEnv
ModuleRes a -> REPL a
forall a. ModuleRes a -> REPL a
moduleCmdResult (ModuleRes a -> REPL a) -> REPL (ModuleRes a) -> REPL a
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO (ModuleRes a) -> REPL (ModuleRes a)
forall a. IO a -> REPL a
io (ModuleCmd a
cmd (EvalOpts
evo, String -> IO ByteString
BS.readFile, ModuleEnv
env))
moduleCmdResult :: M.ModuleRes a -> REPL a
moduleCmdResult :: ModuleRes a -> REPL a
moduleCmdResult (Either ModuleError (a, ModuleEnv)
res,[ModuleWarning]
ws0) = do
Bool
warnDefaulting <- String -> REPL Bool
forall a. IsEnvVal a => String -> REPL a
getKnownUser String
"warnDefaulting"
Bool
warnShadowing <- String -> REPL Bool
forall a. IsEnvVal a => String -> REPL a
getKnownUser String
"warnShadowing"
let isDefaultWarn :: Warning -> Bool
isDefaultWarn (T.DefaultingTo TVarInfo
_ Type
_) = Bool
True
isDefaultWarn Warning
_ = Bool
False
filterDefaults :: ModuleWarning -> Maybe ModuleWarning
filterDefaults ModuleWarning
w | Bool
warnDefaulting = ModuleWarning -> Maybe ModuleWarning
forall a. a -> Maybe a
Just ModuleWarning
w
filterDefaults (M.TypeCheckWarnings NameMap
nameMap [(Range, Warning)]
xs) =
case ((Range, Warning) -> Bool)
-> [(Range, Warning)] -> [(Range, Warning)]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool)
-> ((Range, Warning) -> Bool) -> (Range, Warning) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Warning -> Bool
isDefaultWarn (Warning -> Bool)
-> ((Range, Warning) -> Warning) -> (Range, Warning) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Range, Warning) -> Warning
forall a b. (a, b) -> b
snd) [(Range, Warning)]
xs of
[] -> Maybe ModuleWarning
forall a. Maybe a
Nothing
[(Range, Warning)]
ys -> ModuleWarning -> Maybe ModuleWarning
forall a. a -> Maybe a
Just (NameMap -> [(Range, Warning)] -> ModuleWarning
M.TypeCheckWarnings NameMap
nameMap [(Range, Warning)]
ys)
filterDefaults ModuleWarning
w = ModuleWarning -> Maybe ModuleWarning
forall a. a -> Maybe a
Just ModuleWarning
w
isShadowWarn :: RenamerWarning -> Bool
isShadowWarn (M.SymbolShadowed {}) = Bool
True
isShadowWarn RenamerWarning
_ = Bool
False
filterShadowing :: ModuleWarning -> Maybe ModuleWarning
filterShadowing ModuleWarning
w | Bool
warnShadowing = ModuleWarning -> Maybe ModuleWarning
forall a. a -> Maybe a
Just ModuleWarning
w
filterShadowing (M.RenamerWarnings [RenamerWarning]
xs) =
case (RenamerWarning -> Bool) -> [RenamerWarning] -> [RenamerWarning]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool)
-> (RenamerWarning -> Bool) -> RenamerWarning -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RenamerWarning -> Bool
isShadowWarn) [RenamerWarning]
xs of
[] -> Maybe ModuleWarning
forall a. Maybe a
Nothing
[RenamerWarning]
ys -> ModuleWarning -> Maybe ModuleWarning
forall a. a -> Maybe a
Just ([RenamerWarning] -> ModuleWarning
M.RenamerWarnings [RenamerWarning]
ys)
filterShadowing ModuleWarning
w = ModuleWarning -> Maybe ModuleWarning
forall a. a -> Maybe a
Just ModuleWarning
w
let ws :: [ModuleWarning]
ws = (ModuleWarning -> Maybe ModuleWarning)
-> [ModuleWarning] -> [ModuleWarning]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe ModuleWarning -> Maybe ModuleWarning
filterDefaults ([ModuleWarning] -> [ModuleWarning])
-> ([ModuleWarning] -> [ModuleWarning])
-> [ModuleWarning]
-> [ModuleWarning]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ModuleWarning -> Maybe ModuleWarning)
-> [ModuleWarning] -> [ModuleWarning]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe ModuleWarning -> Maybe ModuleWarning
filterShadowing ([ModuleWarning] -> [ModuleWarning])
-> [ModuleWarning] -> [ModuleWarning]
forall a b. (a -> b) -> a -> b
$ [ModuleWarning]
ws0
NameDisp
names <- ModContext -> NameDisp
M.mctxNameDisp (ModContext -> NameDisp) -> REPL ModContext -> REPL NameDisp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> REPL ModContext
getFocusedEnv
(ModuleWarning -> REPL ()) -> [ModuleWarning] -> REPL ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Doc -> REPL ()
forall a. Show a => a -> REPL ()
rPrint (Doc -> REPL ())
-> (ModuleWarning -> Doc) -> ModuleWarning -> REPL ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NameDisp -> Doc -> Doc
runDoc NameDisp
names (Doc -> Doc) -> (ModuleWarning -> Doc) -> ModuleWarning -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModuleWarning -> Doc
forall a. PP a => a -> Doc
pp) [ModuleWarning]
ws
case Either ModuleError (a, ModuleEnv)
res of
Right (a
a,ModuleEnv
me') -> ModuleEnv -> REPL ()
setModuleEnv ModuleEnv
me' REPL () -> REPL a -> REPL a
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> a -> REPL a
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
Left ModuleError
err ->
do ModuleError
e <- case ModuleError
err of
M.ErrorInFile (M.InFile String
file) ModuleError
e ->
do String -> REPL ()
setEditPath String
file
ModuleError -> REPL ModuleError
forall (m :: * -> *) a. Monad m => a -> m a
return ModuleError
e
ModuleError
_ -> ModuleError -> REPL ModuleError
forall (m :: * -> *) a. Monad m => a -> m a
return ModuleError
err
REPLException -> REPL a
forall a. REPLException -> REPL a
raise (NameDisp -> ModuleError -> REPLException
ModuleSystemError NameDisp
names ModuleError
e)
replCheckExpr :: P.Expr P.PName -> REPL (P.Expr M.Name,T.Expr,T.Schema)
replCheckExpr :: Expr PName -> REPL (Expr Name, Expr, Schema)
replCheckExpr Expr PName
e = ModuleCmd (Expr Name, Expr, Schema)
-> REPL (Expr Name, Expr, Schema)
forall a. ModuleCmd a -> REPL a
liftModuleCmd (ModuleCmd (Expr Name, Expr, Schema)
-> REPL (Expr Name, Expr, Schema))
-> ModuleCmd (Expr Name, Expr, Schema)
-> REPL (Expr Name, Expr, Schema)
forall a b. (a -> b) -> a -> b
$ Expr PName -> ModuleCmd (Expr Name, Expr, Schema)
M.checkExpr Expr PName
e
replCheckDecls :: [P.Decl P.PName] -> REPL [T.DeclGroup]
replCheckDecls :: [Decl PName] -> REPL [DeclGroup]
replCheckDecls [Decl PName]
ds = do
[Decl PName]
npds <- ModuleCmd [Decl PName] -> REPL [Decl PName]
forall a. ModuleCmd a -> REPL a
liftModuleCmd ([Decl PName] -> ModuleCmd [Decl PName]
forall a. RemovePatterns a => a -> ModuleCmd a
M.noPat [Decl PName]
ds)
let mkTop :: Decl name -> TopDecl name
mkTop Decl name
d = TopLevel (Decl name) -> TopDecl name
forall name. TopLevel (Decl name) -> TopDecl name
P.Decl TopLevel :: forall a. ExportType -> Maybe (Located Text) -> a -> TopLevel a
P.TopLevel { tlExport :: ExportType
P.tlExport = ExportType
P.Public
, tlDoc :: Maybe (Located Text)
P.tlDoc = Maybe (Located Text)
forall a. Maybe a
Nothing
, tlValue :: Decl name
P.tlValue = Decl name
d }
(NamingEnv
names,[DeclGroup]
ds') <- ModuleCmd (NamingEnv, [DeclGroup]) -> REPL (NamingEnv, [DeclGroup])
forall a. ModuleCmd a -> REPL a
liftModuleCmd ([TopDecl PName] -> ModuleCmd (NamingEnv, [DeclGroup])
M.checkDecls ((Decl PName -> TopDecl PName) -> [Decl PName] -> [TopDecl PName]
forall a b. (a -> b) -> [a] -> [b]
map Decl PName -> TopDecl PName
forall name. Decl name -> TopDecl name
mkTop [Decl PName]
npds))
DynamicEnv
denv <- REPL DynamicEnv
getDynEnv
DynamicEnv -> REPL ()
setDynEnv DynamicEnv
denv { deNames :: NamingEnv
M.deNames = NamingEnv
names NamingEnv -> NamingEnv -> NamingEnv
`M.shadowing` DynamicEnv -> NamingEnv
M.deNames DynamicEnv
denv }
[DeclGroup] -> REPL [DeclGroup]
forall (m :: * -> *) a. Monad m => a -> m a
return [DeclGroup]
ds'
replSpecExpr :: T.Expr -> REPL T.Expr
replSpecExpr :: Expr -> REPL Expr
replSpecExpr Expr
e = ModuleCmd Expr -> REPL Expr
forall a. ModuleCmd a -> REPL a
liftModuleCmd (ModuleCmd Expr -> REPL Expr) -> ModuleCmd Expr -> REPL Expr
forall a b. (a -> b) -> a -> b
$ Expr -> ModuleCmd Expr
S.specialize Expr
e
replEvalExpr :: P.Expr P.PName -> REPL (Concrete.Value, T.Type)
replEvalExpr :: Expr PName -> REPL (Value, Type)
replEvalExpr Expr PName
expr =
do (Expr Name
_,Expr
def,Schema
sig) <- Expr PName -> REPL (Expr Name, Expr, Schema)
replCheckExpr Expr PName
expr
Expr -> REPL ()
forall a. FreeVars a => a -> REPL ()
validEvalContext Expr
def
Schema -> REPL ()
forall a. FreeVars a => a -> REPL ()
validEvalContext Schema
sig
ModuleEnv
me <- REPL ModuleEnv
getModuleEnv
let cfg :: SolverConfig
cfg = ModuleEnv -> SolverConfig
M.meSolverConfig ModuleEnv
me
Maybe ([(TParam, Type)], Expr)
mbDef <- IO (Maybe ([(TParam, Type)], Expr))
-> REPL (Maybe ([(TParam, Type)], Expr))
forall a. IO a -> REPL a
io (IO (Maybe ([(TParam, Type)], Expr))
-> REPL (Maybe ([(TParam, Type)], Expr)))
-> IO (Maybe ([(TParam, Type)], Expr))
-> REPL (Maybe ([(TParam, Type)], Expr))
forall a b. (a -> b) -> a -> b
$ SolverConfig
-> (Solver -> IO (Maybe ([(TParam, Type)], Expr)))
-> IO (Maybe ([(TParam, Type)], Expr))
forall a. SolverConfig -> (Solver -> IO a) -> IO a
SMT.withSolver SolverConfig
cfg (\Solver
s -> Solver -> Expr -> Schema -> IO (Maybe ([(TParam, Type)], Expr))
defaultReplExpr Solver
s Expr
def Schema
sig)
(Expr
def1,Type
ty) <-
case Maybe ([(TParam, Type)], Expr)
mbDef of
Maybe ([(TParam, Type)], Expr)
Nothing -> REPLException -> REPL (Expr, Type)
forall a. REPLException -> REPL a
raise (Schema -> REPLException
EvalPolyError Schema
sig)
Just ([(TParam, Type)]
tys,Expr
def1) ->
do [(TParam, Type)] -> REPL ()
forall a. PP a => [(TParam, a)] -> REPL ()
warnDefaults [(TParam, Type)]
tys
let su :: Subst
su = [(TParam, Type)] -> Subst
T.listParamSubst [(TParam, Type)]
tys
(Expr, Type) -> REPL (Expr, Type)
forall (m :: * -> *) a. Monad m => a -> m a
return (Expr
def1, Subst -> Type -> Type
forall t. TVars t => Subst -> t -> t
T.apSubst Subst
su (Schema -> Type
T.sType Schema
sig))
Name
itVar <- Type -> Expr -> REPL Name
bindItVariable Type
ty Expr
def1
Value
val <- ModuleCmd Value -> REPL Value
forall a. ModuleCmd a -> REPL a
liftModuleCmd (IO (ModuleRes Value) -> IO (ModuleRes Value)
forall a. IO a -> IO a
rethrowEvalError (IO (ModuleRes Value) -> IO (ModuleRes Value))
-> ModuleCmd Value -> ModuleCmd Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> ModuleCmd Value
M.evalExpr (Name -> Expr
T.EVar Name
itVar))
REPL () -> REPL ()
whenDebug (String -> REPL ()
rPutStrLn (Expr -> String
forall a. PP (WithNames a) => a -> String
dump Expr
def1))
(Value, Type) -> REPL (Value, Type)
forall (m :: * -> *) a. Monad m => a -> m a
return (Value
val,Type
ty)
where
warnDefaults :: [(TParam, a)] -> REPL ()
warnDefaults [(TParam, a)]
ts =
case [(TParam, a)]
ts of
[] -> () -> REPL ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
[(TParam, a)]
_ -> do String -> REPL ()
rPutStrLn String
"Showing a specific instance of polymorphic result:"
((TParam, a) -> REPL ()) -> [(TParam, a)] -> REPL ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (TParam, a) -> REPL ()
forall a. PP a => (TParam, a) -> REPL ()
warnDefault [(TParam, a)]
ts
warnDefault :: (TParam, a) -> REPL ()
warnDefault (TParam
x,a
t) =
Doc -> REPL ()
forall a. Show a => a -> REPL ()
rPrint (Doc
" *" Doc -> Doc -> Doc
<+> Int -> Doc -> Doc
nest Int
2 (Doc
"Using" Doc -> Doc -> Doc
<+> Doc -> Doc
quotes (a -> Doc
forall a. PP a => a -> Doc
pp a
t) Doc -> Doc -> Doc
<+> Doc
"for" Doc -> Doc -> Doc
<+>
TypeSource -> Doc
forall a. PP a => a -> Doc
pp (TVarInfo -> TypeSource
T.tvarDesc (TParam -> TVarInfo
T.tpInfo TParam
x))))
itIdent :: M.Ident
itIdent :: Ident
itIdent = String -> Ident
M.packIdent String
"it"
replWriteFile :: FilePath -> BS.ByteString -> (X.SomeException -> REPL ()) -> REPL ()
replWriteFile :: String -> ByteString -> (SomeException -> REPL ()) -> REPL ()
replWriteFile String
fp ByteString
bytes SomeException -> REPL ()
handler =
do Maybe SomeException
x <- IO (Maybe SomeException) -> REPL (Maybe SomeException)
forall a. IO a -> REPL a
io (IO (Maybe SomeException) -> REPL (Maybe SomeException))
-> IO (Maybe SomeException) -> REPL (Maybe SomeException)
forall a b. (a -> b) -> a -> b
$ IO (Maybe SomeException)
-> (SomeException -> IO (Maybe SomeException))
-> IO (Maybe SomeException)
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
X.catch (String -> ByteString -> IO ()
BS.writeFile String
fp ByteString
bytes IO () -> IO (Maybe SomeException) -> IO (Maybe SomeException)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Maybe SomeException -> IO (Maybe SomeException)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe SomeException
forall a. Maybe a
Nothing) (Maybe SomeException -> IO (Maybe SomeException)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe SomeException -> IO (Maybe SomeException))
-> (SomeException -> Maybe SomeException)
-> SomeException
-> IO (Maybe SomeException)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeException -> Maybe SomeException
forall a. a -> Maybe a
Just)
REPL ()
-> (SomeException -> REPL ()) -> Maybe SomeException -> REPL ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (() -> REPL ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()) SomeException -> REPL ()
handler Maybe SomeException
x
replReadFile :: FilePath -> (X.SomeException -> REPL (Maybe BS.ByteString)) -> REPL (Maybe BS.ByteString)
replReadFile :: String
-> (SomeException -> REPL (Maybe ByteString))
-> REPL (Maybe ByteString)
replReadFile String
fp SomeException -> REPL (Maybe ByteString)
handler =
do Either SomeException ByteString
x <- IO (Either SomeException ByteString)
-> REPL (Either SomeException ByteString)
forall a. IO a -> REPL a
io (IO (Either SomeException ByteString)
-> REPL (Either SomeException ByteString))
-> IO (Either SomeException ByteString)
-> REPL (Either SomeException ByteString)
forall a b. (a -> b) -> a -> b
$ IO (Either SomeException ByteString)
-> (SomeException -> IO (Either SomeException ByteString))
-> IO (Either SomeException ByteString)
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
X.catch (ByteString -> Either SomeException ByteString
forall a b. b -> Either a b
Right (ByteString -> Either SomeException ByteString)
-> IO ByteString -> IO (Either SomeException ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` String -> IO ByteString
BS.readFile String
fp) (\SomeException
e -> Either SomeException ByteString
-> IO (Either SomeException ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either SomeException ByteString
-> IO (Either SomeException ByteString))
-> Either SomeException ByteString
-> IO (Either SomeException ByteString)
forall a b. (a -> b) -> a -> b
$ SomeException -> Either SomeException ByteString
forall a b. a -> Either a b
Left SomeException
e)
(SomeException -> REPL (Maybe ByteString))
-> (ByteString -> REPL (Maybe ByteString))
-> Either SomeException ByteString
-> REPL (Maybe ByteString)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either SomeException -> REPL (Maybe ByteString)
handler (Maybe ByteString -> REPL (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ByteString -> REPL (Maybe ByteString))
-> (ByteString -> Maybe ByteString)
-> ByteString
-> REPL (Maybe ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just) Either SomeException ByteString
x
bindItVariable :: T.Type -> T.Expr -> REPL T.Name
bindItVariable :: Type -> Expr -> REPL Name
bindItVariable Type
ty Expr
expr = do
Name
freshIt <- Ident -> NameSource -> REPL Name
freshName Ident
itIdent NameSource
M.UserName
let schema :: Schema
schema = Forall :: [TParam] -> [Type] -> Type -> Schema
T.Forall { sVars :: [TParam]
T.sVars = []
, sProps :: [Type]
T.sProps = []
, sType :: Type
T.sType = Type
ty
}
decl :: Decl
decl = Decl :: Name
-> Schema
-> DeclDef
-> [Pragma]
-> Bool
-> Maybe Fixity
-> Maybe Text
-> Decl
T.Decl { dName :: Name
T.dName = Name
freshIt
, dSignature :: Schema
T.dSignature = Schema
schema
, dDefinition :: DeclDef
T.dDefinition = Expr -> DeclDef
T.DExpr Expr
expr
, dPragmas :: [Pragma]
T.dPragmas = []
, dInfix :: Bool
T.dInfix = Bool
False
, dFixity :: Maybe Fixity
T.dFixity = Maybe Fixity
forall a. Maybe a
Nothing
, dDoc :: Maybe Text
T.dDoc = Maybe Text
forall a. Maybe a
Nothing
}
ModuleCmd () -> REPL ()
forall a. ModuleCmd a -> REPL a
liftModuleCmd ([DeclGroup] -> ModuleCmd ()
M.evalDecls [Decl -> DeclGroup
T.NonRecursive Decl
decl])
DynamicEnv
denv <- REPL DynamicEnv
getDynEnv
let nenv' :: NamingEnv
nenv' = PName -> Name -> NamingEnv
M.singletonE (Ident -> PName
P.UnQual Ident
itIdent) Name
freshIt
NamingEnv -> NamingEnv -> NamingEnv
`M.shadowing` DynamicEnv -> NamingEnv
M.deNames DynamicEnv
denv
DynamicEnv -> REPL ()
setDynEnv (DynamicEnv -> REPL ()) -> DynamicEnv -> REPL ()
forall a b. (a -> b) -> a -> b
$ DynamicEnv
denv { deNames :: NamingEnv
M.deNames = NamingEnv
nenv' }
Name -> REPL Name
forall (m :: * -> *) a. Monad m => a -> m a
return Name
freshIt
bindItVariableVal :: T.Type -> Concrete.Value -> REPL ()
bindItVariableVal :: Type -> Value -> REPL ()
bindItVariableVal Type
ty Value
val =
do PrimMap
prims <- REPL PrimMap
getPrimMap
Maybe Expr
mb <- Eval (Maybe Expr) -> REPL (Maybe Expr)
forall a. Eval a -> REPL a
rEval (PrimMap -> Type -> Value -> Eval (Maybe Expr)
Concrete.toExpr PrimMap
prims Type
ty Value
val)
case Maybe Expr
mb of
Maybe Expr
Nothing -> () -> REPL ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just Expr
expr -> REPL Name -> REPL ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (REPL Name -> REPL ()) -> REPL Name -> REPL ()
forall a b. (a -> b) -> a -> b
$ Type -> Expr -> REPL Name
bindItVariable Type
ty Expr
expr
bindItVariables :: T.Type -> [T.Expr] -> REPL ()
bindItVariables :: Type -> [Expr] -> REPL ()
bindItVariables Type
ty [Expr]
exprs = REPL Name -> REPL ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (REPL Name -> REPL ()) -> REPL Name -> REPL ()
forall a b. (a -> b) -> a -> b
$ Type -> Expr -> REPL Name
bindItVariable Type
seqTy Expr
seqExpr
where
len :: Int
len = [Expr] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Expr]
exprs
seqTy :: Type
seqTy = Type -> Type -> Type
T.tSeq (Int -> Type
forall a. Integral a => a -> Type
T.tNum Int
len) Type
ty
seqExpr :: Expr
seqExpr = [Expr] -> Type -> Expr
T.EList [Expr]
exprs Type
ty
replEvalDecl :: P.Decl P.PName -> REPL ()
replEvalDecl :: Decl PName -> REPL ()
replEvalDecl Decl PName
decl = do
[DeclGroup]
dgs <- [Decl PName] -> REPL [DeclGroup]
replCheckDecls [Decl PName
decl]
[DeclGroup] -> REPL ()
forall a. FreeVars a => a -> REPL ()
validEvalContext [DeclGroup]
dgs
REPL () -> REPL ()
whenDebug ((DeclGroup -> REPL ()) -> [DeclGroup] -> REPL ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\DeclGroup
dg -> (String -> REPL ()
rPutStrLn (DeclGroup -> String
forall a. PP (WithNames a) => a -> String
dump DeclGroup
dg))) [DeclGroup]
dgs)
ModuleCmd () -> REPL ()
forall a. ModuleCmd a -> REPL a
liftModuleCmd ([DeclGroup] -> ModuleCmd ()
M.evalDecls [DeclGroup]
dgs)
replEdit :: String -> REPL Bool
replEdit :: String -> REPL Bool
replEdit String
file = do
Maybe String
mb <- IO (Maybe String) -> REPL (Maybe String)
forall a. IO a -> REPL a
io (String -> IO (Maybe String)
lookupEnv String
"EDITOR")
let editor :: String
editor = String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"vim" Maybe String
mb
IO Bool -> REPL Bool
forall a. IO a -> REPL a
io (IO Bool -> REPL Bool) -> IO Bool -> REPL Bool
forall a b. (a -> b) -> a -> b
$ do
(Maybe Handle
_,Maybe Handle
_,Maybe Handle
_,ProcessHandle
ph) <- CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
createProcess (String -> CreateProcess
shell ([String] -> String
unwords [String
editor, String
file]))
ExitCode
exit <- ProcessHandle -> IO ExitCode
waitForProcess ProcessHandle
ph
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (ExitCode
exit ExitCode -> ExitCode -> Bool
forall a. Eq a => a -> a -> Bool
== ExitCode
ExitSuccess)
type CommandMap = Trie CommandDescr
sanitize :: String -> String
sanitize :: ShowS
sanitize = (Char -> Bool) -> ShowS
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isSpace
sanitizeEnd :: String -> String
sanitizeEnd :: ShowS
sanitizeEnd = ShowS
forall a. [a] -> [a]
reverse ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
sanitize ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
forall a. [a] -> [a]
reverse
trim :: String -> String
trim :: ShowS
trim = ShowS
sanitizeEnd ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
sanitize
splitCommand :: String -> Maybe (String,String)
splitCommand :: String -> Maybe (String, String)
splitCommand String
txt =
case ShowS
sanitize String
txt of
Char
':' : String
more
| (String
as,String
bs) <- (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
span (\Char
x -> Char -> Bool
isPunctuation Char
x Bool -> Bool -> Bool
|| Char -> Bool
isSymbol Char
x) String
more
, Bool -> Bool
not (String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
as) -> (String, String) -> Maybe (String, String)
forall a. a -> Maybe a
Just (Char
':' Char -> ShowS
forall a. a -> [a] -> [a]
: String
as, ShowS
sanitize String
bs)
| (String
as,String
bs) <- (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isSpace String
more
, Bool -> Bool
not (String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
as) -> (String, String) -> Maybe (String, String)
forall a. a -> Maybe a
Just (Char
':' Char -> ShowS
forall a. a -> [a] -> [a]
: String
as, ShowS
sanitize String
bs)
| Bool
otherwise -> Maybe (String, String)
forall a. Maybe a
Nothing
String
expr -> Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Bool
not (String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
expr)) Maybe () -> Maybe (String, String) -> Maybe (String, String)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (String, String) -> Maybe (String, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (String
expr,[])
uncons :: [a] -> Maybe (a,[a])
uncons :: [a] -> Maybe (a, [a])
uncons [a]
as = case [a]
as of
a
a:[a]
rest -> (a, [a]) -> Maybe (a, [a])
forall a. a -> Maybe a
Just (a
a,[a]
rest)
[a]
_ -> Maybe (a, [a])
forall a. Maybe a
Nothing
findCommand :: String -> [CommandDescr]
findCommand :: String -> [CommandDescr]
findCommand String
str = String -> CommandMap -> [CommandDescr]
forall a. String -> Trie a -> [a]
lookupTrie String
str CommandMap
commands
findCommandExact :: String -> [CommandDescr]
findCommandExact :: String -> [CommandDescr]
findCommandExact String
str = String -> CommandMap -> [CommandDescr]
forall a. String -> Trie a -> [a]
lookupTrieExact String
str CommandMap
commands
findNbCommand :: Bool -> String -> [CommandDescr]
findNbCommand :: Bool -> String -> [CommandDescr]
findNbCommand Bool
True String
str = String -> CommandMap -> [CommandDescr]
forall a. String -> Trie a -> [a]
lookupTrieExact String
str CommandMap
nbCommands
findNbCommand Bool
False String
str = String -> CommandMap -> [CommandDescr]
forall a. String -> Trie a -> [a]
lookupTrie String
str CommandMap
nbCommands
parseCommand :: (String -> [CommandDescr]) -> String -> Maybe Command
parseCommand :: (String -> [CommandDescr]) -> String -> Maybe Command
parseCommand String -> [CommandDescr]
findCmd String
line = do
(String
cmd,String
args) <- String -> Maybe (String, String)
splitCommand String
line
let args' :: String
args' = ShowS
sanitizeEnd String
args
case String -> [CommandDescr]
findCmd String
cmd of
[CommandDescr
c] -> case CommandDescr -> CommandBody
cBody CommandDescr
c of
ExprArg String -> REPL ()
body -> Command -> Maybe Command
forall a. a -> Maybe a
Just (REPL () -> Command
Command (String -> REPL ()
body String
args'))
DeclsArg String -> REPL ()
body -> Command -> Maybe Command
forall a. a -> Maybe a
Just (REPL () -> Command
Command (String -> REPL ()
body String
args'))
ExprTypeArg String -> REPL ()
body -> Command -> Maybe Command
forall a. a -> Maybe a
Just (REPL () -> Command
Command (String -> REPL ()
body String
args'))
ModNameArg String -> REPL ()
body -> Command -> Maybe Command
forall a. a -> Maybe a
Just (REPL () -> Command
Command (String -> REPL ()
body String
args'))
FilenameArg String -> REPL ()
body -> Command -> Maybe Command
forall a. a -> Maybe a
Just (REPL () -> Command
Command (String -> REPL ()
body (String -> REPL ()) -> REPL String -> REPL ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> REPL String
expandHome String
args'))
OptionArg String -> REPL ()
body -> Command -> Maybe Command
forall a. a -> Maybe a
Just (REPL () -> Command
Command (String -> REPL ()
body String
args'))
ShellArg String -> REPL ()
body -> Command -> Maybe Command
forall a. a -> Maybe a
Just (REPL () -> Command
Command (String -> REPL ()
body String
args'))
HelpArg String -> REPL ()
body -> Command -> Maybe Command
forall a. a -> Maybe a
Just (REPL () -> Command
Command (String -> REPL ()
body String
args'))
NoArg REPL ()
body -> Command -> Maybe Command
forall a. a -> Maybe a
Just (REPL () -> Command
Command REPL ()
body)
FileExprArg String -> String -> REPL ()
body ->
case String -> Maybe (String, String)
extractFilePath String
args' of
Just (String
fp,String
expr) -> Command -> Maybe Command
forall a. a -> Maybe a
Just (REPL () -> Command
Command (String -> REPL String
expandHome String
fp REPL String -> (String -> REPL ()) -> REPL ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (String -> String -> REPL ()) -> String -> String -> REPL ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> String -> REPL ()
body String
expr))
Maybe (String, String)
Nothing -> Maybe Command
forall a. Maybe a
Nothing
[] -> case String -> Maybe (Char, String)
forall a. [a] -> Maybe (a, [a])
uncons String
cmd of
Just (Char
':',String
_) -> Command -> Maybe Command
forall a. a -> Maybe a
Just (String -> Command
Unknown String
cmd)
Just (Char, String)
_ -> Command -> Maybe Command
forall a. a -> Maybe a
Just (REPL () -> Command
Command (String -> REPL ()
evalCmd String
line))
Maybe (Char, String)
_ -> Maybe Command
forall a. Maybe a
Nothing
[CommandDescr]
cs -> Command -> Maybe Command
forall a. a -> Maybe a
Just (String -> [String] -> Command
Ambiguous String
cmd ((CommandDescr -> [String]) -> [CommandDescr] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap CommandDescr -> [String]
cNames [CommandDescr]
cs))
where
expandHome :: String -> REPL String
expandHome String
path =
case String
path of
Char
'~' : Char
c : String
more | Char -> Bool
isPathSeparator Char
c -> do String
dir <- IO String -> REPL String
forall a. IO a -> REPL a
io IO String
getHomeDirectory
String -> REPL String
forall (m :: * -> *) a. Monad m => a -> m a
return (String
dir String -> ShowS
</> String
more)
String
_ -> String -> REPL String
forall (m :: * -> *) a. Monad m => a -> m a
return String
path
extractFilePath :: String -> Maybe (String, String)
extractFilePath String
ipt =
let quoted :: a -> [a] -> ([a], [a])
quoted a
q = (\([a]
a,[a]
b) -> ([a]
a, Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
drop Int
1 [a]
b)) (([a], [a]) -> ([a], [a]))
-> ([a] -> ([a], [a])) -> [a] -> ([a], [a])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> [a] -> ([a], [a])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
q)
in case String
ipt of
String
"" -> Maybe (String, String)
forall a. Maybe a
Nothing
Char
'\'':String
rest -> (String, String) -> Maybe (String, String)
forall a. a -> Maybe a
Just ((String, String) -> Maybe (String, String))
-> (String, String) -> Maybe (String, String)
forall a b. (a -> b) -> a -> b
$ Char -> String -> (String, String)
forall a. Eq a => a -> [a] -> ([a], [a])
quoted Char
'\'' String
rest
Char
'"':String
rest -> (String, String) -> Maybe (String, String)
forall a. a -> Maybe a
Just ((String, String) -> Maybe (String, String))
-> (String, String) -> Maybe (String, String)
forall a b. (a -> b) -> a -> b
$ Char -> String -> (String, String)
forall a. Eq a => a -> [a] -> ([a], [a])
quoted Char
'"' String
rest
String
_ -> (String, String) -> Maybe (String, String)
forall a. a -> Maybe a
Just ((String, String) -> Maybe (String, String))
-> (String, String) -> Maybe (String, String)
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isSpace String
ipt