load a prelude

This commit is contained in:
Mirek Kratochvil 2023-03-04 13:51:22 +01:00
parent 1521c628a0
commit b417117130
3 changed files with 27 additions and 9 deletions

View file

@ -1,5 +1,7 @@
module Builtins where
import Paths_prlg
import Code (Builtin(..), Code, Datum(..), Instr(..), InterpFn)
import CodeLens
import qualified Compiler as Co
@ -329,6 +331,17 @@ addBi b n a =
addProc [[U (LocalRef $ r - 1) | r <- [1 .. a]] ++ [Invoke $ bi b]] n a
{- loading code -}
doLoad :: Bool -> String -> InterpFn
doLoad queryMode fn = do
src' <- liftIO $ catch (Right <$> readFile fn) (pure . Left)
case src' of
Right src -> do
res <- runExceptT $ processInput fn queryMode src
case res of
Right _ -> continue
Left e -> prlgError $ "loading from '" ++ fn ++ "': " ++ e
Left e -> prlgError $ show (e :: IOException)
load :: Bool -> InterpFn
load queryMode =
withArgs [0] $ \[arg] -> do
@ -337,14 +350,7 @@ load queryMode =
case derefHeap heap arg of
BoundRef _ (Atom a) -> do
let fn = itos M.! a
src' <- liftIO $ catch (Right <$> readFile fn) (pure . Left)
case src' of
Right src -> do
res <- runExceptT $ processInput fn queryMode src
case res of
Right _ -> continue
Left e -> prlgError $ "loading from '" ++ fn ++ "': " ++ e
Left e -> prlgError $ show (e :: IOException)
doLoad queryMode (itos M.! a)
_ -> prlgError "load needs an atom"
{- actual prlgude -}
@ -426,3 +432,7 @@ addPrelude = do
addBi nl "nl" 0
{- debug -}
addBi (use id >>= liftIO . print >> pure Nothing) "interpreter_trace" 0
{- load the prelude file -}
preludeFile <- liftIO $ getDataFileName "prelude.pl"
doLoad False preludeFile
pure ()

5
inst/prelude.pl Normal file
View file

@ -0,0 +1,5 @@
member(X, [X|_]).
member(X, [_|T]) :- member(X,T).
append([], X, X).
append([X|T], Y, [X|TY]) :- append(T,Y,TY).

View file

@ -21,11 +21,14 @@ maintainer: exa.exa@gmail.com
-- category:
extra-source-files: CHANGELOG.md
data-dir: inst
data-files: *.pl
executable prlg
main-is: Main.hs
-- Modules included in this executable, other than Main.
other-modules: Interpreter, Compiler, Parser, Frontend, IR, Operators, Code, Builtins, Env, Load, CodeLens, Heap
other-modules: Interpreter, Compiler, Parser, Frontend, IR, Operators, Code, Builtins, Env, Load, CodeLens, Heap, Paths_prlg
-- LANGUAGE extensions used by modules in this package.
-- other-extensions: