Smarter decoding of terms

This update includes an update to `decodeResult` that makes string
decoding far less aggressive. This also replaces the `!decode` REPL
command with `!output` to allow users to switch output format on the
fly. New tests are included for verifying decoding behavior; this group
needs to be fleshed out further.
This commit is contained in:
James Eversole 2025-02-07 15:04:13 -06:00
parent 871245b567
commit e6e18239a7
4 changed files with 92 additions and 32 deletions

View File

@ -20,7 +20,7 @@ import System.Console.Haskeline
import qualified Data.Map as Map import qualified Data.Map as Map
repl :: Env -> IO () repl :: Env -> IO ()
repl env = runInputT settings (withInterrupt (loop env True)) repl env = runInputT settings (withInterrupt (loop env Decode))
where where
settings :: Settings IO settings :: Settings IO
settings = Settings settings = Settings
@ -33,19 +33,17 @@ repl env = runInputT settings (withInterrupt (loop env True))
completeCommands str = return $ map simpleCompletion $ completeCommands str = return $ map simpleCompletion $
filter (str `isPrefixOf`) commands filter (str `isPrefixOf`) commands
where where
commands = ["!exit", "!decode", "!definitions", "!import"] commands = ["!exit", "!output", "!definitions", "!import"]
loop :: Env -> Bool -> InputT IO () loop :: Env -> EvaluatedForm -> InputT IO ()
loop env decode = handle (interruptHandler env decode) $ do loop env form = handle (interruptHandler env form) $ do
minput <- getInputLine "tricu < " minput <- getInputLine "tricu < "
case minput of case minput of
Nothing -> outputStrLn "Exiting tricu" Nothing -> outputStrLn "Exiting tricu"
Just s Just s
| strip s == "" -> loop env decode | strip s == "" -> loop env form
| strip s == "!exit" -> outputStrLn "Exiting tricu" | strip s == "!exit" -> outputStrLn "Exiting tricu"
| strip s == "!decode" -> do | strip s == "!output" -> handleOutput env form
outputStrLn $ "Decoding " ++ (if decode then "disabled" else "enabled")
loop env (not decode)
| strip s == "!definitions" -> do | strip s == "!definitions" -> do
let defs = Map.keys $ Map.delete "!result" env let defs = Map.keys $ Map.delete "!result" env
if null defs if null defs
@ -53,15 +51,37 @@ repl env = runInputT settings (withInterrupt (loop env True))
else do else do
outputStrLn "Available definitions:" outputStrLn "Available definitions:"
mapM_ outputStrLn defs mapM_ outputStrLn defs
loop env decode loop env form
| "!import" `isPrefixOf` strip s -> handleImport env decode | "!import" `isPrefixOf` strip s -> handleImport env form
| take 2 s == "--" -> loop env decode | take 2 s == "--" -> loop env form
| otherwise -> do | otherwise -> do
newEnv <- liftIO $ processInput env s decode `catch` errorHandler env newEnv <- liftIO $ processInput env s form `catch` errorHandler env
loop newEnv decode loop newEnv form
handleImport :: Env -> Bool -> InputT IO () handleOutput :: Env -> EvaluatedForm -> InputT IO ()
handleImport env decode = do handleOutput env currentForm = do
let formats = [Decode, TreeCalculus, FSL, AST, Ternary, Ascii]
outputStrLn "Available output formats:"
mapM_ (\(i, f) -> outputStrLn $ show i ++ ". " ++ show f)
(zip [1..] formats)
result <- runMaybeT $ do
input <- MaybeT $ getInputLine "Select output format (1-6) < "
case reads input of
[(n, "")] | n >= 1 && n <= 6 ->
return $ formats !! (n-1)
_ -> MaybeT $ return Nothing
case result of
Nothing -> do
outputStrLn "Invalid selection. Keeping current output format."
loop env currentForm
Just newForm -> do
outputStrLn $ "Output format changed to: " ++ show newForm
loop env newForm
handleImport :: Env -> EvaluatedForm -> InputT IO ()
handleImport env form = do
result <- runMaybeT $ do result <- runMaybeT $ do
let fileSettings = setComplete completeFilename defaultSettings let fileSettings = setComplete completeFilename defaultSettings
path <- MaybeT $ runInputT fileSettings $ path <- MaybeT $ runInputT fileSettings $
@ -84,26 +104,23 @@ repl env = runInputT settings (withInterrupt (loop env True))
if | Nothing <- result -> do if | Nothing <- result -> do
outputStrLn "Import cancelled." outputStrLn "Import cancelled."
loop env decode loop env form
| Just loadedEnv <- result -> | Just loadedEnv <- result ->
loop (Map.delete "!result" loadedEnv) decode loop (Map.delete "!result" loadedEnv) form
interruptHandler :: Env -> Bool -> Interrupt -> InputT IO () interruptHandler :: Env -> EvaluatedForm -> Interrupt -> InputT IO ()
interruptHandler env decode _ = do interruptHandler env form _ = do
outputStrLn "Interrupted with CTRL+C\n\ outputStrLn "Interrupted with CTRL+C\n\
\You can use the !exit command or CTRL+D to exit" \You can use the !exit command or CTRL+D to exit"
loop env decode loop env form
processInput :: Env -> String -> Bool -> IO Env processInput :: Env -> String -> EvaluatedForm -> IO Env
processInput env input decode = do processInput env input form = do
let asts = parseTricu input let asts = parseTricu input
newEnv = evalTricu env asts newEnv = evalTricu env asts
case Map.lookup "!result" newEnv of case Map.lookup "!result" newEnv of
Just r -> do Just r -> do
putStrLn $ "tricu > " ++ putStrLn $ "tricu > " ++ formatResult form r
if decode
then decodeResult r
else show r
Nothing -> pure () Nothing -> pure ()
return newEnv return newEnv

