Skip to content

Commit

Permalink
some ability to use JAC_PATH &c.
Browse files Browse the repository at this point in the history
cli args
  • Loading branch information
vmchale committed Jan 26, 2022
1 parent 23af273 commit 3fc6ad9
Show file tree
Hide file tree
Showing 9 changed files with 102 additions and 54 deletions.
35 changes: 23 additions & 12 deletions app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,9 +9,9 @@ import Options.Applicative
import qualified Paths_jacinda as P
import System.IO (stdin)

data Command = TypeCheck !FilePath
| Run !FilePath !(Maybe FilePath)
| Expr !BSL.ByteString !(Maybe FilePath) !(Maybe BS.ByteString)
data Command = TypeCheck !FilePath ![FilePath]
| Run !FilePath !(Maybe FilePath) ![FilePath]
| Expr !BSL.ByteString !(Maybe FilePath) !(Maybe BS.ByteString) ![FilePath]
| Eval !BSL.ByteString

jacFile :: Parser FilePath
Expand Down Expand Up @@ -47,11 +47,22 @@ commandP = hsubparser
<> command "run" (info runP (progDesc "Run from file")))
<|> exprP
where
tcP = TypeCheck <$> jacFile
runP = Run <$> jacFile <*> inpFile
exprP = Expr <$> jacExpr <*> inpFile <*> jacFs
tcP = TypeCheck <$> jacFile <*> includes
runP = Run <$> jacFile <*> inpFile <*> includes
exprP = Expr <$> jacExpr <*> inpFile <*> jacFs <*> includes
eP = Eval <$> jacExpr

includes :: Parser [FilePath]
includes = many $ strOption
(metavar "DIR"
<> long "include"
<> short 'I'
<> dirCompletions)

dirCompletions :: HasCompleter f => Mod f a
dirCompletions = completer . bashCompleter $ "directory"


