Compare commits
No commits in common. "feat/easy-imports" and "main" have entirely different histories.
feat/easy-
...
main
@ -1,5 +1,5 @@
|
||||
!import "../lib/Base.tri" !Local
|
||||
!import "../lib/List.tri" !Local
|
||||
!import "../lib/base.tri" !Local
|
||||
!import "../lib/list.tri" !Local
|
||||
|
||||
main = lambdaEqualsTC
|
||||
|
||||
|
@ -1,5 +1,5 @@
|
||||
!import "../lib/Base.tri" Lib
|
||||
!import "../lib/List.tri" !Local
|
||||
!import "../lib/base.tri" Lib
|
||||
!import "../lib/list.tri" !Local
|
||||
|
||||
main = exampleTwo
|
||||
-- Level Order Traversal of a labelled binary tree
|
||||
|
@ -1,4 +1,4 @@
|
||||
!import "../lib/Patterns.tri" !Local
|
||||
!import "../lib/patterns.tri" !Local
|
||||
|
||||
-- We can do conditional pattern matching by providing a list of lists, where
|
||||
-- each sublist contains a boolean expression and a function to return if said
|
||||
|
@ -1,5 +1,5 @@
|
||||
!import "../lib/Base.tri" !Local
|
||||
!import "../lib/List.tri" !Local
|
||||
!import "../lib/base.tri" !Local
|
||||
!import "../lib/list.tri" !Local
|
||||
|
||||
main = size size
|
||||
|
||||
|
@ -1,5 +1,5 @@
|
||||
!import "../lib/Base.tri" !Local
|
||||
!import "../lib/List.tri" !Local
|
||||
!import "../lib/base.tri" !Local
|
||||
!import "../lib/list.tri" !Local
|
||||
|
||||
main = toSource not?
|
||||
-- Thanks to intensionality, we can inspect the structure of a given value
|
||||
|
@ -1,6 +0,0 @@
|
||||
#!/bin/bash
|
||||
set -xe
|
||||
|
||||
mkdir -p $HOME/.local/share/tricu/lib
|
||||
|
||||
cp -r lib/* $HOME/.local/share/tricu/lib/
|
@ -1,4 +1,4 @@
|
||||
!import "Base.tri" !Local
|
||||
!import "base.tri" !Local
|
||||
|
||||
_ = t
|
||||
|
@ -1,5 +1,5 @@
|
||||
!import "Base.tri" !Local
|
||||
!import "List.tri" List
|
||||
!import "base.tri" !Local
|
||||
!import "list.tri" List
|
||||
|
||||
match_ = y (self value patterns :
|
||||
triage
|
@ -5,12 +5,11 @@ import Lexer
|
||||
import Parser
|
||||
import Research
|
||||
|
||||
import Data.List (partition, isSuffixOf)
|
||||
import Data.List (partition)
|
||||
import Data.Maybe (mapMaybe)
|
||||
import Control.Monad (foldM)
|
||||
import System.IO
|
||||
import System.Directory (doesFileExist, getCurrentDirectory, getXdgDirectory, XdgDirectory(..))
|
||||
import System.FilePath ((</>), takeDirectory, isAbsolute, normalise)
|
||||
import System.FilePath (takeDirectory, normalise, (</>))
|
||||
|
||||
import qualified Data.Map as Map
|
||||
import qualified Data.Set as Set
|
||||
@ -32,7 +31,7 @@ processImports seen base currentPath asts =
|
||||
where
|
||||
isImp (SImport _ _) = True
|
||||
isImp _ = False
|
||||
getImportInfo (SImport p n) = Just (p, n, p)
|
||||
getImportInfo (SImport p n) = Just (p, n, makeRelativeTo currentPath p)
|
||||
getImportInfo _ = Nothing
|
||||
|
||||
evaluateFileResult :: FilePath -> IO T
|
||||
@ -82,12 +81,11 @@ preprocessFile' seen base currentPath = do
|
||||
Left err -> errorWithoutStackTrace err
|
||||
Right (nonImports, importPaths) -> do
|
||||
let seen' = Set.insert currentPath seen
|
||||
imported <- concat <$> mapM (processImportPath seen' base currentPath) importPaths
|
||||
imported <- concat <$> mapM (processImportPath seen' base) importPaths
|
||||
pure $ imported ++ nonImports
|
||||
where
|
||||
processImportPath seen base currentFile (path, name, _) = do
|
||||
resolvedPath <- resolveImportPath currentFile path
|
||||
ast <- preprocessFile' seen base resolvedPath
|
||||
processImportPath seen base (path, name, importPath) = do
|
||||
ast <- preprocessFile' seen base importPath
|
||||
pure $ map (nsDefinition (if name == "!Local" then "" else name))
|
||||
$ filter (not . isImp) ast
|
||||
isImp (SImport _ _) = True
|
||||
@ -98,40 +96,6 @@ makeRelativeTo f i =
|
||||
let d = takeDirectory f
|
||||
in normalise $ d </> i
|
||||
|
||||
resolveImportPath :: FilePath -> FilePath -> IO FilePath
|
||||
resolveImportPath currentFile importPath = do
|
||||
let pathWithExt = if ".tri" `isSuffixOf` importPath
|
||||
then importPath
|
||||
else importPath ++ ".tri"
|
||||
|
||||
let relativeToFile = makeRelativeTo currentFile pathWithExt
|
||||
fileRelExists <- doesFileExist relativeToFile
|
||||
if fileRelExists
|
||||
then return relativeToFile
|
||||
else if isAbsolute pathWithExt then do
|
||||
exists <- doesFileExist pathWithExt
|
||||
if exists
|
||||
then return pathWithExt
|
||||
else errorWithoutStackTrace $ "File not found: " ++ pathWithExt
|
||||
else do
|
||||
currentDir <- getCurrentDirectory
|
||||
let currentPath = currentDir </> pathWithExt
|
||||
|
||||
currentExists <- doesFileExist currentPath
|
||||
if currentExists
|
||||
then return currentPath
|
||||
else do
|
||||
dataDir <- getXdgDirectory XdgData "tricu"
|
||||
let libPath = dataDir </> "lib" </> pathWithExt
|
||||
|
||||
libExists <- doesFileExist libPath
|
||||
if libExists
|
||||
then return libPath
|
||||
else errorWithoutStackTrace $ "File not found: " ++ pathWithExt ++
|
||||
"\nSearched in:\n- " ++ relativeToFile ++
|
||||
"\n- " ++ currentPath ++
|
||||
"\n- " ++ libPath
|
||||
|
||||
nsDefinitions :: String -> [TricuAST] -> [TricuAST]
|
||||
nsDefinitions moduleName = map (nsDefinition moduleName)
|
||||
|
||||
|
12
src/REPL.hs
12
src/REPL.hs
@ -18,8 +18,6 @@ import Data.List (dropWhile, dropWhileEnd, isPrefixOf)
|
||||
import Data.Version (showVersion)
|
||||
import Paths_tricu (version)
|
||||
import System.Console.Haskeline
|
||||
import System.Directory (doesFileExist, getCurrentDirectory, getXdgDirectory, XdgDirectory(..))
|
||||
import System.FilePath ((</>), takeDirectory, isAbsolute)
|
||||
|
||||
import qualified Data.Map as Map
|
||||
import qualified Data.Text as T
|
||||
@ -109,16 +107,12 @@ repl env = runInputT settings (withInterrupt (loop env Decode))
|
||||
res <- runMaybeT $ do
|
||||
let fset = setComplete completeFilename defaultSettings
|
||||
path <- MaybeT $ runInputT fset $
|
||||
getInputLineWithInitial "Module name or path to import < " ("", "")
|
||||
|
||||
currentDir <- liftIO getCurrentDirectory
|
||||
let currentFile = currentDir </> "dummy.tri"
|
||||
resolvedPath <- liftIO $ resolveImportPath currentFile (strip path)
|
||||
getInputLineWithInitial "File path to load < " ("", "")
|
||||
|
||||
text <- MaybeT $ liftIO $ handle (\e -> do
|
||||
putStrLn $ "Error reading file: " ++ displayException (e :: IOException)
|
||||
return Nothing
|
||||
) $ Just <$> readFile resolvedPath
|
||||
) $ Just <$> readFile (strip path)
|
||||
|
||||
case parseProgram (lexTricu text) of
|
||||
Left err -> do
|
||||
@ -133,7 +127,7 @@ repl env = runInputT settings (withInterrupt (loop env Decode))
|
||||
lift $ outputStrLn "Namespace must start with an uppercase letter"
|
||||
MaybeT $ return Nothing
|
||||
else do
|
||||
prog <- liftIO $ preprocessFile resolvedPath
|
||||
prog <- liftIO $ preprocessFile (strip path)
|
||||
let code = case name of
|
||||
"!Local" -> prog
|
||||
_ -> nsDefinitions name prog
|
||||
|
36
test/Spec.hs
36
test/Spec.hs
@ -366,98 +366,98 @@ lambdas = testGroup "Lambda Evaluation Tests"
|
||||
providedLibraries :: TestTree
|
||||
providedLibraries = testGroup "Library Tests"
|
||||
[ testCase "Triage test Leaf" $ do
|
||||
library <- evaluateFile "./lib/List.tri"
|
||||
library <- evaluateFile "./lib/list.tri"
|
||||
let input = "test t"
|
||||
env = decodeResult $ result $ evalTricu library (parseTricu input)
|
||||
env @?= "\"Leaf\""
|
||||
|
||||
, testCase "Triage test (Stem Leaf)" $ do
|
||||
library <- evaluateFile "./lib/List.tri"
|
||||
library <- evaluateFile "./lib/list.tri"
|
||||
let input = "test (t t)"
|
||||
env = decodeResult $ result $ evalTricu library (parseTricu input)
|
||||
env @?= "\"Stem\""
|
||||
|
||||
, testCase "Triage test (Fork Leaf Leaf)" $ do
|
||||
library <- evaluateFile "./lib/List.tri"
|
||||
library <- evaluateFile "./lib/list.tri"
|
||||
let input = "test (t t t)"
|
||||
env = decodeResult $ result $ evalTricu library (parseTricu input)
|
||||
env @?= "\"Fork\""
|
||||
|
||||
, testCase "Boolean NOT: true" $ do
|
||||
library <- evaluateFile "./lib/List.tri"
|
||||
library <- evaluateFile "./lib/list.tri"
|
||||
let input = "not? true"
|
||||
env = result $ evalTricu library (parseTricu input)
|
||||
env @?= Leaf
|
||||
|
||||
, testCase "Boolean NOT: false" $ do
|
||||
library <- evaluateFile "./lib/List.tri"
|
||||
library <- evaluateFile "./lib/list.tri"
|
||||
let input = "not? false"
|
||||
env = result $ evalTricu library (parseTricu input)
|
||||
env @?= Stem Leaf
|
||||
|
||||
|
||||
, testCase "Boolean AND TF" $ do
|
||||
library <- evaluateFile "./lib/List.tri"
|
||||
library <- evaluateFile "./lib/list.tri"
|
||||
let input = "and? (t t) (t)"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Leaf
|
||||
|
||||
, testCase "Boolean AND FT" $ do
|
||||
library <- evaluateFile "./lib/List.tri"
|
||||
library <- evaluateFile "./lib/list.tri"
|
||||
let input = "and? (t) (t t)"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Leaf
|
||||
|
||||
, testCase "Boolean AND FF" $ do
|
||||
library <- evaluateFile "./lib/List.tri"
|
||||
library <- evaluateFile "./lib/list.tri"
|
||||
let input = "and? (t) (t)"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Leaf
|
||||
|
||||
, testCase "Boolean AND TT" $ do
|
||||
library <- evaluateFile "./lib/List.tri"
|
||||
library <- evaluateFile "./lib/list.tri"
|
||||
let input = "and? (t t) (t t)"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Stem Leaf
|
||||
|
||||
, testCase "List head" $ do
|
||||
library <- evaluateFile "./lib/List.tri"
|
||||
library <- evaluateFile "./lib/list.tri"
|
||||
let input = "head [(t) (t t) (t t t)]"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Leaf
|
||||
|
||||
, testCase "List tail" $ do
|
||||
library <- evaluateFile "./lib/List.tri"
|
||||
library <- evaluateFile "./lib/list.tri"
|
||||
let input = "head (tail (tail [(t) (t t) (t t t)]))"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Fork Leaf Leaf
|
||||
|
||||
, testCase "List map" $ do
|
||||
library <- evaluateFile "./lib/List.tri"
|
||||
library <- evaluateFile "./lib/list.tri"
|
||||
let input = "head (tail (map (a : (t t t)) [(t) (t) (t)]))"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Fork Leaf Leaf
|
||||
|
||||
, testCase "Empty list check" $ do
|
||||
library <- evaluateFile "./lib/List.tri"
|
||||
library <- evaluateFile "./lib/list.tri"
|
||||
let input = "emptyList? []"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Stem Leaf
|
||||
|
||||
, testCase "Non-empty list check" $ do
|
||||
library <- evaluateFile "./lib/List.tri"
|
||||
library <- evaluateFile "./lib/list.tri"
|
||||
let input = "not? (emptyList? [(1) (2) (3)])"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Stem Leaf
|
||||
|
||||
, testCase "Concatenate strings" $ do
|
||||
library <- evaluateFile "./lib/List.tri"
|
||||
library <- evaluateFile "./lib/list.tri"
|
||||
let input = "append \"Hello, \" \"world!\""
|
||||
env = decodeResult $ result $ evalTricu library (parseTricu input)
|
||||
env @?= "\"Hello, world!\""
|
||||
|
||||
, testCase "Verifying Equality" $ do
|
||||
library <- evaluateFile "./lib/List.tri"
|
||||
library <- evaluateFile "./lib/list.tri"
|
||||
let input = "equal? (t t t) (t t t)"
|
||||
env = evalTricu library (parseTricu input)
|
||||
result env @?= Stem Leaf
|
||||
@ -474,12 +474,12 @@ fileEval = testGroup "File evaluation tests"
|
||||
res @?= Fork (Stem Leaf) Leaf
|
||||
|
||||
, testCase "Mapping and Equality" $ do
|
||||
library <- liftIO $ evaluateFile "./lib/List.tri"
|
||||
library <- liftIO $ evaluateFile "./lib/list.tri"
|
||||
fEnv <- liftIO $ evaluateFileWithContext library "./test/map.tri"
|
||||
(mainResult fEnv) @?= Stem Leaf
|
||||
|
||||
, testCase "Eval and decoding string" $ do
|
||||
library <- liftIO $ evaluateFile "./lib/List.tri"
|
||||
library <- liftIO $ evaluateFile "./lib/list.tri"
|
||||
res <- liftIO $ evaluateFileWithContext library "./test/string.tri"
|
||||
decodeResult (result res) @?= "\"String test!\""
|
||||
]
|
||||
|
@ -1,4 +1,5 @@
|
||||
!import "lib/Base.tri"
|
||||
|
||||
!import "lib/base.tri"
|
||||
|
||||
!import "test/named-imports/2.tri"
|
||||
!import "test/named-imports/3.tri" ThreeRenamed
|
||||
|
@ -26,7 +26,6 @@ executable tricu
|
||||
base >=4.7
|
||||
, cmdargs
|
||||
, containers
|
||||
, directory
|
||||
, exceptions
|
||||
, filepath
|
||||
, haskeline
|
||||
@ -56,7 +55,6 @@ test-suite tricu-tests
|
||||
base
|
||||
, cmdargs
|
||||
, containers
|
||||
, directory
|
||||
, exceptions
|
||||
, filepath
|
||||
, haskeline
|
||||
|
Loading…
x
Reference in New Issue
Block a user