{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
module Cryptol.ModuleSystem.Monad where
import Cryptol.Eval (EvalEnv,EvalOpts(..))
import qualified Cryptol.Backend.Monad as E
import Cryptol.ModuleSystem.Env
import Cryptol.ModuleSystem.Fingerprint
import Cryptol.ModuleSystem.Interface
import Cryptol.ModuleSystem.Name (FreshM(..),Supply)
import Cryptol.ModuleSystem.Renamer (RenamerError(),RenamerWarning())
import qualified Cryptol.Parser as Parser
import qualified Cryptol.Parser.AST as P
import Cryptol.Parser.Position (Located)
import Cryptol.Utils.Panic (panic)
import qualified Cryptol.Parser.NoPat as NoPat
import qualified Cryptol.Parser.NoInclude as NoInc
import qualified Cryptol.TypeCheck as T
import qualified Cryptol.TypeCheck.AST as T
import Cryptol.Parser.Position (Range)
import Cryptol.Utils.Ident (interactiveName, noModuleName)
import Cryptol.Utils.PP
import Cryptol.Utils.Logger(Logger)
import qualified Control.Monad.Fail as Fail
import Control.Monad.IO.Class
import Control.Exception (IOException)
import Data.ByteString (ByteString)
import Data.Function (on)
import Data.Maybe (isJust)
import Data.Text.Encoding.Error (UnicodeException)
import MonadLib
import System.Directory (canonicalizePath)
import GHC.Generics (Generic)
import Control.DeepSeq
import Prelude ()
import Prelude.Compat
data ImportSource
= FromModule P.ModName
| FromImport (Located P.Import)
| FromModuleInstance (Located P.ModName)
deriving (Int -> ImportSource -> ShowS
[ImportSource] -> ShowS
ImportSource -> String
(Int -> ImportSource -> ShowS)
-> (ImportSource -> String)
-> ([ImportSource] -> ShowS)
-> Show ImportSource
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImportSource] -> ShowS
$cshowList :: [ImportSource] -> ShowS
show :: ImportSource -> String
$cshow :: ImportSource -> String
showsPrec :: Int -> ImportSource -> ShowS
$cshowsPrec :: Int -> ImportSource -> ShowS
Show, (forall x. ImportSource -> Rep ImportSource x)
-> (forall x. Rep ImportSource x -> ImportSource)
-> Generic ImportSource
forall x. Rep ImportSource x -> ImportSource
forall x. ImportSource -> Rep ImportSource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImportSource x -> ImportSource
$cfrom :: forall x. ImportSource -> Rep ImportSource x
Generic, ImportSource -> ()
(ImportSource -> ()) -> NFData ImportSource
forall a. (a -> ()) -> NFData a
rnf :: ImportSource -> ()
$crnf :: ImportSource -> ()
NFData)
instance Eq ImportSource where
== :: ImportSource -> ImportSource -> Bool
(==) = ModName -> ModName -> Bool
forall a. Eq a => a -> a -> Bool
(==) (ModName -> ModName -> Bool)
-> (ImportSource -> ModName)
-> ImportSource
-> ImportSource
-> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` ImportSource -> ModName
importedModule
instance PP ImportSource where
ppPrec :: Int -> ImportSource -> Doc
ppPrec Int
_ ImportSource
is = case ImportSource
is of
FromModule ModName
n -> String -> Doc
text String
"module name" Doc -> Doc -> Doc
<+> ModName -> Doc
forall a. PP a => a -> Doc
pp ModName
n
FromImport Located Import
li -> String -> Doc
text String
"import of module" Doc -> Doc -> Doc
<+> ModName -> Doc
forall a. PP a => a -> Doc
pp (Import -> ModName
P.iModule (Located Import -> Import
forall a. Located a -> a
P.thing Located Import
li))
FromModuleInstance Located ModName
l ->
String -> Doc
text String
"instantiation of module" Doc -> Doc -> Doc
<+> ModName -> Doc
forall a. PP a => a -> Doc
pp (Located ModName -> ModName
forall a. Located a -> a
P.thing Located ModName
l)
importedModule :: ImportSource -> P.ModName
importedModule :: ImportSource -> ModName
importedModule ImportSource
is =
case ImportSource
is of
FromModule ModName
n -> ModName
n
FromImport Located Import
li -> Import -> ModName
P.iModule (Located Import -> Import
forall a. Located a -> a
P.thing Located Import
li)
FromModuleInstance Located ModName
l -> Located ModName -> ModName
forall a. Located a -> a
P.thing Located ModName
l
data ModuleError
= ModuleNotFound P.ModName [FilePath]
| CantFindFile FilePath
| BadUtf8 ModulePath UnicodeException
| OtherIOError FilePath IOException
| ModuleParseError ModulePath Parser.ParseError
| RecursiveModules [ImportSource]
| RenamerErrors ImportSource [RenamerError]
| NoPatErrors ImportSource [NoPat.Error]
| NoIncludeErrors ImportSource [NoInc.IncludeError]
| TypeCheckingFailed ImportSource T.NameMap [(Range,T.Error)]
| OtherFailure String
| ModuleNameMismatch P.ModName (Located P.ModName)
| DuplicateModuleName P.ModName FilePath FilePath
| ImportedParamModule P.ModName
| FailedToParameterizeModDefs P.ModName [T.Name]
| NotAParameterizedModule P.ModName
| ErrorInFile ModulePath ModuleError
deriving (Int -> ModuleError -> ShowS
[ModuleError] -> ShowS
ModuleError -> String
(Int -> ModuleError -> ShowS)
-> (ModuleError -> String)
-> ([ModuleError] -> ShowS)
-> Show ModuleError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModuleError] -> ShowS
$cshowList :: [ModuleError] -> ShowS
show :: ModuleError -> String
$cshow :: ModuleError -> String
showsPrec :: Int -> ModuleError -> ShowS
$cshowsPrec :: Int -> ModuleError -> ShowS
Show)
instance NFData ModuleError where
rnf :: ModuleError -> ()
rnf ModuleError
e = case ModuleError
e of
ModuleNotFound ModName
src [String]
path -> ModName
src ModName -> [String] -> [String]
forall a b. NFData a => a -> b -> b
`deepseq` [String]
path [String] -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
CantFindFile String
path -> String
path String -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
BadUtf8 ModulePath
path UnicodeException
ue -> (ModulePath, UnicodeException) -> ()
forall a. NFData a => a -> ()
rnf (ModulePath
path, UnicodeException
ue)
OtherIOError String
path IOException
exn -> String
path String -> IOException -> IOException
forall a b. NFData a => a -> b -> b
`deepseq` IOException
exn IOException -> () -> ()
`seq` ()
ModuleParseError ModulePath
source ParseError
err -> ModulePath
source ModulePath -> ParseError -> ParseError
forall a b. NFData a => a -> b -> b
`deepseq` ParseError
err ParseError -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
RecursiveModules [ImportSource]
mods -> [ImportSource]
mods [ImportSource] -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
RenamerErrors ImportSource
src [RenamerError]
errs -> ImportSource
src ImportSource -> [RenamerError] -> [RenamerError]
forall a b. NFData a => a -> b -> b
`deepseq` [RenamerError]
errs [RenamerError] -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
NoPatErrors ImportSource
src [Error]
errs -> ImportSource
src ImportSource -> [Error] -> [Error]
forall a b. NFData a => a -> b -> b
`deepseq` [Error]
errs [Error] -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
NoIncludeErrors ImportSource
src [IncludeError]
errs -> ImportSource
src ImportSource -> [IncludeError] -> [IncludeError]
forall a b. NFData a => a -> b -> b
`deepseq` [IncludeError]
errs [IncludeError] -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
TypeCheckingFailed ImportSource
nm NameMap
src [(Range, Error)]
errs -> ImportSource
nm ImportSource -> NameMap -> NameMap
forall a b. NFData a => a -> b -> b
`deepseq` NameMap
src NameMap -> [(Range, Error)] -> [(Range, Error)]
forall a b. NFData a => a -> b -> b
`deepseq` [(Range, Error)]
errs [(Range, Error)] -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
ModuleNameMismatch ModName
expected Located ModName
found ->
ModName
expected ModName -> Located ModName -> Located ModName
forall a b. NFData a => a -> b -> b
`deepseq` Located ModName
found Located ModName -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
DuplicateModuleName ModName
name String
path1 String
path2 ->
ModName
name ModName -> ShowS
forall a b. NFData a => a -> b -> b
`deepseq` String
path1 String -> ShowS
forall a b. NFData a => a -> b -> b
`deepseq` String
path2 String -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
OtherFailure String
x -> String
x String -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
ImportedParamModule ModName
x -> ModName
x ModName -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
FailedToParameterizeModDefs ModName
x [Name]
xs -> ModName
x ModName -> [Name] -> [Name]
forall a b. NFData a => a -> b -> b
`deepseq` [Name]
xs [Name] -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
NotAParameterizedModule ModName
x -> ModName
x ModName -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
ErrorInFile ModulePath
x ModuleError
y -> ModulePath
x ModulePath -> ModuleError -> ModuleError
forall a b. NFData a => a -> b -> b
`deepseq` ModuleError
y ModuleError -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
instance PP ModuleError where
ppPrec :: Int -> ModuleError -> Doc
ppPrec Int
prec ModuleError
e = case ModuleError
e of
ModuleNotFound ModName
src [String]
path ->
String -> Doc
text String
"[error]" Doc -> Doc -> Doc
<+>
String -> Doc
text String
"Could not find module" Doc -> Doc -> Doc
<+> ModName -> Doc
forall a. PP a => a -> Doc
pp ModName
src
Doc -> Doc -> Doc
$$
Doc -> Int -> Doc -> Doc
hang (String -> Doc
text String
"Searched paths:")
Int
4 ([Doc] -> Doc
vcat ((String -> Doc) -> [String] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map String -> Doc
text [String]
path))
Doc -> Doc -> Doc
$$
String -> Doc
text String
"Set the CRYPTOLPATH environment variable to search more directories"
CantFindFile String
path ->
String -> Doc
text String
"[error]" Doc -> Doc -> Doc
<+>
String -> Doc
text String
"can't find file:" Doc -> Doc -> Doc
<+> String -> Doc
text String
path
BadUtf8 ModulePath
path UnicodeException
_ue ->
String -> Doc
text String
"[error]" Doc -> Doc -> Doc
<+>
String -> Doc
text String
"bad utf-8 encoding:" Doc -> Doc -> Doc
<+> ModulePath -> Doc
forall a. PP a => a -> Doc
pp ModulePath
path
OtherIOError String
path IOException
exn ->
Doc -> Int -> Doc -> Doc
hang (String -> Doc
text String
"[error]" Doc -> Doc -> Doc
<+>
String -> Doc
text String
"IO error while loading file:" Doc -> Doc -> Doc
<+> String -> Doc
text String
path Doc -> Doc -> Doc
<.> Doc
colon)
Int
4 (String -> Doc
text (IOException -> String
forall a. Show a => a -> String
show IOException
exn))
ModuleParseError ModulePath
_source ParseError
err -> ParseError -> Doc
Parser.ppError ParseError
err
RecursiveModules [ImportSource]
mods ->
Doc -> Int -> Doc -> Doc
hang (String -> Doc
text String
"[error] module imports form a cycle:")
Int
4 ([Doc] -> Doc
vcat ((ImportSource -> Doc) -> [ImportSource] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map ImportSource -> Doc
forall a. PP a => a -> Doc
pp ([ImportSource] -> [ImportSource]
forall a. [a] -> [a]
reverse [ImportSource]
mods)))
RenamerErrors ImportSource
_src [RenamerError]
errs -> [Doc] -> Doc
vcat ((RenamerError -> Doc) -> [RenamerError] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map RenamerError -> Doc
forall a. PP a => a -> Doc
pp [RenamerError]
errs)
NoPatErrors ImportSource
_src [Error]
errs -> [Doc] -> Doc
vcat ((Error -> Doc) -> [Error] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Error -> Doc
forall a. PP a => a -> Doc
pp [Error]
errs)
NoIncludeErrors ImportSource
_src [IncludeError]
errs -> [Doc] -> Doc
vcat ((IncludeError -> Doc) -> [IncludeError] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map IncludeError -> Doc
NoInc.ppIncludeError [IncludeError]
errs)
TypeCheckingFailed ImportSource
_src NameMap
nm [(Range, Error)]
errs -> [Doc] -> Doc
vcat (((Range, Error) -> Doc) -> [(Range, Error)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (NameMap -> (Range, Error) -> Doc
T.ppNamedError NameMap
nm) [(Range, Error)]
errs)
ModuleNameMismatch ModName
expected Located ModName
found ->
Doc -> Int -> Doc -> Doc
hang (String -> Doc
text String
"[error]" Doc -> Doc -> Doc
<+> Range -> Doc
forall a. PP a => a -> Doc
pp (Located ModName -> Range
forall a. Located a -> Range
P.srcRange Located ModName
found) Doc -> Doc -> Doc
<.> Char -> Doc
char Char
':')
Int
4 ([Doc] -> Doc
vcat [ String -> Doc
text String
"File name does not match module name:"
, String -> Doc
text String
"Saw:" Doc -> Doc -> Doc
<+> ModName -> Doc
forall a. PP a => a -> Doc
pp (Located ModName -> ModName
forall a. Located a -> a
P.thing Located ModName
found)
, String -> Doc
text String
"Expected:" Doc -> Doc -> Doc
<+> ModName -> Doc
forall a. PP a => a -> Doc
pp ModName
expected
])
DuplicateModuleName ModName
name String
path1 String
path2 ->
Doc -> Int -> Doc -> Doc
hang (String -> Doc
text String
"[error] module" Doc -> Doc -> Doc
<+> ModName -> Doc
forall a. PP a => a -> Doc
pp ModName
name Doc -> Doc -> Doc
<+>
String -> Doc
text String
"is defined in multiple files:")
Int
4 ([Doc] -> Doc
vcat [String -> Doc
text String
path1, String -> Doc
text String
path2])
OtherFailure String
x -> String -> Doc
text String
x
ImportedParamModule ModName
p ->
String -> Doc
text String
"[error] Import of a non-instantiated parameterized module:" Doc -> Doc -> Doc
<+> ModName -> Doc
forall a. PP a => a -> Doc
pp ModName
p
FailedToParameterizeModDefs ModName
x [Name]
xs ->
Doc -> Int -> Doc -> Doc
hang (String -> Doc
text String
"[error] Parameterized module" Doc -> Doc -> Doc
<+> ModName -> Doc
forall a. PP a => a -> Doc
pp ModName
x Doc -> Doc -> Doc
<+>
String -> Doc
text String
"has polymorphic parameters:")
Int
4 ([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
$ (Name -> Doc) -> [Name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Name -> Doc
forall a. PP a => a -> Doc
pp [Name]
xs)
NotAParameterizedModule ModName
x ->
String -> Doc
text String
"[error] Module" Doc -> Doc -> Doc
<+> ModName -> Doc
forall a. PP a => a -> Doc
pp ModName
x Doc -> Doc -> Doc
<+> String -> Doc
text String
"does not have parameters."
ErrorInFile ModulePath
_ ModuleError
x -> Int -> ModuleError -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
prec ModuleError
x
moduleNotFound :: P.ModName -> [FilePath] -> ModuleM a
moduleNotFound :: ModName -> [String] -> ModuleM a
moduleNotFound ModName
name [String]
paths = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ModuleM a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleError
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
forall (m :: * -> *) i a. ExceptionM m i => i -> m a
raise (ModName -> [String] -> ModuleError
ModuleNotFound ModName
name [String]
paths))
cantFindFile :: FilePath -> ModuleM a
cantFindFile :: String -> ModuleM a
cantFindFile String
path = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ModuleM a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleError
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
forall (m :: * -> *) i a. ExceptionM m i => i -> m a
raise (String -> ModuleError
CantFindFile String
path))
badUtf8 :: ModulePath -> UnicodeException -> ModuleM a
badUtf8 :: ModulePath -> UnicodeException -> ModuleM a
badUtf8 ModulePath
path UnicodeException
ue = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ModuleM a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleError
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
forall (m :: * -> *) i a. ExceptionM m i => i -> m a
raise (ModulePath -> UnicodeException -> ModuleError
BadUtf8 ModulePath
path UnicodeException
ue))
otherIOError :: FilePath -> IOException -> ModuleM a
otherIOError :: String -> IOException -> ModuleM a
otherIOError String
path IOException
exn = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ModuleM a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleError
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
forall (m :: * -> *) i a. ExceptionM m i => i -> m a
raise (String -> IOException -> ModuleError
OtherIOError String
path IOException
exn))
moduleParseError :: ModulePath -> Parser.ParseError -> ModuleM a
moduleParseError :: ModulePath -> ParseError -> ModuleM a
moduleParseError ModulePath
path ParseError
err =
ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ModuleM a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleError
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
forall (m :: * -> *) i a. ExceptionM m i => i -> m a
raise (ModulePath -> ParseError -> ModuleError
ModuleParseError ModulePath
path ParseError
err))
recursiveModules :: [ImportSource] -> ModuleM a
recursiveModules :: [ImportSource] -> ModuleM a
recursiveModules [ImportSource]
loaded = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ModuleM a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleError
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
forall (m :: * -> *) i a. ExceptionM m i => i -> m a
raise ([ImportSource] -> ModuleError
RecursiveModules [ImportSource]
loaded))
renamerErrors :: [RenamerError] -> ModuleM a
renamerErrors :: [RenamerError] -> ModuleM a
renamerErrors [RenamerError]
errs = do
ImportSource
src <- ModuleM ImportSource
getImportSource
ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ModuleM a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleError
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
forall (m :: * -> *) i a. ExceptionM m i => i -> m a
raise (ImportSource -> [RenamerError] -> ModuleError
RenamerErrors ImportSource
src [RenamerError]
errs))
noPatErrors :: [NoPat.Error] -> ModuleM a
noPatErrors :: [Error] -> ModuleM a
noPatErrors [Error]
errs = do
ImportSource
src <- ModuleM ImportSource
getImportSource
ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ModuleM a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleError
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
forall (m :: * -> *) i a. ExceptionM m i => i -> m a
raise (ImportSource -> [Error] -> ModuleError
NoPatErrors ImportSource
src [Error]
errs))
noIncludeErrors :: [NoInc.IncludeError] -> ModuleM a
noIncludeErrors :: [IncludeError] -> ModuleM a
noIncludeErrors [IncludeError]
errs = do
ImportSource
src <- ModuleM ImportSource
getImportSource
ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ModuleM a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleError
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
forall (m :: * -> *) i a. ExceptionM m i => i -> m a
raise (ImportSource -> [IncludeError] -> ModuleError
NoIncludeErrors ImportSource
src [IncludeError]
errs))
typeCheckingFailed :: T.NameMap -> [(Range,T.Error)] -> ModuleM a
typeCheckingFailed :: NameMap -> [(Range, Error)] -> ModuleM a
typeCheckingFailed NameMap
nameMap [(Range, Error)]
errs = do
ImportSource
src <- ModuleM ImportSource
getImportSource
ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ModuleM a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleError
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
forall (m :: * -> *) i a. ExceptionM m i => i -> m a
raise (ImportSource -> NameMap -> [(Range, Error)] -> ModuleError
TypeCheckingFailed ImportSource
src NameMap
nameMap [(Range, Error)]
errs))
moduleNameMismatch :: P.ModName -> Located P.ModName -> ModuleM a
moduleNameMismatch :: ModName -> Located ModName -> ModuleM a
moduleNameMismatch ModName
expected Located ModName
found =
ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ModuleM a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleError
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
forall (m :: * -> *) i a. ExceptionM m i => i -> m a
raise (ModName -> Located ModName -> ModuleError
ModuleNameMismatch ModName
expected Located ModName
found))
duplicateModuleName :: P.ModName -> FilePath -> FilePath -> ModuleM a
duplicateModuleName :: ModName -> String -> String -> ModuleM a
duplicateModuleName ModName
name String
path1 String
path2 =
ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ModuleM a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleError
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
forall (m :: * -> *) i a. ExceptionM m i => i -> m a
raise (ModName -> String -> String -> ModuleError
DuplicateModuleName ModName
name String
path1 String
path2))
importParamModule :: P.ModName -> ModuleM a
importParamModule :: ModName -> ModuleM a
importParamModule ModName
x = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ModuleM a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleError
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
forall (m :: * -> *) i a. ExceptionM m i => i -> m a
raise (ModName -> ModuleError
ImportedParamModule ModName
x))
failedToParameterizeModDefs :: P.ModName -> [T.Name] -> ModuleM a
failedToParameterizeModDefs :: ModName -> [Name] -> ModuleM a
failedToParameterizeModDefs ModName
x [Name]
xs =
ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ModuleM a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleError
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
forall (m :: * -> *) i a. ExceptionM m i => i -> m a
raise (ModName -> [Name] -> ModuleError
FailedToParameterizeModDefs ModName
x [Name]
xs))
notAParameterizedModule :: P.ModName -> ModuleM a
notAParameterizedModule :: ModName -> ModuleM a
notAParameterizedModule ModName
x = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ModuleM a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleError
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
forall (m :: * -> *) i a. ExceptionM m i => i -> m a
raise (ModName -> ModuleError
NotAParameterizedModule ModName
x))
errorInFile :: ModulePath -> ModuleM a -> ModuleM a
errorInFile :: ModulePath -> ModuleM a -> ModuleM a
errorInFile ModulePath
file (ModuleT ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
m) = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ModuleM a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
m ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> (ModuleError
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a)
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
forall (m :: * -> *) x a.
RunExceptionM m x =>
m a -> (x -> m a) -> m a
`handle` ModuleError
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
forall (m :: * -> *) a.
ExceptionM m ModuleError =>
ModuleError -> m a
h)
where h :: ModuleError -> m a
h ModuleError
e = ModuleError -> m a
forall (m :: * -> *) i a. ExceptionM m i => i -> m a
raise (ModuleError -> m a) -> ModuleError -> m a
forall a b. (a -> b) -> a -> b
$ case ModuleError
e of
ErrorInFile {} -> ModuleError
e
ModuleError
_ -> ModulePath -> ModuleError -> ModuleError
ErrorInFile ModulePath
file ModuleError
e
data ModuleWarning
= TypeCheckWarnings T.NameMap [(Range,T.Warning)]
| RenamerWarnings [RenamerWarning]
deriving (Int -> ModuleWarning -> ShowS
[ModuleWarning] -> ShowS
ModuleWarning -> String
(Int -> ModuleWarning -> ShowS)
-> (ModuleWarning -> String)
-> ([ModuleWarning] -> ShowS)
-> Show ModuleWarning
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModuleWarning] -> ShowS
$cshowList :: [ModuleWarning] -> ShowS
show :: ModuleWarning -> String
$cshow :: ModuleWarning -> String
showsPrec :: Int -> ModuleWarning -> ShowS
$cshowsPrec :: Int -> ModuleWarning -> ShowS
Show, (forall x. ModuleWarning -> Rep ModuleWarning x)
-> (forall x. Rep ModuleWarning x -> ModuleWarning)
-> Generic ModuleWarning
forall x. Rep ModuleWarning x -> ModuleWarning
forall x. ModuleWarning -> Rep ModuleWarning x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ModuleWarning x -> ModuleWarning
$cfrom :: forall x. ModuleWarning -> Rep ModuleWarning x
Generic, ModuleWarning -> ()
(ModuleWarning -> ()) -> NFData ModuleWarning
forall a. (a -> ()) -> NFData a
rnf :: ModuleWarning -> ()
$crnf :: ModuleWarning -> ()
NFData)
instance PP ModuleWarning where
ppPrec :: Int -> ModuleWarning -> Doc
ppPrec Int
_ ModuleWarning
w = case ModuleWarning
w of
TypeCheckWarnings NameMap
nm [(Range, Warning)]
ws -> [Doc] -> Doc
vcat (((Range, Warning) -> Doc) -> [(Range, Warning)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (NameMap -> (Range, Warning) -> Doc
T.ppNamedWarning NameMap
nm) [(Range, Warning)]
ws)
RenamerWarnings [RenamerWarning]
ws -> [Doc] -> Doc
vcat ((RenamerWarning -> Doc) -> [RenamerWarning] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map RenamerWarning -> Doc
forall a. PP a => a -> Doc
pp [RenamerWarning]
ws)
warn :: [ModuleWarning] -> ModuleM ()
warn :: [ModuleWarning] -> ModuleM ()
warn = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ()
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ())
-> ([ModuleWarning]
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
())
-> [ModuleWarning]
-> ModuleM ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ModuleWarning]
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall (m :: * -> *) i. WriterM m i => i -> m ()
put
typeCheckWarnings :: T.NameMap -> [(Range,T.Warning)] -> ModuleM ()
typeCheckWarnings :: NameMap -> [(Range, Warning)] -> ModuleM ()
typeCheckWarnings NameMap
nameMap [(Range, Warning)]
ws
| [(Range, Warning)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Range, Warning)]
ws = () -> ModuleM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = [ModuleWarning] -> ModuleM ()
warn [NameMap -> [(Range, Warning)] -> ModuleWarning
TypeCheckWarnings NameMap
nameMap [(Range, Warning)]
ws]
renamerWarnings :: [RenamerWarning] -> ModuleM ()
renamerWarnings :: [RenamerWarning] -> ModuleM ()
renamerWarnings [RenamerWarning]
ws
| [RenamerWarning] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [RenamerWarning]
ws = () -> ModuleM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = [ModuleWarning] -> ModuleM ()
warn [[RenamerWarning] -> ModuleWarning
RenamerWarnings [RenamerWarning]
ws]
data RO m =
RO { RO m -> [ImportSource]
roLoading :: [ImportSource]
, RO m -> EvalOpts
roEvalOpts :: EvalOpts
, RO m -> String -> m ByteString
roFileReader :: FilePath -> m ByteString
}
emptyRO :: EvalOpts -> (FilePath -> m ByteString) -> RO m
emptyRO :: EvalOpts -> (String -> m ByteString) -> RO m
emptyRO EvalOpts
ev String -> m ByteString
fileReader =
RO :: forall (m :: * -> *).
[ImportSource] -> EvalOpts -> (String -> m ByteString) -> RO m
RO { roLoading :: [ImportSource]
roLoading = [], roEvalOpts :: EvalOpts
roEvalOpts = EvalOpts
ev, roFileReader :: String -> m ByteString
roFileReader = String -> m ByteString
fileReader }
newtype ModuleT m a = ModuleT
{ ModuleT m a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
unModuleT :: ReaderT (RO m)
(StateT ModuleEnv
(ExceptionT ModuleError
(WriterT [ModuleWarning] m))) a
}
instance Monad m => Functor (ModuleT m) where
{-# INLINE fmap #-}
fmap :: (a -> b) -> ModuleT m a -> ModuleT m b
fmap a -> b
f ModuleT m a
m = ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
b
-> ModuleT m b
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT ((a -> b)
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f (ModuleT m a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
forall (m :: * -> *) a.
ModuleT m a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
unModuleT ModuleT m a
m))
instance Monad m => Applicative (ModuleT m) where
{-# INLINE pure #-}
pure :: a -> ModuleT m a
pure a
x = ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
x)
{-# INLINE (<*>) #-}
ModuleT m (a -> b)
l <*> :: ModuleT m (a -> b) -> ModuleT m a -> ModuleT m b
<*> ModuleT m a
r = ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
b
-> ModuleT m b
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleT m (a -> b)
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
(a -> b)
forall (m :: * -> *) a.
ModuleT m a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
unModuleT ModuleT m (a -> b)
l ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
(a -> b)
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ModuleT m a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
forall (m :: * -> *) a.
ModuleT m a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
unModuleT ModuleT m a
r)
instance Monad m => Monad (ModuleT m) where
{-# INLINE return #-}
return :: a -> ModuleT m a
return a
x = ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
forall (m :: * -> *) a. Monad m => a -> m a
return a
x)
{-# INLINE (>>=) #-}
ModuleT m a
m >>= :: ModuleT m a -> (a -> ModuleT m b) -> ModuleT m b
>>= a -> ModuleT m b
f = ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
b
-> ModuleT m b
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleT m a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
forall (m :: * -> *) a.
ModuleT m a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
unModuleT ModuleT m a
m ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> (a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
b)
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ModuleT m b
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
b
forall (m :: * -> *) a.
ModuleT m a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
unModuleT (ModuleT m b
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
b)
-> (a -> ModuleT m b)
-> a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ModuleT m b
f)
instance Fail.MonadFail m => Fail.MonadFail (ModuleT m) where
{-# INLINE fail #-}
fail :: String -> ModuleT m a
fail = ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a)
-> (String
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a)
-> String
-> ModuleT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModuleError
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
forall (m :: * -> *) i a. ExceptionM m i => i -> m a
raise (ModuleError
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a)
-> (String -> ModuleError)
-> String
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ModuleError
OtherFailure
instance MonadT ModuleT where
{-# INLINE lift #-}
lift :: m a -> ModuleT m a
lift = ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a)
-> (m a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a)
-> m a
-> ModuleT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)) a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadT t, Monad m) =>
m a -> t m a
lift (StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)) a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a)
-> (m a
-> StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)) a)
-> m a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExceptionT ModuleError (WriterT [ModuleWarning] m) a
-> StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)) a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadT t, Monad m) =>
m a -> t m a
lift (ExceptionT ModuleError (WriterT [ModuleWarning] m) a
-> StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)) a)
-> (m a -> ExceptionT ModuleError (WriterT [ModuleWarning] m) a)
-> m a
-> StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WriterT [ModuleWarning] m a
-> ExceptionT ModuleError (WriterT [ModuleWarning] m) a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadT t, Monad m) =>
m a -> t m a
lift (WriterT [ModuleWarning] m a
-> ExceptionT ModuleError (WriterT [ModuleWarning] m) a)
-> (m a -> WriterT [ModuleWarning] m a)
-> m a
-> ExceptionT ModuleError (WriterT [ModuleWarning] m) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m a -> WriterT [ModuleWarning] m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadT t, Monad m) =>
m a -> t m a
lift
instance Monad m => FreshM (ModuleT m) where
liftSupply :: (Supply -> (a, Supply)) -> ModuleT m a
liftSupply Supply -> (a, Supply)
f = ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a)
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
forall a b. (a -> b) -> a -> b
$
do ModuleEnv
me <- ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get
let (a
a,Supply
s') = Supply -> (a, Supply)
f (ModuleEnv -> Supply
meSupply ModuleEnv
me)
ModuleEnv
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
()
forall (m :: * -> *) i. StateM m i => i -> m ()
set (ModuleEnv
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
())
-> ModuleEnv
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
()
forall a b. (a -> b) -> a -> b
$! ModuleEnv
me { meSupply :: Supply
meSupply = Supply
s' }
a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
instance MonadIO m => MonadIO (ModuleT m) where
liftIO :: IO a -> ModuleT m a
liftIO IO a
m = m a -> ModuleT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadT t, Monad m) =>
m a -> t m a
lift (m a -> ModuleT m a) -> m a -> ModuleT m a
forall a b. (a -> b) -> a -> b
$ IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO a
m
runModuleT :: Monad m
=> (EvalOpts, FilePath -> m ByteString, ModuleEnv)
-> ModuleT m a
-> m (Either ModuleError (a, ModuleEnv), [ModuleWarning])
runModuleT :: (EvalOpts, String -> m ByteString, ModuleEnv)
-> ModuleT m a
-> m (Either ModuleError (a, ModuleEnv), [ModuleWarning])
runModuleT (EvalOpts
ev, String -> m ByteString
byteReader, ModuleEnv
env) ModuleT m a
m =
WriterT [ModuleWarning] m (Either ModuleError (a, ModuleEnv))
-> m (Either ModuleError (a, ModuleEnv), [ModuleWarning])
forall (m :: * -> *) i a. Monad m => WriterT i m a -> m (a, i)
runWriterT
(WriterT [ModuleWarning] m (Either ModuleError (a, ModuleEnv))
-> m (Either ModuleError (a, ModuleEnv), [ModuleWarning]))
-> WriterT [ModuleWarning] m (Either ModuleError (a, ModuleEnv))
-> m (Either ModuleError (a, ModuleEnv), [ModuleWarning])
forall a b. (a -> b) -> a -> b
$ ExceptionT ModuleError (WriterT [ModuleWarning] m) (a, ModuleEnv)
-> WriterT [ModuleWarning] m (Either ModuleError (a, ModuleEnv))
forall i (m :: * -> *) a. ExceptionT i m a -> m (Either i a)
runExceptionT
(ExceptionT ModuleError (WriterT [ModuleWarning] m) (a, ModuleEnv)
-> WriterT [ModuleWarning] m (Either ModuleError (a, ModuleEnv)))
-> ExceptionT
ModuleError (WriterT [ModuleWarning] m) (a, ModuleEnv)
-> WriterT [ModuleWarning] m (Either ModuleError (a, ModuleEnv))
forall a b. (a -> b) -> a -> b
$ ModuleEnv
-> StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)) a
-> ExceptionT
ModuleError (WriterT [ModuleWarning] m) (a, ModuleEnv)
forall i (m :: * -> *) a. i -> StateT i m a -> m (a, i)
runStateT ModuleEnv
env
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)) a
-> ExceptionT
ModuleError (WriterT [ModuleWarning] m) (a, ModuleEnv))
-> StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)) a
-> ExceptionT
ModuleError (WriterT [ModuleWarning] m) (a, ModuleEnv)
forall a b. (a -> b) -> a -> b
$ RO m
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)) a
forall i (m :: * -> *) a. i -> ReaderT i m a -> m a
runReaderT (EvalOpts -> (String -> m ByteString) -> RO m
forall (m :: * -> *). EvalOpts -> (String -> m ByteString) -> RO m
emptyRO EvalOpts
ev String -> m ByteString
byteReader)
(ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)) a)
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)) a
forall a b. (a -> b) -> a -> b
$ ModuleT m a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
forall (m :: * -> *) a.
ModuleT m a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
unModuleT ModuleT m a
m
type ModuleM = ModuleT IO
runModuleM :: (EvalOpts, FilePath -> IO ByteString, ModuleEnv) -> ModuleM a
-> IO (Either ModuleError (a,ModuleEnv),[ModuleWarning])
runModuleM :: (EvalOpts, String -> IO ByteString, ModuleEnv)
-> ModuleM a
-> IO (Either ModuleError (a, ModuleEnv), [ModuleWarning])
runModuleM = (EvalOpts, String -> IO ByteString, ModuleEnv)
-> ModuleM a
-> IO (Either ModuleError (a, ModuleEnv), [ModuleWarning])
forall (m :: * -> *) a.
Monad m =>
(EvalOpts, String -> m ByteString, ModuleEnv)
-> ModuleT m a
-> m (Either ModuleError (a, ModuleEnv), [ModuleWarning])
runModuleT
io :: BaseM m IO => IO a -> ModuleT m a
io :: IO a -> ModuleT m a
io IO a
m = ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (IO a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
forall (m :: * -> *) (n :: * -> *) a. BaseM m n => n a -> m a
inBase IO a
m)
getByteReader :: Monad m => ModuleT m (FilePath -> m ByteString)
getByteReader :: ModuleT m (String -> m ByteString)
getByteReader = ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
(String -> m ByteString)
-> ModuleT m (String -> m ByteString)
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
(String -> m ByteString)
-> ModuleT m (String -> m ByteString))
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
(String -> m ByteString)
-> ModuleT m (String -> m ByteString)
forall a b. (a -> b) -> a -> b
$ do
RO { roFileReader :: forall (m :: * -> *). RO m -> String -> m ByteString
roFileReader = String -> m ByteString
readFileBytes } <- ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
(RO m)
forall (m :: * -> *) i. ReaderM m i => m i
ask
(String -> m ByteString)
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
(String -> m ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return String -> m ByteString
readFileBytes
readBytes :: Monad m => FilePath -> ModuleT m ByteString
readBytes :: String -> ModuleT m ByteString
readBytes String
fn = do
String -> m ByteString
fileReader <- ModuleT m (String -> m ByteString)
forall (m :: * -> *). Monad m => ModuleT m (String -> m ByteString)
getByteReader
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
ByteString
-> ModuleT m ByteString
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
ByteString
-> ModuleT m ByteString)
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
ByteString
-> ModuleT m ByteString
forall a b. (a -> b) -> a -> b
$ StateT
ModuleEnv
(ExceptionT ModuleError (WriterT [ModuleWarning] m))
ByteString
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
ByteString
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadT t, Monad m) =>
m a -> t m a
lift (StateT
ModuleEnv
(ExceptionT ModuleError (WriterT [ModuleWarning] m))
ByteString
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
ByteString)
-> StateT
ModuleEnv
(ExceptionT ModuleError (WriterT [ModuleWarning] m))
ByteString
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
ByteString
forall a b. (a -> b) -> a -> b
$ ExceptionT ModuleError (WriterT [ModuleWarning] m) ByteString
-> StateT
ModuleEnv
(ExceptionT ModuleError (WriterT [ModuleWarning] m))
ByteString
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadT t, Monad m) =>
m a -> t m a
lift (ExceptionT ModuleError (WriterT [ModuleWarning] m) ByteString
-> StateT
ModuleEnv
(ExceptionT ModuleError (WriterT [ModuleWarning] m))
ByteString)
-> ExceptionT ModuleError (WriterT [ModuleWarning] m) ByteString
-> StateT
ModuleEnv
(ExceptionT ModuleError (WriterT [ModuleWarning] m))
ByteString
forall a b. (a -> b) -> a -> b
$ WriterT [ModuleWarning] m ByteString
-> ExceptionT ModuleError (WriterT [ModuleWarning] m) ByteString
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadT t, Monad m) =>
m a -> t m a
lift (WriterT [ModuleWarning] m ByteString
-> ExceptionT ModuleError (WriterT [ModuleWarning] m) ByteString)
-> WriterT [ModuleWarning] m ByteString
-> ExceptionT ModuleError (WriterT [ModuleWarning] m) ByteString
forall a b. (a -> b) -> a -> b
$ m ByteString -> WriterT [ModuleWarning] m ByteString
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadT t, Monad m) =>
m a -> t m a
lift (m ByteString -> WriterT [ModuleWarning] m ByteString)
-> m ByteString -> WriterT [ModuleWarning] m ByteString
forall a b. (a -> b) -> a -> b
$ String -> m ByteString
fileReader String
fn
getModuleEnv :: Monad m => ModuleT m ModuleEnv
getModuleEnv :: ModuleT m ModuleEnv
getModuleEnv = ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
ModuleEnv
-> ModuleT m ModuleEnv
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get
setModuleEnv :: Monad m => ModuleEnv -> ModuleT m ()
setModuleEnv :: ModuleEnv -> ModuleT m ()
setModuleEnv = ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
()
-> ModuleT m ()
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
()
-> ModuleT m ())
-> (ModuleEnv
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
())
-> ModuleEnv
-> ModuleT m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModuleEnv
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
()
forall (m :: * -> *) i. StateM m i => i -> m ()
set
modifyModuleEnv :: Monad m => (ModuleEnv -> ModuleEnv) -> ModuleT m ()
modifyModuleEnv :: (ModuleEnv -> ModuleEnv) -> ModuleT m ()
modifyModuleEnv ModuleEnv -> ModuleEnv
f = ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
()
-> ModuleT m ()
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
()
-> ModuleT m ())
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
()
-> ModuleT m ()
forall a b. (a -> b) -> a -> b
$ do
ModuleEnv
env <- ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get
ModuleEnv
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
()
forall (m :: * -> *) i. StateM m i => i -> m ()
set (ModuleEnv
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
())
-> ModuleEnv
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
()
forall a b. (a -> b) -> a -> b
$! ModuleEnv -> ModuleEnv
f ModuleEnv
env
getLoadedMaybe :: P.ModName -> ModuleM (Maybe LoadedModule)
getLoadedMaybe :: ModName -> ModuleM (Maybe LoadedModule)
getLoadedMaybe ModName
mn = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
(Maybe LoadedModule)
-> ModuleM (Maybe LoadedModule)
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
(Maybe LoadedModule)
-> ModuleM (Maybe LoadedModule))
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
(Maybe LoadedModule)
-> ModuleM (Maybe LoadedModule)
forall a b. (a -> b) -> a -> b
$
do ModuleEnv
env <- ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get
Maybe LoadedModule
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
(Maybe LoadedModule)
forall (m :: * -> *) a. Monad m => a -> m a
return (ModName -> ModuleEnv -> Maybe LoadedModule
lookupModule ModName
mn ModuleEnv
env)
isLoaded :: P.ModName -> ModuleM Bool
isLoaded :: ModName -> ModuleM Bool
isLoaded ModName
mn = Maybe LoadedModule -> Bool
forall a. Maybe a -> Bool
isJust (Maybe LoadedModule -> Bool)
-> ModuleM (Maybe LoadedModule) -> ModuleM Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ModName -> ModuleM (Maybe LoadedModule)
getLoadedMaybe ModName
mn
loadingImport :: Located P.Import -> ModuleM a -> ModuleM a
loadingImport :: Located Import -> ModuleM a -> ModuleM a
loadingImport = ImportSource -> ModuleM a -> ModuleM a
forall a. ImportSource -> ModuleM a -> ModuleM a
loading (ImportSource -> ModuleM a -> ModuleM a)
-> (Located Import -> ImportSource)
-> Located Import
-> ModuleM a
-> ModuleM a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Located Import -> ImportSource
FromImport
loadingModule :: P.ModName -> ModuleM a -> ModuleM a
loadingModule :: ModName -> ModuleM a -> ModuleM a
loadingModule = ImportSource -> ModuleM a -> ModuleM a
forall a. ImportSource -> ModuleM a -> ModuleM a
loading (ImportSource -> ModuleM a -> ModuleM a)
-> (ModName -> ImportSource) -> ModName -> ModuleM a -> ModuleM a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModName -> ImportSource
FromModule
loadingModInstance :: Located P.ModName -> ModuleM a -> ModuleM a
loadingModInstance :: Located ModName -> ModuleM a -> ModuleM a
loadingModInstance = ImportSource -> ModuleM a -> ModuleM a
forall a. ImportSource -> ModuleM a -> ModuleM a
loading (ImportSource -> ModuleM a -> ModuleM a)
-> (Located ModName -> ImportSource)
-> Located ModName
-> ModuleM a
-> ModuleM a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Located ModName -> ImportSource
FromModuleInstance
interactive :: ModuleM a -> ModuleM a
interactive :: ModuleM a -> ModuleM a
interactive = ModName -> ModuleM a -> ModuleM a
forall a. ModName -> ModuleM a -> ModuleM a
loadingModule ModName
interactiveName
loading :: ImportSource -> ModuleM a -> ModuleM a
loading :: ImportSource -> ModuleM a -> ModuleM a
loading ImportSource
src ModuleM a
m = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ModuleM a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ModuleM a)
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ModuleM a
forall a b. (a -> b) -> a -> b
$ do
RO IO
ro <- ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
(RO IO)
forall (m :: * -> *) i. ReaderM m i => m i
ask
let ro' :: RO IO
ro' = RO IO
ro { roLoading :: [ImportSource]
roLoading = ImportSource
src ImportSource -> [ImportSource] -> [ImportSource]
forall a. a -> [a] -> [a]
: RO IO -> [ImportSource]
forall (m :: * -> *). RO m -> [ImportSource]
roLoading RO IO
ro }
Bool
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (ImportSource
src ImportSource -> [ImportSource] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` RO IO -> [ImportSource]
forall (m :: * -> *). RO m -> [ImportSource]
roLoading RO IO
ro) (ModuleError
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall (m :: * -> *) i a. ExceptionM m i => i -> m a
raise ([ImportSource] -> ModuleError
RecursiveModules (RO IO -> [ImportSource]
forall (m :: * -> *). RO m -> [ImportSource]
roLoading RO IO
ro')))
RO IO
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
forall (m :: * -> *) i a. RunReaderM m i => i -> m a -> m a
local RO IO
ro' (ModuleM a
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
forall (m :: * -> *) a.
ModuleT m a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
unModuleT ModuleM a
m)
getImportSource :: ModuleM ImportSource
getImportSource :: ModuleM ImportSource
getImportSource = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ImportSource
-> ModuleM ImportSource
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ImportSource
-> ModuleM ImportSource)
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ImportSource
-> ModuleM ImportSource
forall a b. (a -> b) -> a -> b
$ do
RO IO
ro <- ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
(RO IO)
forall (m :: * -> *) i. ReaderM m i => m i
ask
case RO IO -> [ImportSource]
forall (m :: * -> *). RO m -> [ImportSource]
roLoading RO IO
ro of
ImportSource
is : [ImportSource]
_ -> ImportSource
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ImportSource
forall (m :: * -> *) a. Monad m => a -> m a
return ImportSource
is
[ImportSource]
_ -> ImportSource
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ImportSource
forall (m :: * -> *) a. Monad m => a -> m a
return (ModName -> ImportSource
FromModule ModName
noModuleName)
getIface :: P.ModName -> ModuleM Iface
getIface :: ModName -> ModuleM Iface
getIface ModName
mn =
do ModuleEnv
env <- ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
-> ModuleT IO ModuleEnv
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get
case ModName -> ModuleEnv -> Maybe LoadedModule
lookupModule ModName
mn ModuleEnv
env of
Just LoadedModule
lm -> Iface -> ModuleM Iface
forall (m :: * -> *) a. Monad m => a -> m a
return (LoadedModule -> Iface
lmInterface LoadedModule
lm)
Maybe LoadedModule
Nothing -> String -> [String] -> ModuleM Iface
forall a. HasCallStack => String -> [String] -> a
panic String
"ModuleSystem" [String
"Interface not available", Doc -> String
forall a. Show a => a -> String
show (ModName -> Doc
forall a. PP a => a -> Doc
pp ModName
mn)]
getLoaded :: P.ModName -> ModuleM T.Module
getLoaded :: ModName -> ModuleM Module
getLoaded ModName
mn = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
Module
-> ModuleM Module
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
Module
-> ModuleM Module)
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
Module
-> ModuleM Module
forall a b. (a -> b) -> a -> b
$
do ModuleEnv
env <- ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get
case ModName -> ModuleEnv -> Maybe LoadedModule
lookupModule ModName
mn ModuleEnv
env of
Just LoadedModule
lm -> Module
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
Module
forall (m :: * -> *) a. Monad m => a -> m a
return (LoadedModule -> Module
lmModule LoadedModule
lm)
Maybe LoadedModule
Nothing -> String
-> [String]
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
Module
forall a. HasCallStack => String -> [String] -> a
panic String
"ModuleSystem" [String
"Module not available", Doc -> String
forall a. Show a => a -> String
show (ModName -> Doc
forall a. PP a => a -> Doc
pp ModName
mn) ]
getNameSeeds :: ModuleM T.NameSeeds
getNameSeeds :: ModuleM NameSeeds
getNameSeeds = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
NameSeeds
-> ModuleM NameSeeds
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleEnv -> NameSeeds
meNameSeeds (ModuleEnv -> NameSeeds)
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
NameSeeds
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get)
getSupply :: ModuleM Supply
getSupply :: ModuleM Supply
getSupply = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
Supply
-> ModuleM Supply
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleEnv -> Supply
meSupply (ModuleEnv -> Supply)
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
Supply
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get)
getMonoBinds :: ModuleM Bool
getMonoBinds :: ModuleM Bool
getMonoBinds = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
Bool
-> ModuleM Bool
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleEnv -> Bool
meMonoBinds (ModuleEnv -> Bool)
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get)
setMonoBinds :: Bool -> ModuleM ()
setMonoBinds :: Bool -> ModuleM ()
setMonoBinds Bool
b = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ()
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ())
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ()
forall a b. (a -> b) -> a -> b
$ do
ModuleEnv
env <- ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get
ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall (m :: * -> *) i. StateM m i => i -> m ()
set (ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
())
-> ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall a b. (a -> b) -> a -> b
$! ModuleEnv
env { meMonoBinds :: Bool
meMonoBinds = Bool
b }
setNameSeeds :: T.NameSeeds -> ModuleM ()
setNameSeeds :: NameSeeds -> ModuleM ()
setNameSeeds NameSeeds
seeds = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ()
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ())
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ()
forall a b. (a -> b) -> a -> b
$ do
ModuleEnv
env <- ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get
ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall (m :: * -> *) i. StateM m i => i -> m ()
set (ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
())
-> ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall a b. (a -> b) -> a -> b
$! ModuleEnv
env { meNameSeeds :: NameSeeds
meNameSeeds = NameSeeds
seeds }
setSupply :: Supply -> ModuleM ()
setSupply :: Supply -> ModuleM ()
setSupply Supply
supply = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ()
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ())
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ()
forall a b. (a -> b) -> a -> b
$
do ModuleEnv
env <- ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get
ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall (m :: * -> *) i. StateM m i => i -> m ()
set (ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
())
-> ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall a b. (a -> b) -> a -> b
$! ModuleEnv
env { meSupply :: Supply
meSupply = Supply
supply }
unloadModule :: (LoadedModule -> Bool) -> ModuleM ()
unloadModule :: (LoadedModule -> Bool) -> ModuleM ()
unloadModule LoadedModule -> Bool
rm = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ()
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ())
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ()
forall a b. (a -> b) -> a -> b
$ do
ModuleEnv
env <- ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get
ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall (m :: * -> *) i. StateM m i => i -> m ()
set (ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
())
-> ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall a b. (a -> b) -> a -> b
$! ModuleEnv
env { meLoadedModules :: LoadedModules
meLoadedModules = (LoadedModule -> Bool) -> LoadedModules -> LoadedModules
removeLoadedModule LoadedModule -> Bool
rm (ModuleEnv -> LoadedModules
meLoadedModules ModuleEnv
env) }
loadedModule :: ModulePath -> Fingerprint -> T.Module -> ModuleM ()
loadedModule :: ModulePath -> Fingerprint -> Module -> ModuleM ()
loadedModule ModulePath
path Fingerprint
fp Module
m = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ()
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ())
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ()
forall a b. (a -> b) -> a -> b
$ do
ModuleEnv
env <- ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get
String
ident <- case ModulePath
path of
InFile String
p -> ModuleT IO String
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
String
forall (m :: * -> *) a.
ModuleT m a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
unModuleT (ModuleT IO String
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
String)
-> ModuleT IO String
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
String
forall a b. (a -> b) -> a -> b
$ IO String -> ModuleT IO String
forall (m :: * -> *) a. BaseM m IO => IO a -> ModuleT m a
io (String -> IO String
canonicalizePath String
p)
InMem String
l ByteString
_ -> String
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
String
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
l
ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall (m :: * -> *) i. StateM m i => i -> m ()
set (ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
())
-> ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall a b. (a -> b) -> a -> b
$! ModuleEnv
env { meLoadedModules :: LoadedModules
meLoadedModules = ModulePath
-> String
-> Fingerprint
-> Module
-> LoadedModules
-> LoadedModules
addLoadedModule ModulePath
path String
ident Fingerprint
fp Module
m (ModuleEnv -> LoadedModules
meLoadedModules ModuleEnv
env) }
modifyEvalEnv :: (EvalEnv -> E.Eval EvalEnv) -> ModuleM ()
modifyEvalEnv :: (EvalEnv -> Eval EvalEnv) -> ModuleM ()
modifyEvalEnv EvalEnv -> Eval EvalEnv
f = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ()
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ())
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ()
forall a b. (a -> b) -> a -> b
$ do
ModuleEnv
env <- ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get
let evalEnv :: EvalEnv
evalEnv = ModuleEnv -> EvalEnv
meEvalEnv ModuleEnv
env
EvalEnv
evalEnv' <- IO EvalEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
EvalEnv
forall (m :: * -> *) (n :: * -> *) a. BaseM m n => n a -> m a
inBase (IO EvalEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
EvalEnv)
-> IO EvalEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
EvalEnv
forall a b. (a -> b) -> a -> b
$ Eval EvalEnv -> IO EvalEnv
forall a. Eval a -> IO a
E.runEval (EvalEnv -> Eval EvalEnv
f EvalEnv
evalEnv)
ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall (m :: * -> *) i. StateM m i => i -> m ()
set (ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
())
-> ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall a b. (a -> b) -> a -> b
$! ModuleEnv
env { meEvalEnv :: EvalEnv
meEvalEnv = EvalEnv
evalEnv' }
getEvalEnv :: ModuleM EvalEnv
getEvalEnv :: ModuleM EvalEnv
getEvalEnv = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
EvalEnv
-> ModuleM EvalEnv
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleEnv -> EvalEnv
meEvalEnv (ModuleEnv -> EvalEnv)
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
EvalEnv
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get)
getEvalOpts :: ModuleM EvalOpts
getEvalOpts :: ModuleM EvalOpts
getEvalOpts = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
EvalOpts
-> ModuleM EvalOpts
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (RO IO -> EvalOpts
forall (m :: * -> *). RO m -> EvalOpts
roEvalOpts (RO IO -> EvalOpts)
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
(RO IO)
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
EvalOpts
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
(RO IO)
forall (m :: * -> *) i. ReaderM m i => m i
ask)
getFocusedModule :: ModuleM (Maybe P.ModName)
getFocusedModule :: ModuleM (Maybe ModName)
getFocusedModule = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
(Maybe ModName)
-> ModuleM (Maybe ModName)
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleEnv -> Maybe ModName
meFocusedModule (ModuleEnv -> Maybe ModName)
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
(Maybe ModName)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get)
setFocusedModule :: P.ModName -> ModuleM ()
setFocusedModule :: ModName -> ModuleM ()
setFocusedModule ModName
n = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ()
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ())
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ()
forall a b. (a -> b) -> a -> b
$ do
ModuleEnv
me <- ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get
ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall (m :: * -> *) i. StateM m i => i -> m ()
set (ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
())
-> ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall a b. (a -> b) -> a -> b
$! ModuleEnv
me { meFocusedModule :: Maybe ModName
meFocusedModule = ModName -> Maybe ModName
forall a. a -> Maybe a
Just ModName
n }
getSearchPath :: ModuleM [FilePath]
getSearchPath :: ModuleM [String]
getSearchPath = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
[String]
-> ModuleM [String]
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleEnv -> [String]
meSearchPath (ModuleEnv -> [String])
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
[String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get)
withPrependedSearchPath :: [FilePath] -> ModuleM a -> ModuleM a
withPrependedSearchPath :: [String] -> ModuleM a -> ModuleM a
withPrependedSearchPath [String]
fps ModuleM a
m = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ModuleM a
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ModuleM a)
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
-> ModuleM a
forall a b. (a -> b) -> a -> b
$ do
ModuleEnv
env0 <- ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get
let fps0 :: [String]
fps0 = ModuleEnv -> [String]
meSearchPath ModuleEnv
env0
ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall (m :: * -> *) i. StateM m i => i -> m ()
set (ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
())
-> ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall a b. (a -> b) -> a -> b
$! ModuleEnv
env0 { meSearchPath :: [String]
meSearchPath = [String]
fps [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
fps0 }
a
x <- ModuleM a
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
forall (m :: * -> *) a.
ModuleT m a
-> ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
unModuleT ModuleM a
m
ModuleEnv
env <- ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get
ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall (m :: * -> *) i. StateM m i => i -> m ()
set (ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
())
-> ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall a b. (a -> b) -> a -> b
$! ModuleEnv
env { meSearchPath :: [String]
meSearchPath = [String]
fps0 }
a
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
a
forall (m :: * -> *) a. Monad m => a -> m a
return a
x
getFocusedEnv :: ModuleM ModContext
getFocusedEnv :: ModuleM ModContext
getFocusedEnv = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModContext
-> ModuleM ModContext
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleEnv -> ModContext
focusedEnv (ModuleEnv -> ModContext)
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModContext
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get)
getDynEnv :: ModuleM DynamicEnv
getDynEnv :: ModuleM DynamicEnv
getDynEnv = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
DynamicEnv
-> ModuleM DynamicEnv
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ModuleEnv -> DynamicEnv
meDynEnv (ModuleEnv -> DynamicEnv)
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
DynamicEnv
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get)
setDynEnv :: DynamicEnv -> ModuleM ()
setDynEnv :: DynamicEnv -> ModuleM ()
setDynEnv DynamicEnv
denv = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ()
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ())
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ()
forall a b. (a -> b) -> a -> b
$ do
ModuleEnv
me <- ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get
ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall (m :: * -> *) i. StateM m i => i -> m ()
set (ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
())
-> ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall a b. (a -> b) -> a -> b
$! ModuleEnv
me { meDynEnv :: DynamicEnv
meDynEnv = DynamicEnv
denv }
setSolver :: T.SolverConfig -> ModuleM ()
setSolver :: SolverConfig -> ModuleM ()
setSolver SolverConfig
cfg = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ()
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ())
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
-> ModuleM ()
forall a b. (a -> b) -> a -> b
$ do
ModuleEnv
me <- ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get
ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall (m :: * -> *) i. StateM m i => i -> m ()
set (ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
())
-> ModuleEnv
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
()
forall a b. (a -> b) -> a -> b
$! ModuleEnv
me { meSolverConfig :: SolverConfig
meSolverConfig = SolverConfig
cfg }
getSolverConfig :: ModuleM T.SolverConfig
getSolverConfig :: ModuleM SolverConfig
getSolverConfig = ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
SolverConfig
-> ModuleM SolverConfig
forall (m :: * -> *) a.
ReaderT
(RO m)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m)))
a
-> ModuleT m a
ModuleT (ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
SolverConfig
-> ModuleM SolverConfig)
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
SolverConfig
-> ModuleM SolverConfig
forall a b. (a -> b) -> a -> b
$ do
ModuleEnv
me <- ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
ModuleEnv
forall (m :: * -> *) i. StateM m i => m i
get
SolverConfig
-> ReaderT
(RO IO)
(StateT
ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] IO)))
SolverConfig
forall (m :: * -> *) a. Monad m => a -> m a
return (ModuleEnv -> SolverConfig
meSolverConfig ModuleEnv
me)
withLogger :: (Logger -> a -> IO b) -> a -> ModuleM b
withLogger :: (Logger -> a -> IO b) -> a -> ModuleM b
withLogger Logger -> a -> IO b
f a
a = do EvalOpts
l <- ModuleM EvalOpts
getEvalOpts
IO b -> ModuleM b
forall (m :: * -> *) a. BaseM m IO => IO a -> ModuleT m a
io (Logger -> a -> IO b
f (EvalOpts -> Logger
evalLogger EvalOpts
l) a
a)