wrapper :: ParserInfo Command
wrapper = info (helper <*> versionMod <*> commandP)
(fullDesc
Expand All @@ -65,9 +76,9 @@ main :: IO ()
main = run =<< execParser wrapper

run :: Command -> IO ()
run (TypeCheck fp) = tcIO =<< BSL.readFile fp
run (Run fp Nothing) = do { contents <- BSL.readFile fp ; runOnHandle contents Nothing stdin }
run (Run fp (Just dat)) = do { contents <- BSL.readFile fp ; runOnFile contents Nothing dat }
run (Expr eb Nothing fs) = runOnHandle eb fs stdin
run (Expr eb (Just fp) fs) = runOnFile eb fs fp
run (Eval e) = print (exprEval e)
run (TypeCheck fp is) = tcIO is =<< BSL.readFile fp
run (Run fp Nothing is) = do { contents <- BSL.readFile fp ; runOnHandle is contents Nothing stdin }
run (Run fp (Just dat) is) = do { contents <- BSL.readFile fp ; runOnFile is contents Nothing dat }
run (Expr eb Nothing fs is) = runOnHandle is eb fs stdin
run (Expr eb (Just fp) fs is) = runOnFile is eb fs fp
run (Eval e) = print (exprEval e)
2 changes: 1 addition & 1 deletion bench/Bench.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ import Jacinda.File

main :: IO ()
main =
defaultMain [ bgroup "exprEval"
defaultMain [ bgroup "eval"
[ bench "exprEval" $ nf exprEval "[x+' '+y]|'' split '01-23-1987' /-/"
]
]
Expand Down
9 changes: 8 additions & 1 deletion jacinda.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,9 @@ extra-source-files:
man/ja.1
doc/guide.pdf
test/examples/*.jac
examples/*.jac

data-files:
lib/*.jac
prelude/*.jac

Expand Down Expand Up @@ -49,9 +52,11 @@ library jacinda-lib
Jacinda.Backend.Normalize
Jacinda.Backend.TreeWalk
Jacinda.Backend.Printf
Jacinda.Env
Jacinda.Include
Data.List.Ext
Data.Vector.Ext
Paths_jacinda
autogen-modules: Paths_jacinda

default-language: Haskell2010
ghc-options: -Wall -O2
Expand All @@ -66,6 +71,8 @@ library jacinda-lib
transformers,
regex-rure >=0.1.2.0,
microlens,
directory,
filepath,
microlens-mtl,
vector,
recursion >=1.0.0.0,
Expand Down
3 changes: 3 additions & 0 deletions man/MANPAGE.md
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,9 @@ ja - Jacinda: data filtering, processing, reporting
**-V** **-\-version**
: Display version information

**-I** **-\-include**
: Include directory for imports

# LANGUAGE

## REGEX
Expand Down
3 changes: 3 additions & 0 deletions man/ja.1
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,9 @@ Display help
.TP
\f[B]-V\f[R] \f[B]--version\f[R]
Display version information
.TP
\f[B]-I\f[R] \f[B]--include\f[R]
Include directory for imports
.SH LANGUAGE
.SS REGEX
.PP
Expand Down
12 changes: 0 additions & 12 deletions src/Jacinda/Env.hs

This file was deleted.

54 changes: 27 additions & 27 deletions src/Jacinda/File.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
module Jacinda.File ( tyCheck
, tcIO
module Jacinda.File ( tcIO
, tySrc
, runOnHandle
, runOnFile
Expand All @@ -21,6 +20,7 @@ import Data.Tuple (swap)
import Jacinda.AST
import Jacinda.Backend.Normalize
import Jacinda.Backend.TreeWalk
import Jacinda.Include
import Jacinda.Lexer
import Jacinda.Parser
import Jacinda.Parser.Rewrite
Expand All @@ -30,28 +30,28 @@ import Jacinda.Ty
import Regex.Rure (RurePtr)
import System.IO (Handle)

parseLib :: FilePath -> StateT AlexUserState IO [D AlexPosn]
parseLib fp = do
contents <- liftIO $ BSL.readFile fp
parseLib :: [FilePath] -> FilePath -> StateT AlexUserState IO [D AlexPosn]
parseLib incls fp = do
contents <- liftIO $ BSL.readFile =<< resolveImport incls fp
st <- get
case parseLibWithCtx contents st of
Left err -> liftIO (throwIO err)
Right (st', ([], ds)) -> put st' $> (rewriteD <$> ds)
Right (st', (is, ds)) -> do { put st' ; dss <- traverse parseLib is ; pure (concat dss ++ ds) }
Right (st', (is, ds)) -> do { put st' ; dss <- traverse (parseLib incls) is ; pure (concat dss ++ ds) }

parseE :: BSL.ByteString -> StateT AlexUserState IO (Program AlexPosn)
parseE bs = do
parseE :: [FilePath] -> BSL.ByteString -> StateT AlexUserState IO (Program AlexPosn)
parseE incls bs = do
st <- get
case parseWithCtx bs st of
Left err -> liftIO $ throwIO err
Right (st', (is, Program ds e)) -> do
put st'
dss <- traverse parseLib is
dss <- traverse (parseLib incls) is
pure $ Program (concat dss ++ fmap rewriteD ds) (rewriteE e)

-- | Parse + rename (decls)
parseEWithMax :: BSL.ByteString -> IO (Program AlexPosn, Int)
parseEWithMax bsl = uncurry renamePGlobal . swap . second fst3 <$> runStateT (parseE bsl) alexInitUserState
parseEWithMax :: [FilePath] -> BSL.ByteString -> IO (Program AlexPosn, Int)
parseEWithMax incls bsl = uncurry renamePGlobal . swap . second fst3 <$> runStateT (parseE incls bsl) alexInitUserState
where fst3 (x, _, _) = x

-- | Parse + rename (globally)
Expand All @@ -70,39 +70,39 @@ compileFS :: Maybe BS.ByteString -> RurePtr
compileFS (Just bs) = compileDefault bs
compileFS Nothing = defaultRurePtr

runOnBytes :: FilePath
runOnBytes :: [FilePath]
-> FilePath -- ^ Data file name, for @nf@
-> BSL.ByteString -- ^ Program
-> Maybe BS.ByteString -- ^ Field separator
-> BSL.ByteString
-> IO ()
runOnBytes fp src cliFS contents = do
(ast, m) <- parseEWithMax src
runOnBytes incls fp src cliFS contents = do
incls' <- defaultIncludes <*> pure incls
(ast, m) <- parseEWithMax incls' src
(typed, i) <- yeetIO $ runTypeM m (tyProgram ast)
cont <- yeetIO $ runJac (ASCII.pack fp) (compileFS (cliFS <|> getFS ast)) i typed
cont $ fmap BSL.toStrict (ASCIIL.lines contents)
-- see: BSL.split, BSL.splitWith

runOnHandle :: BSL.ByteString -- ^ Program
runOnHandle :: [FilePath]
-> BSL.ByteString -- ^ Program
-> Maybe BS.ByteString -- ^ Field separator
-> Handle
-> IO ()
runOnHandle src cliFS = runOnBytes "(runOnBytes)" src cliFS <=< BSL.hGetContents
runOnHandle is src cliFS = runOnBytes is "(runOnBytes)" src cliFS <=< BSL.hGetContents

runOnFile :: BSL.ByteString
runOnFile :: [FilePath]
-> BSL.ByteString
-> Maybe BS.ByteString
-> FilePath
-> IO ()
runOnFile e fs fp = runOnBytes fp e fs =<< BSL.readFile fp
runOnFile is e fs fp = runOnBytes is fp e fs =<< BSL.readFile fp

tcIO :: BSL.ByteString -> IO ()
tcIO = yeetIO . tyCheck

-- | Typecheck an expression
tyCheck :: BSL.ByteString -> Either (Error AlexPosn) ()
tyCheck src =
case parseWithMax' src of
Right (ast, m) -> void $ runTypeM m (tyProgram ast)
Left err -> throw err
tcIO :: [FilePath] -> BSL.ByteString -> IO ()
tcIO incls src = do
incls' <- defaultIncludes <*> pure incls
(ast, m) <- parseEWithMax incls' src
yeetIO $ void $ runTypeM m (tyProgram ast)

tySrc :: BSL.ByteString -> T K
tySrc src =
Expand Down
36 changes: 36 additions & 0 deletions src/Jacinda/Include.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,36 @@
module Jacinda.Include ( defaultIncludes
, resolveImport
) where

import Control.Exception (Exception, throwIO)
import Control.Monad (filterM)
import Data.List.Split (splitWhen)
import Data.Maybe (listToMaybe)
import Paths_jacinda (getDataDir)
import System.Directory (doesFileExist)
import System.Environment (lookupEnv)
import System.FilePath ((</>))

data ImportError = FileNotFound !FilePath ![FilePath] deriving (Show)

instance Exception ImportError where

defaultIncludes :: IO ([FilePath] -> [FilePath])
defaultIncludes = do
path <- jacPath
d <- getDataDir
pure $ (d:) . (++path)

-- | Parsed @JAC_PATH@
jacPath :: IO [FilePath]
jacPath = maybe [] splitEnv <$> lookupEnv "JAC_PATH"

splitEnv :: String -> [FilePath]
splitEnv = splitWhen (== ':')

resolveImport :: [FilePath] -- ^ Places to look
-> FilePath
-> IO FilePath
resolveImport incl fp =
maybe (throwIO $ FileNotFound fp incl) pure . listToMaybe
=<< (filterM doesFileExist . fmap (</> fp) $ incl)
2 changes: 1 addition & 1 deletion test/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -85,7 +85,7 @@ sumBytesAST =
(IParseCol () 5)

tyFile :: FilePath -> Assertion
tyFile = tcIO <=< BSL.readFile
tyFile = tcIO [] <=< BSL.readFile

tyOfT :: BSL.ByteString -> T K -> Assertion
tyOfT src expected =
Expand Down

0 comments on commit 3fc6ad9

Please sign in to comment.