View File

@ -160,8 +160,18 @@ toAscii tree = go tree "" True
++ go right (prefix ++ (if isLast then " " else "| ")) True ++ go right (prefix ++ (if isLast then " " else "| ")) True
decodeResult :: T -> String decodeResult :: T -> String
decodeResult tc decodeResult Leaf = "t"
| Right num <- toNumber tc = show num decodeResult tc =
| Right str <- toString tc = "\"" ++ str ++ "\"" case (toString tc, toList tc, toNumber tc) of
| Right list <- toList tc = "[" ++ intercalate ", " (map decodeResult list) ++ "]" (Right s, _, _) | all isCommonChar s -> "\"" ++ s ++ "\""
| otherwise = formatResult TreeCalculus tc (_, _, Right n) -> show n
(_, Right xs@(_:_), _) -> "[" ++ intercalate ", " (map decodeResult xs) ++ "]"
(_, Right [], _) -> "[]"
_ -> formatResult TreeCalculus tc
where
isCommonChar c =
let n = fromEnum c
in (n >= 32 && n <= 126)
|| n == 9
|| n == 10
|| n == 13

View File

@ -34,6 +34,7 @@ tests = testGroup "Tricu Tests"
, fileEval , fileEval
, modules , modules
, demos , demos
, decoding
] ]
lexer :: TestTree lexer :: TestTree
@ -522,3 +523,35 @@ demos = testGroup "Test provided demo functionality"
res <- liftIO $ evaluateFileResult "./demos/levelOrderTraversal.tri" res <- liftIO $ evaluateFileResult "./demos/levelOrderTraversal.tri"
decodeResult res @?= "\"\n1 \n2 3 \n4 5 6 7 \n8 11 10 9 12 \"" decodeResult res @?= "\"\n1 \n2 3 \n4 5 6 7 \n8 11 10 9 12 \""
] ]
decoding :: TestTree
decoding = testGroup "Decoding Tests"
[ testCase "Decode Leaf" $ do
decodeResult Leaf @?= "t"
, testCase "Decode list of non-ASCII numbers" $ do
let input = ofList [ofNumber 1, ofNumber 14, ofNumber 6]
decodeResult input @?= "[1, 14, 6]"
, testCase "Decode list of ASCII numbers as a string" $ do
let input = ofList [ofNumber 97, ofNumber 98, ofNumber 99]
decodeResult input @?= "\"abc\""
, testCase "Decode small number" $ do
decodeResult (ofNumber 42) @?= "42"
, testCase "Decode large number" $ do
decodeResult (ofNumber 9999) @?= "9999"
, testCase "Decode string in list" $ do
let input = ofList [ofString "hello", ofString "world"]
decodeResult input @?= "[\"hello\", \"world\"]"
, testCase "Decode mixed list with strings" $ do
let input = ofList [ofString "hello", ofNumber 42, ofString "world"]
decodeResult input @?= "[\"hello\", 42, \"world\"]"
, testCase "Decode nested lists with strings" $ do
let input = ofList [ofList [ofString "nested"], ofString "string"]
decodeResult input @?= "[[\"nested\"], \"string\"]"
]

View File

@ -1,7 +1,7 @@
cabal-version: 1.12 cabal-version: 1.12
name: tricu name: tricu
version: 0.16.0 version: 0.17.0
description: A micro-language for exploring Tree Calculus description: A micro-language for exploring Tree Calculus
author: James Eversole author: James Eversole
maintainer: james@eversole.co maintainer: james@eversole.co