1
1
mirror of https://github.com/anoma/juvix.git synced 2024-09-11 08:15:41 +03:00

Refactor readFile and some parsers to use Path instead of FilePath (#2649)

Now the prelude exports this function:
```
readFile :: (MonadIO m) => Path Abs File -> m Text
readFile = liftIO . Utf8.readFile . toFilePath
```
It is more convenient to use because it uses typed `Path` and works in
any `MonadIO`.
This commit is contained in:
Jan Mas Rovira 2024-02-19 17:33:58 +01:00 committed by GitHub
parent 86e8458b9f
commit a825f41507
No known key found for this signature in database
GPG Key ID: B5690EEEBB952194
55 changed files with 142 additions and 138 deletions

View File

@ -11,8 +11,8 @@ import Juvix.Compiler.Reg.Pretty qualified as Reg
runCommand :: forall r. (Members '[EmbedIO, App, TaggedLock] r) => AsmCompileOptions -> Sem r ()
runCommand opts = do
file <- getFile
s <- readFile (toFilePath file)
case Asm.runParser (toFilePath file) s of
s <- readFile file
case Asm.runParser file s of
Left err -> exitJuvixError (JuvixError err)
Right tab -> do
ep <- getEntryPoint (AppPath (preFileFromAbs file) True)

View File

@ -8,8 +8,8 @@ import Juvix.Compiler.Asm.Translation.FromSource qualified as Asm
runCommand :: forall r. (Members '[EmbedIO, App] r) => AsmRunOptions -> Sem r ()
runCommand opts = do
afile :: Path Abs File <- fromAppPathFile file
s <- readFile (toFilePath afile)
case Asm.runParser (toFilePath afile) s of
s <- readFile afile
case Asm.runParser afile s of
Left err -> exitJuvixError (JuvixError err)
Right tab -> runAsm (not (opts ^. asmRunNoValidate)) tab
where

View File

@ -9,8 +9,8 @@ import Juvix.Compiler.Asm.Translation.FromSource qualified as Asm
runCommand :: forall r. (Members '[EmbedIO, App] r) => AsmValidateOptions -> Sem r ()
runCommand opts = do
afile :: Path Abs File <- fromAppPathFile file
s <- readFile (toFilePath afile)
case Asm.runParser (toFilePath afile) s of
s <- readFile afile
case Asm.runParser afile s of
Left err -> exitJuvixError (JuvixError err)
Right tab -> do
case Asm.validate' tab of

View File

@ -9,8 +9,8 @@ import Juvix.Compiler.Casm.Validate qualified as Casm
runCommand :: forall r. (Members '[EmbedIO, App] r) => CasmReadOptions -> Sem r ()
runCommand opts = do
afile :: Path Abs File <- fromAppPathFile file
s <- readFile (toFilePath afile)
case Casm.runParser (toFilePath afile) s of
s <- readFile afile
case Casm.runParser afile s of
Left err -> exitJuvixError (JuvixError err)
Right (labi, code) ->
case Casm.validate labi code of

View File

@ -9,8 +9,8 @@ import Juvix.Compiler.Casm.Validate qualified as Casm
runCommand :: forall r. (Members '[EmbedIO, App] r) => CasmRunOptions -> Sem r ()
runCommand opts = do
afile :: Path Abs File <- fromAppPathFile file
s <- readFile (toFilePath afile)
case Casm.runParser (toFilePath afile) s of
s <- readFile afile
case Casm.runParser afile s of
Left err -> exitJuvixError (JuvixError err)
Right (labi, code) ->
case Casm.validate labi code of

View File

@ -10,7 +10,7 @@ runCommand :: forall r a. (Members '[EmbedIO, App, TaggedLock] r, CanonicalProje
runCommand opts = do
inputFile :: Path Abs File <- fromAppPathFile sinputFile
ep <- getEntryPoint sinputFile
s' <- readFile $ toFilePath inputFile
s' <- readFile inputFile
tab <- getRight (mapLeft JuvixError (Core.runParserMain inputFile defaultModuleId mempty s'))
r <- runReader ep . runError @JuvixError $ coreToAsm (Core.moduleFromInfoTable tab)
tab' <- getRight r

View File

@ -9,7 +9,7 @@ import Juvix.Compiler.Core.Translation.FromSource qualified as Core
runCommand :: forall r. (Members '[EmbedIO, App, TaggedLock] r) => CompileOptions -> Sem r ()
runCommand opts = do
file <- getFile
s <- readFile (toFilePath file)
s <- readFile file
tab <- getRight (mapLeft JuvixError (Core.runParserMain file defaultModuleId mempty s))
let arg = PipelineArg opts file (Core.moduleFromInfoTable tab)
case opts ^. compileTarget of

View File

@ -8,7 +8,7 @@ import Juvix.Compiler.Core.Translation.FromSource qualified as Core
runCommand :: forall r. (Members '[EmbedIO, App] r) => CoreEvalOptions -> Sem r ()
runCommand opts = do
f :: Path Abs File <- fromAppPathFile b
s <- readFile (toFilePath f)
s <- readFile f
case Core.runParser f defaultModuleId mempty s of
Left err -> exitJuvixError (JuvixError err)
Right (tab, Just node) -> do evalAndPrint opts tab node

View File

@ -8,7 +8,7 @@ import Juvix.Compiler.Core.Translation.FromSource qualified as Core
runCommand :: forall r. (Members '[EmbedIO, App] r) => CoreNormalizeOptions -> Sem r ()
runCommand opts = do
f :: Path Abs File <- fromAppPathFile b
s <- readFile (toFilePath f)
s <- readFile f
case Core.runParser f defaultModuleId mempty s of
Left err -> exitJuvixError (JuvixError err)
Right (tab, Just node) -> do normalizeAndPrint opts tab node

View File

@ -22,7 +22,7 @@ runCommand ::
runCommand opts = do
gopts <- askGlobalOptions
inputFile :: Path Abs File <- fromAppPathFile sinputFile
s' <- readFile . toFilePath $ inputFile
s' <- readFile inputFile
tab <- getRight (mapLeft JuvixError (Core.runParserMain inputFile defaultModuleId mempty s'))
let r = run $ runReader (project @GlobalOptions @Core.CoreOptions gopts) $ runError @JuvixError $ Core.applyTransformations (project opts ^. coreReadTransformations) (Core.moduleFromInfoTable tab)
tab0 <- getRight $ mapLeft JuvixError r

View File

@ -75,7 +75,7 @@ runRepl opts tab = do
Right (tab', Nothing) ->
runRepl opts tab'
':' : 'l' : ' ' : f -> do
s' <- readFile f
s' <- readFile (absFile f)
sf <- someBaseToAbs' (someFile f)
case Core.runParser sf defaultModuleId mempty s' of
Left err -> do

View File

@ -10,7 +10,7 @@ runCommand :: forall r a. (Members '[EmbedIO, App] r, CanonicalProjection a Core
runCommand opts = do
gopts <- askGlobalOptions
inputFile :: Path Abs File <- fromAppPathFile sinputFile
s' <- readFile $ toFilePath inputFile
s' <- readFile inputFile
(tab, _) <- getRight (mapLeft JuvixError (Core.runParser inputFile defaultModuleId mempty s'))
let r =
run $

View File

@ -14,7 +14,7 @@ runCommand opts = do
let b :: AppPath File
b = opts ^. gebInferOptionsInputFile
f :: Path Abs File <- fromAppPathFile b
content :: Text <- readFile (toFilePath f)
content :: Text <- readFile f
case Geb.runParser f content of
Right (Geb.ExpressionMorphism morph) -> do
case Geb.inferObject' morph of

View File

@ -19,7 +19,7 @@ runCommand opts = do
let b :: AppPath File
b = project opts ^. gebEvalOptionsInputFile
f :: Path Abs File <- fromAppPathFile b
content :: Text <- readFile (toFilePath f)
content :: Text <- readFile f
case Geb.runParser f content of
Left err -> exitJuvixError (JuvixError err)
Right gebTerm -> do

View File

@ -13,7 +13,7 @@ runCommand opts = do
let b :: AppPath File
b = opts ^. gebInferOptionsInputFile
f :: Path Abs File <- fromAppPathFile b
content :: Text <- readFile (toFilePath f)
content :: Text <- readFile f
case Geb.runParser f content of
Right (Geb.ExpressionMorphism gebTerm) ->
case Geb.inferObject' gebTerm of

View File

@ -14,7 +14,7 @@ runCommand opts = do
let b :: AppPath File
b = opts ^. gebReadOptionsInputFile
f :: Path Abs File <- fromAppPathFile b
content :: Text <- readFile (toFilePath f)
content :: Text <- readFile f
case Geb.runParser f content of
Left err -> exitJuvixError (JuvixError err)
Right gebTerm -> do

View File

@ -62,9 +62,8 @@ loadEntryPoint ep = do
)
let epPath :: Maybe (Path Abs File) = ep ^. entryPointModulePath
whenJust epPath $ \path -> do
let filepath = toFilePath path
liftIO (putStrLn . pack $ "OK loaded " <> filepath)
content <- liftIO (readFile filepath)
liftIO (putStrLn . pack $ "OK loaded " <> toFilePath path)
content <- liftIO (readFile path)
let evalRes =
Geb.runEval $
Geb.RunEvalArgs

View File

@ -10,7 +10,7 @@ import Juvix.Compiler.Nockma.Translation.FromSource qualified as Nockma
runCommand :: forall r. (Members '[EmbedIO, App] r) => NockmaEvalOptions -> Sem r ()
runCommand opts = do
afile <- fromAppPathFile file
parsedTerm <- Nockma.parseTermFile (toFilePath afile)
parsedTerm <- Nockma.parseTermFile afile
case parsedTerm of
Left err -> exitJuvixError (JuvixError err)
Right (TermCell c) -> do

View File

@ -8,7 +8,7 @@ import Juvix.Compiler.Nockma.Translation.FromSource qualified as Nockma
runCommand :: forall r. (Members '[EmbedIO, App] r) => NockmaFormatOptions -> Sem r ()
runCommand opts = do
afile <- fromAppPathFile file
parsedTerm <- Nockma.parseTermFile (toFilePath afile)
parsedTerm <- Nockma.parseTermFile afile
case parsedTerm of
Left err -> exitJuvixError (JuvixError err)
Right t -> putStrLn (ppPrint t)

View File

@ -12,6 +12,7 @@ import Juvix.Compiler.Nockma.Pretty
import Juvix.Compiler.Nockma.Pretty qualified as Nockma
import Juvix.Compiler.Nockma.Translation.FromSource (parseProgramFile, parseReplStatement, parseReplText, parseText)
import Juvix.Parser.Error
import Juvix.Prelude qualified as Prelude
import System.Console.Haskeline
import System.Console.Repline qualified as Repline
import Prelude (read)
@ -21,7 +22,7 @@ type ReplS = State.StateT ReplState IO
data ReplState = ReplState
{ _replStateProgram :: Maybe (Program Natural),
_replStateStack :: Maybe (Term Natural),
_replStateLoadedFile :: Maybe (FilePath)
_replStateLoadedFile :: Maybe (Prelude.Path Abs File)
}
type Repl a = Repline.HaskelineT ReplS a
@ -62,7 +63,7 @@ setStack s = Repline.dontCrash $ do
newStack <- readReplTerm s
State.modify (set replStateStack (Just newStack))
loadFile :: String -> Repl ()
loadFile :: Prelude.Path Abs File -> Repl ()
loadFile s = Repline.dontCrash $ do
State.modify (set replStateLoadedFile (Just s))
prog <- readProgram s
@ -82,7 +83,7 @@ options =
[ ("quit", quit),
("get-stack", printStack),
("set-stack", setStack),
("load", loadFile),
("load", loadFile . Prelude.absFile),
("reload", const reloadFile),
("dir", direction')
]
@ -98,7 +99,7 @@ getStack = State.gets (^. replStateStack)
getProgram :: Repl (Maybe (Program Natural))
getProgram = State.gets (^. replStateProgram)
readProgram :: FilePath -> Repl (Program Natural)
readProgram :: Prelude.Path Abs File -> Repl (Program Natural)
readProgram s = fromMegaParsecError <$> parseProgramFile s
direction' :: String -> Repl ()

View File

@ -10,8 +10,8 @@ import RegInterpreter
runCommand :: forall r. (Members '[EmbedIO, App] r) => RegReadOptions -> Sem r ()
runCommand opts = do
afile :: Path Abs File <- fromAppPathFile file
s <- readFile (toFilePath afile)
case Reg.runParser (toFilePath afile) s of
s <- readFile afile
case Reg.runParser afile s of
Left err ->
exitJuvixError (JuvixError err)
Right tab -> do

View File

@ -8,8 +8,8 @@ import RegInterpreter
runCommand :: forall r. (Members '[Embed IO, App] r) => RegRunOptions -> Sem r ()
runCommand opts = do
afile :: Path Abs File <- fromAppPathFile file
s <- readFile (toFilePath afile)
case Reg.runParser (toFilePath afile) s of
s <- readFile afile
case Reg.runParser afile s of
Left err -> exitJuvixError (JuvixError err)
Right tab -> runReg tab
where

View File

@ -8,8 +8,8 @@ import Juvix.Compiler.Tree.Translation.FromSource qualified as Tree
runCommand :: forall r. (Members '[EmbedIO, App, TaggedLock] r) => CompileOptions -> Sem r ()
runCommand opts = do
file <- getFile
s <- readFile (toFilePath file)
tab <- getRight (mapLeft JuvixError (Tree.runParser (toFilePath file) s))
s <- readFile file
tab <- getRight (mapLeft JuvixError (Tree.runParser file s))
let arg = PipelineArg opts file tab
case opts ^. compileTarget of
TargetWasm32Wasi -> runCPipeline arg

View File

@ -8,8 +8,8 @@ import TreeEvaluator
runCommand :: forall r. (Members '[EmbedIO, App] r) => TreeEvalOptions -> Sem r ()
runCommand opts = do
afile :: Path Abs File <- fromAppPathFile file
s <- readFile (toFilePath afile)
case Tree.runParser (toFilePath afile) s of
s <- readFile afile
case Tree.runParser afile s of
Left err -> exitJuvixError (JuvixError err)
Right tab -> evalTree (opts ^. treeEvalEvaluator) tab
where

View File

@ -11,8 +11,8 @@ import Juvix.Compiler.Tree.Translation.FromAsm qualified as Tree
runCommand :: forall r. (Members '[EmbedIO, App] r) => TreeFromAsmOptions -> Sem r ()
runCommand opts = do
afile :: Path Abs File <- fromAppPathFile file
s <- readFile (toFilePath afile)
case Asm.runParser (toFilePath afile) s of
s <- readFile afile
case Asm.runParser afile s of
Left err -> exitJuvixError (JuvixError err)
Right tab -> do
r :: Either JuvixError Tree.InfoTable <- runError $ mapError (JuvixError @TreeError) $ Tree.fromAsm tab

View File

@ -11,8 +11,8 @@ import TreeEvaluator qualified as Eval
runCommand :: forall r. (Members '[EmbedIO, App] r) => TreeReadOptions -> Sem r ()
runCommand opts = do
afile :: Path Abs File <- fromAppPathFile file
s <- readFile (toFilePath afile)
case Tree.runParser (toFilePath afile) s of
s <- readFile afile
case Tree.runParser afile s of
Left err -> exitJuvixError (JuvixError err)
Right tab -> do
r <- runError @JuvixError (Tree.applyTransformations (project opts ^. treeReadTransformations) tab)

View File

@ -18,7 +18,7 @@ type ReplS = State.StateT ReplState IO
data ReplState = ReplState
{ _replStateBuilderState :: Tree.BuilderState,
_replStateLoadedFile :: Maybe FilePath
_replStateLoadedFile :: Maybe (Path Abs File)
}
type Repl a = Repline.HaskelineT ReplS a
@ -40,7 +40,7 @@ printHelpTxt = liftIO $ putStrLn helpTxt
quit :: String -> Repl ()
quit _ = liftIO (throwIO Interrupt)
loadFile :: String -> Repl ()
loadFile :: Path Abs File -> Repl ()
loadFile s = Repline.dontCrash $ do
State.modify (set replStateLoadedFile (Just s))
readProgram s
@ -52,7 +52,7 @@ reloadFile = Repline.dontCrash $ do
Nothing -> error "no file loaded"
Just f -> readProgram f
readProgram :: FilePath -> Repl ()
readProgram :: Path Abs File -> Repl ()
readProgram f = do
bs <- State.gets (^. replStateBuilderState)
txt <- readFile f
@ -65,7 +65,7 @@ options :: [(String, String -> Repl ())]
options =
[ ("help", Repline.dontCrash . const printHelpTxt),
("quit", quit),
("load", loadFile),
("load", loadFile . absFile),
("reload", const reloadFile)
]
@ -83,8 +83,8 @@ readNode s = do
State.modify (set replStateBuilderState bs')
return n
where
replFile :: FilePath
replFile = "<file>"
replFile :: Path Abs File
replFile = $(mkAbsFile "/<repl>")
evalNode :: Node -> Repl ()
evalNode node = do

View File

@ -99,7 +99,7 @@ csvRules s =
csv :: Path Abs File = suiteCsvFile s
addColorColumn :: IO ()
addColorColumn = do
header :| rows <- nonEmpty' . Text.lines <$> readFile (toFilePath csv)
header :| rows <- nonEmpty' . Text.lines <$> readFile csv
let rows' =
[ showColour (v ^. variantColor) <> "," <> r
| (v, r) <- zipExact (s ^. suiteVariants) rows

View File

@ -31,16 +31,19 @@ parseAsmSig =
_parserSigEmptyExtra = mempty
}
noFile :: Path Abs File
noFile = $(mkAbsFile "/<text>")
parseText :: Text -> Either MegaparsecError InfoTable
parseText = runParser ""
parseText = runParser noFile
parseText' :: BuilderState -> Text -> Either MegaparsecError BuilderState
parseText' bs = runParser' bs ""
parseText' bs = runParser' bs noFile
runParser :: FilePath -> Text -> Either MegaparsecError InfoTable
runParser :: Path Abs File -> Text -> Either MegaparsecError InfoTable
runParser = runParserS parseAsmSig
runParser' :: BuilderState -> FilePath -> Text -> Either MegaparsecError BuilderState
runParser' :: BuilderState -> Path Abs File -> Text -> Either MegaparsecError BuilderState
runParser' = runParserS' parseAsmSig
parseCode ::

View File

@ -9,11 +9,11 @@ import Juvix.Parser.Error
import Text.Megaparsec qualified as P
parseText :: Text -> Either MegaparsecError (LabelInfo, [Instruction])
parseText = runParser ""
parseText = runParser $(mkAbsFile "/<text>")
runParser :: FilePath -> Text -> Either MegaparsecError (LabelInfo, [Instruction])
runParser :: Path Abs File -> Text -> Either MegaparsecError (LabelInfo, [Instruction])
runParser fileName input_ =
case run $ runLabelInfoBuilder $ P.runParserT parseToplevel fileName input_ of
case run . runLabelInfoBuilder $ P.runParserT parseToplevel (toFilePath fileName) input_ of
(_, Left err) -> Left (MegaparsecError err)
(li, Right instrs) -> Right (li, instrs)

View File

@ -8,6 +8,7 @@ import Juvix.Extra.Strings qualified as Str
import Juvix.Parser.Error
import Juvix.Parser.Lexer (onlyInterval, withLoc)
import Juvix.Prelude hiding (Atom, Path, many, some)
import Juvix.Prelude qualified as Prelude
import Juvix.Prelude.Parsing hiding (runParser)
import Text.Megaparsec qualified as P
import Text.Megaparsec.Char.Lexer qualified as L
@ -20,12 +21,12 @@ parseText = runParser noFile
parseReplText :: Text -> Either MegaparsecError (ReplTerm Natural)
parseReplText = runParserFor replTerm noFile
parseTermFile :: (MonadIO m) => FilePath -> m (Either MegaparsecError (Term Natural))
parseTermFile :: (MonadIO m) => Prelude.Path Abs File -> m (Either MegaparsecError (Term Natural))
parseTermFile fp = do
txt <- readFile fp
return (runParser fp txt)
parseProgramFile :: (MonadIO m) => FilePath -> m (Either MegaparsecError (Program Natural))
parseProgramFile :: (MonadIO m) => Prelude.Path Abs File -> m (Either MegaparsecError (Program Natural))
parseProgramFile fp = do
txt <- readFile fp
return (runParserProgram fp txt)
@ -33,18 +34,18 @@ parseProgramFile fp = do
parseReplStatement :: Text -> Either MegaparsecError (ReplStatement Natural)
parseReplStatement = runParserFor replStatement noFile
noFile :: FilePath
noFile = "/<text>"
noFile :: Prelude.Path Abs File
noFile = $(mkAbsFile "/<text>")
runParserProgram :: FilePath -> Text -> Either MegaparsecError (Program Natural)
runParserProgram :: Prelude.Path Abs File -> Text -> Either MegaparsecError (Program Natural)
runParserProgram = runParserFor program
runParserFor :: Parser a -> FilePath -> Text -> Either MegaparsecError a
runParserFor p f input_ = case P.runParser (spaceConsumer >> p <* eof) f input_ of
runParserFor :: Parser a -> Prelude.Path Abs File -> Text -> Either MegaparsecError a
runParserFor p f input_ = case P.runParser (spaceConsumer >> p <* eof) (toFilePath f) input_ of
Left err -> Left (MegaparsecError err)
Right t -> Right t
runParser :: FilePath -> Text -> Either MegaparsecError (Term Natural)
runParser :: Prelude.Path Abs File -> Text -> Either MegaparsecError (Term Natural)
runParser = runParserFor term
spaceConsumer :: Parser ()

View File

@ -30,16 +30,19 @@ parseRegSig =
_parserSigEmptyExtra = ()
}
noFile :: Path Abs File
noFile = $(mkAbsFile "/<text>")
parseText :: Text -> Either MegaparsecError InfoTable
parseText = runParser ""
parseText = runParser noFile
parseText' :: BuilderState -> Text -> Either MegaparsecError BuilderState
parseText' bs = runParser' bs ""
parseText' bs = runParser' bs noFile
runParser :: FilePath -> Text -> Either MegaparsecError InfoTable
runParser :: Path Abs File -> Text -> Either MegaparsecError InfoTable
runParser = runParserS parseRegSig
runParser' :: BuilderState -> FilePath -> Text -> Either MegaparsecError BuilderState
runParser' :: BuilderState -> Path Abs File -> Text -> Either MegaparsecError BuilderState
runParser' = runParserS' parseRegSig
parseCode ::

View File

@ -31,19 +31,22 @@ parseTreeSig =
_parserSigEmptyExtra = ()
}
noFile :: Path Abs File
noFile = $(mkAbsFile "/<text")
parseText :: Text -> Either MegaparsecError InfoTable
parseText = runParser ""
parseText = runParser noFile
parseText' :: BuilderState -> Text -> Either MegaparsecError BuilderState
parseText' bs = runParser' bs ""
parseText' bs = runParser' bs noFile
runParser :: FilePath -> Text -> Either MegaparsecError InfoTable
runParser :: Path Abs File -> Text -> Either MegaparsecError InfoTable
runParser = runParserS parseTreeSig
runParser' :: BuilderState -> FilePath -> Text -> Either MegaparsecError BuilderState
runParser' :: BuilderState -> Path Abs File -> Text -> Either MegaparsecError BuilderState
runParser' = runParserS' parseTreeSig
parseNodeText' :: BuilderState -> FilePath -> Text -> Either MegaparsecError (BuilderState, Node)
parseNodeText' :: BuilderState -> Path Abs File -> Text -> Either MegaparsecError (BuilderState, Node)
parseNodeText' bs file txt = runParserS'' parseNode parseTreeSig bs file txt
parseNode ::

View File

@ -37,10 +37,10 @@ localS update a = do
lift $ put s
return a'
runParserS :: ParserSig t e d -> FilePath -> Text -> Either MegaparsecError (InfoTable' t e)
runParserS :: ParserSig t e d -> Path Abs File -> Text -> Either MegaparsecError (InfoTable' t e)
runParserS sig fileName input_ = (^. stateInfoTable) <$> runParserS' sig emptyBuilderState fileName input_
runParserS' :: forall t e d. ParserSig t e d -> BuilderState' t e -> FilePath -> Text -> Either MegaparsecError (BuilderState' t e)
runParserS' :: forall t e d. ParserSig t e d -> BuilderState' t e -> Path Abs File -> Text -> Either MegaparsecError (BuilderState' t e)
runParserS' sig bs fileName input_ = case runParserS'' (parseToplevel @t @e @d) sig bs fileName input_ of
Left e -> Left e
Right (bs', ()) -> Right bs'
@ -50,15 +50,15 @@ runParserS'' ::
ParsecS '[Reader (ParserSig t e d), InfoTableBuilder' t e, State (LocalParams' d)] a ->
ParserSig t e d ->
BuilderState' t e ->
FilePath ->
Path Abs File ->
Text ->
Either MegaparsecError (BuilderState' t e, a)
runParserS'' parser sig bs fileName input_ =
case run $
evalState emptyLocalParams $
runInfoTableBuilder' bs $
runReader sig $
P.runParserT parser fileName input_ of
case run
. evalState emptyLocalParams
. runInfoTableBuilder' bs
. runReader sig
$ P.runParserT parser (toFilePath fileName) input_ of
(_, Left err) -> Left (MegaparsecError err)
(bs', Right x) -> Right (bs', x)

View File

@ -30,7 +30,7 @@ runFilesIO = interpret helper
helper' :: forall rInitial x. Files (Sem rInitial) x -> IO x
helper' = \case
ReadFile' f -> readFile (toFilePath f)
ReadFile' f -> readFile f
WriteFileBS p bs -> ByteString.writeFile (toFilePath p) bs
WriteFileEnsureLn' f txt -> writeFileEnsureLn f txt
EnsureDir' p -> Path.ensureDir p

View File

@ -606,10 +606,9 @@ ensureLn t =
'\n' -> t
_ -> Text.snoc t '\n'
readFile :: (MonadIO m) => Path Abs File -> m Text
readFile = liftIO . Utf8.readFile . toFilePath
writeFileEnsureLn :: (MonadIO m) => Path Abs File -> Text -> m ()
writeFileEnsureLn p = liftIO . Utf8.writeFile (toFilePath p)
{-# INLINE writeFileEnsureLn #-}
-- TODO: change FilePath to Path Abs File
readFile :: (MonadIO m) => FilePath -> m Text
readFile = liftIO . Utf8.readFile

View File

@ -35,7 +35,7 @@ asmCompileAssertion' optLevel tab mainFile expectedFile stdinText step = do
asmCompileAssertion :: Path Abs File -> Path Abs File -> Text -> (String -> IO ()) -> Assertion
asmCompileAssertion mainFile expectedFile stdinText step = do
step "Parse"
s <- readFile (toFilePath mainFile)
case runParser (toFilePath mainFile) s of
s <- readFile mainFile
case runParser mainFile s of
Left err -> assertFailure (show err)
Right tab -> asmCompileAssertion' 3 tab mainFile expectedFile stdinText step

View File

@ -39,9 +39,9 @@ asmRunAssertionParam' interpretFun tab expectedFile step = do
step "Interpret"
interpretFun hout sym tab
hClose hout
actualOutput <- readFile (toFilePath outputFile)
actualOutput <- readFile outputFile
step "Compare expected and actual program output"
expected <- readFile (toFilePath expectedFile)
expected <- readFile expectedFile
assertEqDiffText ("Check: RUN output = " <> toFilePath expectedFile) actualOutput expected
)
Nothing -> assertFailure "no 'main' function"
@ -90,9 +90,8 @@ asmRunErrorAssertion mainFile step = do
parseFile :: Path Abs File -> IO (Either MegaparsecError InfoTable)
parseFile f = do
let f' = toFilePath f
s <- readFile f'
return $ runParser f' s
s <- readFile f
return (runParser f s)
doRun ::
Handle ->

View File

@ -19,5 +19,5 @@ asmValidateErrorAssertion mainFile step = do
parseFile :: Path Abs File -> IO (Either MegaparsecError InfoTable)
parseFile f = do
s <- readFile (toFilePath f)
return $ runParser (toFilePath f) s
s <- readFile f
return (runParser f s)

View File

@ -11,7 +11,7 @@ gebEvalAssertion ::
Assertion
gebEvalAssertion mainFile expectedFile step = do
step "Parse"
input_ <- readFile (toFilePath mainFile)
input_ <- readFile mainFile
case Geb.runParser mainFile input_ of
Left err -> assertFailure (show (pretty err))
Right (Geb.ExpressionObject _) -> do
@ -51,8 +51,8 @@ gebEvalAssertion' _mainFile expectedFile step gebMorphism = do
Right value -> do
hPutStrLn hout (Geb.ppPrint value)
hClose hout
actualOutput <- readFile (toFilePath outputFile)
expected <- readFile (toFilePath expectedFile)
actualOutput <- readFile outputFile
expected <- readFile expectedFile
step "Compare expected and actual program output"
assertEqDiffText
("Check: EVAL output = " <> toFilePath expectedFile)
@ -62,7 +62,7 @@ gebEvalAssertion' _mainFile expectedFile step gebMorphism = do
gebEvalErrorAssertion :: Path Abs File -> (String -> IO ()) -> Assertion
gebEvalErrorAssertion mainFile step = do
step "Parse"
input_ <- readFile (toFilePath mainFile)
input_ <- readFile mainFile
case Geb.runParser mainFile input_ of
Left _ -> assertBool "" True
Right (Geb.ExpressionObject _) -> assertFailure "no error"

View File

@ -16,7 +16,7 @@ coreToGebTranslationAssertion ::
Assertion
coreToGebTranslationAssertion root mainFile expectedFile step = do
step "Parse Juvix Core file"
input_ <- readFile . toFilePath $ mainFile
input_ <- readFile mainFile
entryPoint <- set entryPointTarget TargetGeb <$> testDefaultEntryPointIO root mainFile
case Core.runParserMain mainFile defaultModuleId mempty input_ of
Left err -> assertFailure . show . pretty $ err
@ -72,8 +72,7 @@ coreToGebTranslationAssertion' coreInfoTable entryPoint expectedFile step = do
| resEvalTranslatedMorph /= resEvalGebCoreEvalResult ->
assertFailure "The evaluation for the Core node and the Geb node are not equal"
| otherwise -> do
let fpath = toFilePath expectedFile
expectedInput <- readFile fpath
expectedInput <- readFile expectedFile
step "Compare expected and actual program output"
let compareEvalOutput morph =
if

View File

@ -55,7 +55,7 @@ testDescr PosTest {..} =
Left err -> assertFailure (show err)
Right md -> do
step "Checking against expected output file"
expFile :: Text <- readFile (toFilePath _expectedFile)
expFile :: Text <- readFile _expectedFile
assertEqDiffText "Compare to expected output" md expFile
}

View File

@ -26,9 +26,9 @@ casmRunAssertion' labi instrs expectedFile step =
hout <- openFile (toFilePath outputFile) WriteMode
hPrint hout value'
hClose hout
actualOutput <- readFile (toFilePath outputFile)
actualOutput <- readFile outputFile
step "Compare expected and actual program output"
expected <- readFile (toFilePath expectedFile)
expected <- readFile expectedFile
assertEqDiffText ("Check: RUN output = " <> toFilePath expectedFile) actualOutput expected
)
@ -59,9 +59,8 @@ casmRunErrorAssertion mainFile step = do
parseFile :: Path Abs File -> IO (Either MegaparsecError (LabelInfo, Code))
parseFile f = do
let f' = toFilePath f
s <- readFile f'
return $ runParser f' s
s <- readFile f
return (runParser f s)
doRun ::
LabelInfo ->

View File

@ -47,7 +47,7 @@ coreAsmAssertion mainFile expectedFile step = do
Left err -> assertFailure (show (pretty err))
Right (_, Nothing) -> do
step "Empty program: compare expected and actual program output"
expected <- readFile (toFilePath expectedFile)
expected <- readFile expectedFile
assertEqDiffText ("Check: EVAL output = " <> toFilePath expectedFile) "" expected
Right (tabIni, Just node) -> do
step "Translate"

View File

@ -72,7 +72,7 @@ coreCompileAssertion mainFile expectedFile stdinText step = do
Left err -> assertFailure (show (pretty err))
Right (_, Nothing) -> do
step "Empty program: compare expected and actual program output"
expected <- readFile (toFilePath expectedFile)
expected <- readFile expectedFile
assertEqDiffText ("Check: EVAL output = " <> toFilePath expectedFile) "" expected
Right (tabIni, Just node) ->
coreCompileAssertion' 3 (setupMainFunction defaultModuleId tabIni node) mainFile expectedFile stdinText step

View File

@ -76,7 +76,7 @@ coreEvalAssertion' mode tab mainFile expectedFile step =
(Info.member kNoDisplayInfo (getInfo value))
(hPutStrLn hout (ppPrint (toValue tab value)))
hClose hout
actualOutput <- readFile (toFilePath outputFile)
actualOutput <- readFile outputFile
step "Compare expected and actual program output"
assertEqDiffText ("Check: EVAL output = " <> toFilePath expectedFile) actualOutput _evalDataOutput
)
@ -101,7 +101,7 @@ coreEvalAssertion' mode tab mainFile expectedFile step =
readEvalData :: [Maybe Text] -> IO (Either String EvalData)
readEvalData argnames = case mode of
EvalModePlain -> do
expected <- readFile (toFilePath expectedFile)
expected <- readFile expectedFile
return $
Right $
EvalData
@ -146,7 +146,7 @@ coreEvalAssertion mainFile expectedFile trans testTrans step = do
Left err -> assertFailure (show (pretty err))
Right (_, Nothing) -> do
step "Compare expected and actual program output"
expected <- readFile (toFilePath expectedFile)
expected <- readFile expectedFile
assertEqDiffText ("Check: EVAL output = " <> toFilePath expectedFile) "" expected
Right (tabIni, Just node) ->
case run $ runReader defaultCoreOptions $ runError $ applyTransformations trans $ moduleFromInfoTable $ setupMainFunction defaultModuleId tabIni node of
@ -179,9 +179,8 @@ coreEvalErrorAssertion mainFile step = do
parseFile :: Path Abs File -> IO (Either MegaparsecError (InfoTable, Maybe Node))
parseFile f = do
let f' = toFilePath f
s <- readFile f'
return $ runParser f defaultModuleId mempty s
s <- readFile f
return (runParser f defaultModuleId mempty s)
doEval' ::
EvalOptions ->

View File

@ -42,7 +42,7 @@ corePrintAssertion mainFile expectedFile step = do
Left err -> assertFailure (show (pretty err))
Right (_, Nothing) -> do
step "Empty program: compare expected and actual program output"
expected <- readFile (toFilePath expectedFile)
expected <- readFile expectedFile
assertEqDiffText ("Check: EVAL output = " <> toFilePath expectedFile) "" expected
Right (tabIni, Just node) -> do
let m = disambiguateNames (moduleFromInfoTable $ setupMainFunction defaultModuleId tabIni node)

View File

@ -33,7 +33,7 @@ testDescr PosTest {..} =
let maybeFile = entryPoint ^. entryPointModulePath
f <- fromMaybeM (assertFailure "Not a module") (return maybeFile)
original :: Text <- readFile (toFilePath f)
original :: Text <- readFile f
step "Parsing & scoping"
PipelineResult {..} <- snd <$> testRunIO entryPoint upToScoping
@ -45,7 +45,7 @@ testDescr PosTest {..} =
assertEqDiffText "check: pretty . scope . parse = id" original formatted
Just eFile -> do
step "Checking against expected output file"
expFile :: Text <- readFile (toFilePath eFile)
expFile :: Text <- readFile eFile
assertEqDiffText "Compare to expected output" formatted expFile
}

View File

@ -35,9 +35,9 @@ internalCoreAssertion root' mainFile expectedFile step = do
(Info.member kNoDisplayInfo (getInfo value))
(hPutStrLn hout (ppPrint value))
hClose hout
actualOutput <- readFile (toFilePath outputFile)
actualOutput <- readFile outputFile
step "Compare expected and actual program output"
expected <- readFile (toFilePath expectedFile)
expected <- readFile expectedFile
assertEqDiffText ("Check: EVAL output = " <> toFilePath expectedFile) actualOutput expected
)
Nothing -> assertFailure ("No main function registered in: " <> toFilePath mainFile)

View File

@ -28,5 +28,5 @@ regParseAssertion mainFile step = do
parseFile :: Path Abs File -> IO (Either MegaparsecError InfoTable)
parseFile f = do
s <- readFile (toFilePath f)
return $ runParser (toFilePath f) s
s <- readFile f
return (runParser f s)

View File

@ -35,9 +35,9 @@ regRunAssertionParam' interpretFun tab expectedFile step = do
step "Interpret"
interpretFun hout sym tab
hClose hout
actualOutput <- readFile (toFilePath outputFile)
actualOutput <- readFile outputFile
step "Compare expected and actual program output"
expected <- readFile (toFilePath expectedFile)
expected <- readFile expectedFile
assertEqDiffText ("Check: RUN output = " <> toFilePath expectedFile) actualOutput expected
)
Nothing -> assertFailure "no 'main' function"
@ -84,9 +84,8 @@ regRunErrorAssertion mainFile step = do
parseFile :: Path Abs File -> IO (Either MegaparsecError InfoTable)
parseFile f = do
let f' = toFilePath f
s <- readFile f'
return $ runParser f' s
s <- readFile f
return (runParser f s)
doRun ::
Handle ->

View File

@ -58,7 +58,7 @@ clangAssertion optLevel inputFile expectedFile stdinText step = do
step "Lookup WASI_SYSROOT_PATH"
sysrootPath :: Path Abs Dir <- getWasiSysrootPath
expected <- readFile (toFilePath expectedFile)
expected <- readFile expectedFile
let executeWasm :: Path Abs File -> IO Text
executeWasm outputFile = readProcess "wasmer" [toFilePath outputFile] stdinText

View File

@ -13,8 +13,8 @@ treeAsmAssertion ::
Assertion
treeAsmAssertion mainFile expectedFile step = do
step "Parse"
s <- readFile (toFilePath mainFile)
case runParser (toFilePath mainFile) s of
s <- readFile mainFile
case runParser mainFile s of
Left err -> assertFailure (show (pretty err))
Right tabIni -> do
step "Translate"

View File

@ -31,8 +31,8 @@ treeEvalAssertionParam ::
Assertion
treeEvalAssertionParam evalParam mainFile expectedFile trans testTrans step = do
step "Parse"
s <- readFile (toFilePath mainFile)
case runParser (toFilePath mainFile) s of
s <- readFile mainFile
case runParser mainFile s of
Left err -> assertFailure (show (pretty err))
Right tab0 -> do
step "Validate"
@ -54,9 +54,9 @@ treeEvalAssertionParam evalParam mainFile expectedFile trans testTrans step = do
step "Evaluate"
evalParam hout sym tab
hClose hout
actualOutput <- readFile (toFilePath outputFile)
actualOutput <- readFile outputFile
step "Compare expected and actual program output"
expected <- readFile (toFilePath expectedFile)
expected <- readFile expectedFile
assertEqDiffText ("Check: RUN output = " <> toFilePath expectedFile) actualOutput expected
)
Nothing -> assertFailure "no 'main' function"
@ -83,8 +83,8 @@ doEval hout tab funInfo = catchEvalErrorIO (hEvalIO stdin hout tab funInfo)
treeEvalErrorAssertion :: Path Abs File -> (String -> IO ()) -> Assertion
treeEvalErrorAssertion mainFile step = do
step "Parse"
s <- readFile (toFilePath mainFile)
case runParser (toFilePath mainFile) s of
s <- readFile mainFile
case runParser mainFile s of
Left err -> assertFailure (show (pretty err))
Right tab ->
case tab ^. infoMainFunction of

View File

@ -11,7 +11,7 @@ data VampirBackend = VampirHalo2 | VampirPlonk
vampirAssertion :: VampirBackend -> Path Abs File -> Path Abs File -> (String -> IO ()) -> Assertion
vampirAssertion backend mainFile dataFile step = do
step "Parse"
s <- readFile (toFilePath mainFile)
s <- readFile mainFile
case runParserMain mainFile defaultModuleId mempty s of
Left err -> assertFailure (show err)
Right tab -> vampirAssertion' backend tab dataFile step