diff options
author | Marvin Borner | 2022-08-12 18:43:27 +0200 |
---|---|---|
committer | Marvin Borner | 2022-08-12 19:47:47 +0200 |
commit | cbc9a382e356951896a21f80f52e0e5b3e8c4e1f (patch) | |
tree | 4ba22cea48d2ac36a8ab8c12557007431602a6ab | |
parent | cce495b3b4440997274ecab3d72ed61d6a50b007 (diff) |
Added prefix support
Needs some work regarding namespaces
-rw-r--r-- | README.md | 26 | ||||
-rw-r--r-- | editors/vim/syntax/bruijn.vim | 2 | ||||
-rw-r--r-- | src/Eval.hs | 6 | ||||
-rw-r--r-- | src/Helper.hs | 5 | ||||
-rw-r--r-- | src/Parser.hs | 24 | ||||
-rw-r--r-- | std/List.bruijn | 82 | ||||
-rw-r--r-- | std/Logic.bruijn | 50 | ||||
-rw-r--r-- | std/Number.bruijn | 254 |
8 files changed, 258 insertions, 191 deletions
@@ -88,8 +88,9 @@ mandatory. ### Numerals Numbers in bruijn always have a sign in front of them or else they will -be mistaken for De Bruijn indices. Generally the decimal representation -is only syntactic sugar for its internal balanced ternary +be mistaken for De Bruijn indices. They also need to be between +parenthesis because of prefix functions. Generally the decimal +representation is only syntactic sugar for its internal balanced ternary representation. We use balanced ternary because it’s a great compromise between performance and size (according to [\[1\]](#References)). @@ -118,11 +119,11 @@ Plain execution without any predefined functions: # this is a comment # we now define a function returning a ternary 1 - get-one +1 + get-one (+1) # we can use the function in all functions below its definition get-one2 get-one - :test (get-one2) (+1) + :test (get-one2 =? (+1)) (T) # equivalent of λx.x id [0] @@ -132,9 +133,10 @@ Plain execution without any predefined functions: # multiple arguments set-of-three [[[[0 1 2 3]]]] - number-set set-of-three +1 +2 +3 + number-set set-of-three (+1) (+2) (+3) access-first [0 [[[0]]]] - :test (access-first number-set) (+1) + + :test ((access-first number-set) =? (+1)) (T) # endless loop using omega combinator om [0 0] @@ -161,18 +163,20 @@ Using standard library: :test (snd love) (you) # options - :test (map inc (some +1)) (some +2) - :test (apply (some +1) [some (inc 0)]) (some +2) + :test (map inc (some (+1))) (some (+2)) + :test (apply (some (+1)) [some (inc 0)]) (some (+2)) # numerical operations - five dec (sub (add +8 -4) -2) - not-five? [if (eq? 0 +5) F T] + five --(((+8) + (-4)) - (-2)) + not-five? [if (0 =? (+5)) F T] + :test (not-five? five) (F) - :test (eq? (uncurry mul (pair +3 +2))) (+6) + :test ((uncurry mul (pair (+3) (+2))) =? (+6)) (T) # boolean main not (or (and F T) T) + :test (main) (F) # read the files in std/ for an overview of all functions/libraries diff --git a/editors/vim/syntax/bruijn.vim b/editors/vim/syntax/bruijn.vim index 8bd194c..5ea9017 100644 --- a/editors/vim/syntax/bruijn.vim +++ b/editors/vim/syntax/bruijn.vim @@ -8,7 +8,7 @@ endif syn match bruijnApplication /[()]/ syn match bruijnAbstraction /[[\]]/ syn match bruijnIndex /\([^0-9]\)\@<=\d\([^0-9]\)\@=/ -syn match bruijnNumber /[+-]\d\+/ +syn match bruijnNumber /([+-]\d\+)/ syn match bruijnDefinition /^\t*\S\+/ syn match bruijnKeyword /:test\|:import\|:print/ syn match bruijnNamespace /[A-Z][a-z]*\(\.\)\@=/ diff --git a/src/Eval.hs b/src/Eval.hs index 6b165b2..445e41d 100644 --- a/src/Eval.hs +++ b/src/Eval.hs @@ -67,7 +67,10 @@ evalApp f g sub = ) evalInfix :: Expression -> String -> Expression -> Environment -> Program (Failable Expression) -evalInfix le i re = evalExp $ Application (Application (Variable i) le) re +evalInfix le i re = evalExp $ Application (Application (Variable $ "(" ++ i ++ ")") le) re + +evalPrefix :: String -> Expression -> Environment -> Program (Failable Expression) +evalPrefix p e = evalExp $ Application (Variable $ p ++ "(") e evalExp :: Expression -> Environment -> Program (Failable Expression) evalExp idx@(Bruijn _ ) = const $ pure $ Right idx @@ -75,6 +78,7 @@ evalExp ( Variable var) = evalVar var evalExp ( Abstraction e) = evalAbs e evalExp ( Application f g) = evalApp f g evalExp (Infix le i re) = evalInfix le i re +evalExp (Prefix p e) = evalPrefix p e evalDefine :: String -> Expression -> Environment -> Program (Failable Expression) diff --git a/src/Helper.hs b/src/Helper.hs index 66fe265..eb41673 100644 --- a/src/Helper.hs +++ b/src/Helper.hs @@ -89,7 +89,7 @@ printBundle ParseErrorBundle {..} = <> pointer <> "\n" -data Expression = Bruijn Int | Variable String | Abstraction Expression | Application Expression Expression | Infix Expression String Expression +data Expression = Bruijn Int | Variable String | Abstraction Expression | Application Expression Expression | Infix Expression String Expression | Prefix String Expression deriving (Ord, Eq) data Instruction = Define String Expression [Instruction] | Evaluate Expression | Comment | Import String String | Test Expression Expression | ContextualInstruction Instruction String deriving (Show) @@ -100,7 +100,8 @@ instance Show Expression where show (Application exp1 exp2) = "\ESC[33m(\ESC[0m" <> show exp1 <> " " <> show exp2 <> "\ESC[33m)\ESC[0m" show (Infix le i re) = - show le <> "\ESC[95m(" <> i <> ")" <> "\ESC[0m" <> show re + show le <> " \ESC[95m(" <> i <> ")" <> "\ESC[0m " <> show re + show (Prefix p e) = "\ESC[95m" <> p <> show e <> "\ESC[0m" type EnvDef = (String, Expression) -- TODO: Add EvalConf to EnvState? diff --git a/src/Parser.hs b/src/Parser.hs index ddf09fb..44bae87 100644 --- a/src/Parser.hs +++ b/src/Parser.hs @@ -18,13 +18,18 @@ sc :: Parser () sc = void $ char ' ' infixOperator :: Parser String -infixOperator = some $ oneOf "!?*@+$%^&<>/|=" +infixOperator = some $ oneOf "!?*@:+-#$%^&<>/|~=" + +prefixOperator :: Parser String +prefixOperator = some $ oneOf "!?*@:+-#$%^&<>/|~=" -- def identifier disallows the import prefix dots defIdentifier :: Parser String defIdentifier = ((:) <$> (letterChar <|> char '_') <*> many (alphaNumChar <|> oneOf "?!'_-")) - <|> parens infixOperator + <|> ((\l i r -> [l] ++ i ++ [r]) <$> char '(' <*> infixOperator <*> char ')' + ) + <|> ((\p i -> p ++ [i]) <$> prefixOperator <*> char '(') <?> "defining identifier" -- TODO: write as extension to defIdentifier @@ -53,7 +58,7 @@ parseAbstraction = do -- one or more singletons wrapped in coupled application parseApplication :: Parser Expression parseApplication = do - s <- sepEndBy1 parseSingleton sc + s <- sepEndBy1 (try parsePrefix <|> parseSingleton) sc pure $ foldl1 Application s parseBruijn :: Parser Expression @@ -63,7 +68,7 @@ parseBruijn = do parseNumeral :: Parser Expression parseNumeral = do - num <- number <?> "signed number" + num <- parens number <?> "signed number" pure $ decimalToTernary num where sign :: Parser (Integer -> Integer) @@ -104,6 +109,12 @@ parseInfix = do e2 <- parseSingleton pure $ Infix e1 i e2 +parsePrefix :: Parser Expression +parsePrefix = do + p <- prefixOperator + e <- parseSingleton + pure $ Prefix p e + parseSingleton :: Parser Expression parseSingleton = parseBruijn @@ -114,10 +125,11 @@ parseSingleton = <|> try (parens parseInfix <?> "enclosed infix expr") <|> (parens parseApplication <?> "enclosed application") <|> parseVariable + <|> parsePrefix parseExpression :: Parser Expression parseExpression = do - e <- try parseInfix <|> parseApplication + e <- try parseInfix <|> try parseApplication <|> parsePrefix pure e <?> "expression" parseEvaluate :: Parser Instruction @@ -199,6 +211,6 @@ parseBlock lvl = try parseCommentBlock <|> parseDefBlock lvl parseReplLine :: Parser Instruction parseReplLine = try parseReplDefine - <|> try parseEvaluate <|> try parseImport <|> try parseTest + <|> try parseEvaluate diff --git a/std/List.bruijn b/std/List.bruijn index 8f5f478..6cabfd1 100644 --- a/std/List.bruijn +++ b/std/List.bruijn @@ -15,113 +15,123 @@ empty F empty? [0 [[[F]]] T] :test (empty? empty) (T) -:test (empty? (cons +2 empty)) (F) +:test (empty? (cons (+2) empty)) (F) # appends an element to a list cons P.pair -:test (cons +1 (cons +2 empty)) (P.pair +1 (P.pair +2 empty)) -:test (cons 'a' (cons 'b' (cons 'c' empty))) ("abc") +(:) cons + +:test ((+1) : ((+2) : empty)) (P.pair (+1) (P.pair (+2) empty)) +:test ('a' : ('b' : ('c' : empty))) ("abc") # returns the head of a list or empty head P.fst -:test (head (cons +1 (cons +2 empty))) (+1) +:test (head ((+1) : ((+2) : empty))) ((+1)) # returns the tail of a list or empty tail P.snd -:test (tail (cons +1 (cons +2 empty))) (cons +2 empty) +:test (tail ((+1) : ((+2) : empty))) ((+2) : empty) # returns the length of a list in balanced ternary -length Z [[[empty? 0 [2] [3 (N.inc 2) (tail 1)] I]]] +0 +length Z [[[empty? 0 [2] [3 (N.inc 2) (tail 1)] I]]] (+0) + +#( length -:test (length (cons +1 (cons +2 empty))) (+2) -:test (length empty) (+0) +:test (#((+1) : ((+2) : empty))) ((+2)) +:test (#empty) ((+0)) # returns the element at index in list # TODO: fix for balanced ternary index [[head (1 tail 0)]] +(!!) [[index 0 1]] + # reverses a list -reverse Z [[[empty? 0 [2] [3 (cons (head 1) 2) (tail 1)] I]]] empty +reverse Z [[[empty? 0 [2] [3 ((head 1) : 2) (tail 1)] I]]] empty -:test (reverse (cons +1 (cons +2 (cons +3 empty)))) (cons +3 (cons +2 (cons +1 empty))) +:test (reverse ((+1) : ((+2) : ((+3) : empty)))) ((+3) : ((+2) : ((+1) : empty))) # creates list out of n terms # TODO: fix for balanced ternary -list [0 [[[2 (cons 0 1)]]] reverse empty] +list [0 [[[2 (0 : 1)]]] reverse empty] # merges two lists -merge Z [[[empty? 1 [1] [cons (head 2) (3 (tail 2) 1)] I]]] +merge Z [[[empty? 1 [1] [(head 2) : (3 (tail 2) 1)] I]]] -:test (merge (cons +1 (cons +2 (cons +3 empty))) (cons +4 empty)) (cons +1 (cons +2 (cons +3 (cons +4 empty)))) +(++) merge + +:test (((+1) : ((+2) : ((+3) : empty))) ++ ((+4) : empty)) ((+1) : ((+2) : ((+3) : ((+4) : empty)))) # maps each element to a function -map Z [[[empty? 0 [empty] [cons (2 (head 1)) (3 2 (tail 1))] I]]] +map Z [[[empty? 0 [empty] [(2 (head 1)) : (3 2 (tail 1))] I]]] + +(<$>) map -:test (map N.inc (cons +1 (cons +2 (cons +3 empty)))) (cons +2 (cons +3 (cons +4 empty))) +:test (N.inc <$> ((+1) : ((+2) : ((+3) : empty)))) ((+2) : ((+3) : ((+4) : empty))) # applies a left fold on a list foldl Z [[[[empty? 0 [2] [4 3 (3 2 (head 1)) (tail 1)] I]]]] -:test (N.eq? (foldl N.add +0 (cons +1 (cons +2 (cons +3 empty)))) +6) (T) -:test (N.eq? (foldl N.sub +6 (cons +1 (cons +2 (cons +3 empty)))) +0) (T) +:test (N.eq? (foldl N.add (+0) ((+1) : ((+2) : ((+3) : empty)))) (+6)) (T) +:test (N.eq? (foldl N.sub (+6) ((+1) : ((+2) : ((+3) : empty)))) (+0)) (T) # applies a right fold on a list foldr [[[Z [[empty? 0 [4] [5 (head 1) (2 (tail 1))] I]] 0]]] -:test (N.eq? (foldr N.add +0 (cons +1 (cons +2 (cons +3 empty)))) +6) (T) -:test (N.eq? (foldr N.sub +2 (cons +1 (cons +2 (cons +3 empty)))) +0) (T) +:test (N.eq? (foldr N.add (+0) ((+1) : ((+2) : ((+3) : empty)))) (+6)) (T) +:test (N.eq? (foldr N.sub (+2) ((+1) : ((+2) : ((+3) : empty)))) (+0)) (T) # filters a list based on a predicate filter Z [[[empty? 0 [empty] [2 (head 1) (cons (head 1)) I (3 2 (tail 1))] I]]] -:test (filter N.zero? (cons +1 (cons +0 (cons +3 empty)))) (cons +0 empty) +:test (filter N.zero? ((+1) : ((+0) : ((+3) : empty)))) ((+0) : empty) # returns the last element of a list last Z [[empty? 0 [empty] [empty? (tail 1) (head 1) (2 (tail 1))] I]] -:test (last (cons +1 (cons +2 (cons +3 empty)))) (+3) +:test (last ((+1) : ((+2) : ((+3) : empty)))) ((+3)) # returns everything but the last element of a list -init Z [[empty? 0 [empty] [empty? (tail 1) empty (cons (head 1) (2 (tail 1)))] I]] +init Z [[empty? 0 [empty] [empty? (tail 1) empty ((head 1) : (2 (tail 1)))] I]] -:test (init (cons +1 (cons +2 (cons +3 empty)))) (cons +1 (cons +2 empty)) +:test (init ((+1) : ((+2) : ((+3) : empty)))) ((+1) : ((+2) : empty)) # zips two lists discarding excess elements -zip Z [[[empty? 1 [empty] [empty? 1 empty (cons (cons (head 2) (head 1)) (3 (tail 2) (tail 1)))] I]]] +zip Z [[[empty? 1 [empty] [empty? 1 empty (((head 2) : (head 1)) : (3 (tail 2) (tail 1)))] I]]] -:test (zip (cons +1 (cons +2 empty)) (cons +2 (cons +1 empty))) (cons (P.pair +1 +2) (cons (P.pair +2 +1) empty)) +:test (zip ((+1) : ((+2) : empty)) ((+2) : ((+1) : empty))) ((P.pair (+1) (+2)) : ((P.pair (+2) (+1)) : empty)) # applies pairs of the zipped list as arguments to a function -zip-with Z [[[[empty? 1 [empty] [empty? 1 empty (cons (3 (head 2) (head 1)) (4 3 (tail 2) (tail 1)))] I]]]] +zip-with Z [[[[empty? 1 [empty] [empty? 1 empty ((3 (head 2) (head 1)) : (4 3 (tail 2) (tail 1)))] I]]]] -:test (zip-with N.add (cons +1 (cons +2 empty)) (cons +2 (cons +1 empty))) (cons +3 (cons +3 empty)) +:test (zip-with N.add ((+1) : ((+2) : empty)) ((+2) : ((+1) : empty))) ((+3) : ((+3) : empty)) # returns first n elements of a list -take Z [[[empty? 0 [empty] [N.zero? 2 empty (cons (head 1) (3 (N.dec 2) (tail 1)))] I]]] +take Z [[[empty? 0 [empty] [N.zero? 2 empty ((head 1) : (3 (N.dec 2) (tail 1)))] I]]] -:test (take +2 (cons +1 (cons +2 (cons +3 empty)))) (cons +1 (cons +2 empty)) +:test (take (+2) ((+1) : ((+2) : ((+3) : empty)))) ((+1) : ((+2) : empty)) # takes elements while a predicate is satisfied -take-while Z [[[empty? 0 [empty] [2 (head 1) (cons (head 1) (3 2 (tail 1))) empty] I]]] +take-while Z [[[empty? 0 [empty] [2 (head 1) ((head 1) : (3 2 (tail 1))) empty] I]]] -:test (take-while N.zero? (cons +0 (cons +0 (cons +1 empty)))) (cons +0 (cons +0 empty)) +:test (take-while N.zero? ((+0) : ((+0) : ((+1) : empty)))) ((+0) : ((+0) : empty)) # removes first n elements of a list drop Z [[[empty? 0 [empty] [N.zero? 2 1 (3 (N.dec 2) (tail 1))] I]]] -:test (drop +2 (cons +1 (cons +2 (cons +3 empty)))) (cons +3 empty) +:test (drop (+2) ((+1) : ((+2) : ((+3) : empty)))) ((+3) : empty) # removes elements while a predicate is satisfied drop-while Z [[[empty? 0 [empty] [2 (head 1) (3 2 (tail 1)) 1] I]]] -:test (drop-while N.zero? (cons +0 (cons +0 (cons +1 empty)))) (cons +1 empty) +:test (drop-while N.zero? ((+0) : ((+0) : ((+1) : empty)))) ((+1) : empty) # returns a list with n-times a element repeat Z [[[N.zero? 1 [empty] [P.pair 1 (3 (N.dec 2) 1)] I]]] -:test (repeat +5 +4) ((cons +4 (cons +4 (cons +4 (cons +4 (cons +4 empty)))))) -:test (repeat +1 +4) ((cons +4 empty)) -:test (repeat +0 +4) (empty) +:test (repeat (+5) (+4)) (((+4) : ((+4) : ((+4) : ((+4) : ((+4) : empty)))))) +:test (repeat (+1) (+4)) (((+4) : empty)) +:test (repeat (+0) (+4)) (empty) diff --git a/std/Logic.bruijn b/std/Logic.bruijn index 932a70f..c2a12a4 100644 --- a/std/Logic.bruijn +++ b/std/Logic.bruijn @@ -4,15 +4,19 @@ not [0 F T] -:test (not T) (F) -:test (not F) (T) +!( not + +:test (!T) (F) +:test (!F) (T) and [[1 0 F]] -:test (and T T) (T) -:test (and T F) (F) -:test (and F T) (F) -:test (and F F) (F) +(&&) and + +:test (T && T) (T) +:test (T && F) (F) +:test (F && T) (F) +:test (F && F) (F) nand [[1 0 1 F T]] @@ -23,10 +27,12 @@ nand [[1 0 1 F T]] or [[1 T 0]] -:test (or T T) (T) -:test (or T F) (T) -:test (or F T) (T) -:test (or F F) (F) +(||) or + +:test (T || T) (T) +:test (T || F) (T) +:test (F || T) (T) +:test (F || F) (F) nor [[1 1 0 F T]] @@ -51,19 +57,27 @@ xnor [[1 0 (not 0)]] if [[[2 1 0]]] +(?!) if + :test (if T T F) (T) +:test ((T ?! T) F) (T) :test (if F T F) (F) +:test ((F ?! T) F) (F) implies [[or (not 1) 0]] -:test (implies T T) (T) -:test (implies T F) (F) -:test (implies F T) (T) -:test (implies F F) (T) +(=>?) implies + +:test (T =>? T) (T) +:test (T =>? F) (F) +:test (F =>? T) (T) +:test (F =>? F) (T) iff [[and (implies 1 0) (implies 0 1)]] -:test (iff T T) (T) -:test (iff T F) (F) -:test (iff F T) (F) -:test (iff F F) (T) +(<=>?) iff + +:test (T <=>? T) (T) +:test (T <=>? F) (F) +:test (F <=>? T) (F) +:test (F <=>? F) (T) diff --git a/std/Number.bruijn b/std/Number.bruijn index f603d88..bd54232 100644 --- a/std/Number.bruijn +++ b/std/Number.bruijn @@ -7,13 +7,13 @@ :import std/Logic . -# negative trit indicating coeffecient of -1 +# negative trit indicating coeffecient of (-1) trit-neg [[[2]]] # returns whether a trit is negative trit-neg? [0 T F F] -# positive trit indicating coeffecient of +1 +# positive trit indicating coeffecient of (+1) trit-pos [[[1]]] # returns whether a trit is positive @@ -38,44 +38,52 @@ trit-zero? [0 F F T] # shifts a negative trit into a balanced ternary number up-neg [[[[[2 (4 3 2 1 0)]]]]] -:test (up-neg +0) (-1) -:test (up-neg -1) (-4) -:test (up-neg +42) (+125) +^<( up-neg + +:test (^<(+0)) ((-1)) +:test (^<(-1)) ((-4)) +:test (^<(+42)) ((+125)) # shifts a positive trit into a balanced ternary number up-pos [[[[[1 (4 3 2 1 0)]]]]] -:test (up-pos +0) (+1) -:test (up-pos -1) (-2) -:test (up-pos +42) (+127) +^>( up-pos + +:test (^>(+0)) ((+1)) +:test (^>(-1)) ((-2)) +:test (^>(+42)) ((+127)) # shifts a zero trit into a balanced ternary number up-zero [[[[[0 (4 3 2 1 0)]]]]] -:test (up-zero +0) ([[[[0 3]]]]) -:test (up-zero +1) (+3) -:test (up-zero +42) (+126) +^=( up-zero + +:test (^=(+0)) ([[[[0 3]]]]) +:test (^=(+1)) ((+3)) +:test (^=(+42)) ((+126)) # shifts a specified trit into a balanced ternary number up [[[[[[5 2 1 0 (4 3 2 1 0)]]]]]] -:test (up trit-neg +42) (up-neg +42) -:test (up trit-pos +42) (up-pos +42) -:test (up trit-zero +42) (up-zero +42) +:test (up trit-neg (+42)) (^<(+42)) +:test (up trit-pos (+42)) (^>(+42)) +:test (up trit-zero (+42)) (^=(+42)) # shifts the least significant trit out - basically div by 3 down [snd (0 z neg pos zero)] - z pair +0 +0 - neg [0 [[pair (up-neg 1) 1]]] - pos [0 [[pair (up-pos 1) 1]]] - zero [0 [[pair (up-zero 1) 1]]] + z pair (+0) (+0) + neg [0 [[pair (^<1) 1]]] + pos [0 [[pair (^>1) 1]]] + zero [0 [[pair (^=1) 1]]] # negates a balanced ternary number negate [[[[[4 3 1 2 0]]]]] -:test (negate +0) (+0) -:test (negate -1) (+1) -:test (negate +42) (-42) +-( negate + +:test (-(+0)) ((+0)) +:test (-(-1)) ((+1)) +:test (-(+42)) ((-42)) # converts a balanced ternary number to a list of trits list! [0 z neg pos zero] @@ -88,22 +96,24 @@ list! [0 z neg pos zero] # strips leading 0s from balanced ternary number strip [fst (0 z neg pos zero)] - z pair +0 T - neg [0 [[pair (up-neg 1) F]]] - pos [0 [[pair (up-pos 1) F]]] - zero [0 [[pair (0 +0 (up-zero 1)) 0]]] + z pair (+0) T + neg [0 [[pair (^<1) F]]] + pos [0 [[pair (^>1) F]]] + zero [0 [[pair (0 (+0) (^=1)) 0]]] + +~( strip -:test (strip [[[[0 3]]]]) (+0) -:test (strip [[[[2 (0 (0 (0 (0 3))))]]]]) (-1) -:test (strip +42) (+42) +:test (~[[[[0 3]]]]) ((+0)) +:test (~[[[[2 (0 (0 (0 (0 3))))]]]]) ((-1)) +:test (~(+42)) ((+42)) # extracts least significant trit from balanced ternary numbers lst [0 trit-zero [trit-neg] [trit-pos] [trit-zero]] -:test (lst +0) (trit-zero) -:test (lst -1) (trit-neg) -:test (lst +1) (trit-pos) -:test (lst +42) (trit-zero) +:test (lst (+0)) (trit-zero) +:test (lst (-1)) (trit-neg) +:test (lst (+1)) (trit-pos) +:test (lst (+42)) (trit-zero) # extracts most significant trit from balanced ternary numbers # TODO: Find a more elegant way to do this @@ -113,55 +123,61 @@ lst [0 trit-zero [trit-neg] [trit-pos] [trit-zero]] # TODO: Fix list import loop mst [trit-zero] -:test (mst +0) (trit-zero) -:test (mst -1) (trit-neg) -:test (mst +1) (trit-pos) -:test (mst +42) (trit-pos) +:test (mst (+0)) (trit-zero) +:test (mst (-1)) (trit-neg) +:test (mst (+1)) (trit-pos) +:test (mst (+42)) (trit-pos) # returns whether balanced ternary number is negative negative? [trit-neg? (mst 0)] -:test (negative? +0) (F) -:test (negative? -1) (T) -:test (negative? +1) (F) -:test (negative? +42) (F) +<?( negative? + +:test (<?(+0)) (F) +:test (<?(-1)) (T) +:test (<?(+1)) (F) +:test (<?(+42)) (F) # returns whether balanced ternary number is positive positive? [trit-pos? (mst 0)] -:test (positive? +0) (F) -:test (positive? -1) (F) -:test (positive? +1) (T) -:test (positive? +42) (T) +>?( positive? + +:test (>?(+0)) (F) +:test (>?(-1)) (F) +:test (>?(+1)) (T) +:test (>?(+42)) (T) # checks whether balanced ternary number is zero zero? [0 T [F] [F] I] -:test (zero? +0) (T) -:test (zero? -1) (F) -:test (zero? +1) (F) -:test (zero? +42) (F) +=?( zero? + +:test (=?(+0)) (T) +:test (=?(-1)) (F) +:test (=?(+1)) (F) +:test (=?(+42)) (F) # converts the normal balanced ternary representation into abstract # -> the abstract representation is used in add/sub/mul abstract! [0 z neg pos zero] - z +0 + z (+0) neg [[[[[2 4]]]]] pos [[[[[1 4]]]]] zero [[[[[0 4]]]]] -:test (abstract! -3) ([[[[0 [[[[2 [[[[3]]]]]]]]]]]]) -:test (abstract! +0) ([[[[3]]]]) -:test (abstract! +3) ([[[[0 [[[[1 [[[[3]]]]]]]]]]]]) +:test (abstract! (-3)) ([[[[0 [[[[2 [[[[3]]]]]]]]]]]]) +:test (abstract! (+0)) ([[[[3]]]]) +:test (abstract! (+3)) ([[[[0 [[[[1 [[[[3]]]]]]]]]]]]) # converts the abstracted balanced ternary representation back to normal # using ω to solve recursion normal! ω rec - rec [[0 +0 [up-neg ([3 3 0] 0)] [up-pos ([3 3 0] 0)] [up-zero ([3 3 0] 0)]]] + rec [[0 (+0) [^<([3 3 0] 0)] [^>([3 3 0] 0)] [^=([3 3 0] 0)]]] -:test (normal! [[[[3]]]]) (+0) -:test (normal! (abstract! +42)) (+42) -:test (normal! (abstract! -42)) (-42) +:test (normal! [[[[3]]]]) ((+0)) +:test (normal! (abstract! (+42))) ((+42)) +:test (normal! (abstract! (-42))) ((-42)) # checks whether two balanced ternary numbers are equal # -> ignores leading 0s! @@ -174,90 +190,96 @@ eq? [[abs 1 (abstract! 0)]] (=?) eq? -:test (-42 =? -42) (T) -:test (-1 =? -1) (T) -:test (-1 =? +0) (F) -:test (+0 =? +0) (T) -:test (+1 =? +0) (F) -:test (+1 =? +1) (T) -:test (+42 =? +42) (T) -:test ([[[[(1 (0 (0 (0 (0 3)))))]]]] =? +1) (T) +:test ((-42) =? (-42)) (T) +:test ((-1) =? (-1)) (T) +:test ((-1) =? (+0)) (F) +:test ((+0) =? (+0)) (T) +:test ((+1) =? (+0)) (F) +:test ((+1) =? (+1)) (T) +:test ((+42) =? (+42)) (T) +:test ([[[[(1 (0 (0 (0 (0 3)))))]]]] =? (+1)) (T) # I believe Mogensen's Paper has an error in its inc/dec/add/mul/eq definitions. # They use 3 instead of 2 abstractions in the functions, also we use switched # +/0 in comparison to their implementation, yet the order of neg/pos/zero is # the same. Something's weird. -# adds +1 to a balanced ternary number (can introduce leading 0s) +# adds (+1) to a balanced ternary number (can introduce leading 0s) inc [snd (0 z neg pos zero)] - z pair +0 +1 - neg [0 [[pair (up-neg 1) (up-zero 1)]]] - zero [0 [[pair (up-zero 1) (up-pos 1)]]] - pos [0 [[pair (up-pos 1) (up-neg 0)]]] + z pair (+0) (+1) + neg [0 [[pair (^<1) (^=1)]]] + zero [0 [[pair (^=1) (^>1)]]] + pos [0 [[pair (^>1) (^<0)]]] + +++( inc -# adds +1 to a balanced ternary number and strips leading 0s -sinc [strip (inc 0)] +# adds (+1) to a balanced ternary number and strips leading 0s +ssinc [~(++0)] -:test (eq? (inc -42) -41) (T) -:test (eq? (inc -1) +0) (T) -:test (eq? (inc +0) +1) (T) -:test (eq? (inc (inc (inc (inc (inc +0))))) +5) (T) -:test (eq? (inc +42) +43) (T) +:test ((++(-42)) =? (-41)) (T) +:test ((++(-1)) =? (+0)) (T) +:test ((++(+0)) =? (+1)) (T) +:test ((++(++(++(++(++(+0)))))) =? (+5)) (T) +:test ((++(+42)) =? (+43)) (T) -# subs +1 from a balanced ternary number (can introduce leading 0s) +# subs (+1) from a balanced ternary number (can introduce leading 0s) dec [snd (0 dec-z dec-neg dec-pos dec-zero)] - dec-z pair +0 -1 - dec-neg [0 [[pair (up-neg 1) (up-pos 0)]]] - dec-zero [0 [[pair (up-zero 1) (up-neg 1)]]] - dec-pos [0 [[pair (up-pos 1) (up-zero 1)]]] + dec-z pair (+0) (-1) + dec-neg [0 [[pair (^<1) (^>0)]]] + dec-zero [0 [[pair (^=1) (^<1)]]] + dec-pos [0 [[pair (^>1) (^=1)]]] -# subs +1 from a balanced ternary number and strips leading 0s -sdec [strip (dec 0)] +--( dec -:test (eq? (dec -42) -43) (T) -:test (eq? (dec +0) -1) (T) -:test (eq? (dec (dec (dec (dec (dec +5))))) +0) (T) -:test (eq? (dec +1) +0) (T) -:test (eq? (dec +42) +41) (T) +# subs (+1) from a balanced ternary number and strips leading 0s +ssub [~(--0)] + +:test ((--(-42)) =? (-43)) (T) +:test ((--(+0)) =? (-1)) (T) +:test ((--(--(--(--(--(+5)))))) =? (+0)) (T) +:test ((--(+1)) =? (+0)) (T) +:test ((--(+42)) =? (+41)) (T) # adds two balanced ternary numbers (can introduce leading 0s) add [[abs 1 (abstract! 0)]] c [[1 0 trit-zero]] - b-neg2 [1 (up-zero (3 0 trit-neg)) (up-neg (3 0 trit-zero)) (up-pos (3 0 trit-neg))] - b-neg [1 (up-pos (3 0 trit-neg)) (up-zero (3 0 trit-zero)) (up-neg (3 0 trit-zero))] + b-neg2 [1 (^=(3 0 trit-neg)) (^<(3 0 trit-zero)) (^>(3 0 trit-neg))] + b-neg [1 (^>(3 0 trit-neg)) (^=(3 0 trit-zero)) (^<(3 0 trit-zero))] b-zero [up 1 (3 0 trit-zero)] - b-pos [1 (up-zero (3 0 trit-zero)) (up-neg (3 0 trit-pos)) (up-pos (3 0 trit-zero))] - b-pos2 [1 (up-pos (3 0 trit-zero)) (up-zero (3 0 trit-pos)) (up-neg (3 0 trit-pos))] + b-pos [1 (^=(3 0 trit-zero)) (^<(3 0 trit-pos)) (^>(3 0 trit-zero))] + b-pos2 [1 (^>(3 0 trit-zero)) (^=(3 0 trit-pos)) (^<(3 0 trit-pos))] a-neg [[[1 (b-neg 1) b-neg2 b-zero b-neg]]] a-pos [[[1 (b-pos 1) b-zero b-pos2 b-pos]]] a-zero [[[1 (b-zero 1) b-neg b-pos b-zero]]] - z [[0 (dec (normal! 1)) (inc (normal! 1)) (normal! 1)]] + z [[0 (--(normal! 1)) (++(normal! 1)) (normal! 1)]] abs [c (0 z a-neg a-pos a-zero)] (+) add # adds two balanced ternary numbers and strips leading 0s -sadd [[strip (add 1 0)]] +sadd [[~(1 + 0)]] -:test (eq? (add -42 -1) -43) (T) -:test (eq? (add -5 +6) +1) (T) -:test (eq? (add -1 +0) -1) (T) -:test (eq? (add +0 +0) +0) (T) -:test (eq? (add +1 +2) +3) (T) -:test (eq? (add +42 +1) +43) (T) +:test (((-42) + (-1)) =? (-43)) (T) +:test (((-5) + (+6)) =? (+1)) (T) +:test (((-1) + (+0)) =? (-1)) (T) +:test (((+0) + (+0)) =? (+0)) (T) +:test (((+1) + (+2)) =? (+3)) (T) +:test (((+42) + (+1)) =? (+43)) (T) # subs two balanced ternary numbers (can introduce leading 0s) -sub [[add 1 (negate 0)]] +sub [[1 + -0]] + +(-) sub # subs two balanced ternary numbers and strips leading 0s -ssub [[strip (sub 1 0)]] +ssub [[~(1 - 0)]] -:test (eq? (sub -42 -1) -41) (T) -:test (eq? (sub -5 +6) -11) (T) -:test (eq? (sub -1 +0) -1) (T) -:test (eq? (sub +0 +0) +0) (T) -:test (eq? (sub +1 +2) -1) (T) -:test (eq? (sub +42 +1) +41) (T) +:test (((-42) - (-1)) =? (-41)) (T) +:test (((-5) - (+6)) =? (-11)) (T) +:test (((-1) - (+0)) =? (-1)) (T) +:test (((+0) - (+0)) =? (+0)) (T) +:test (((+1) - (+2)) =? (-1)) (T) +:test (((+42) - (+1)) =? (+41)) (T) # returns whether number is greater than other number gre? [[negative? (sub 0 1)]] @@ -270,16 +292,16 @@ leq? [[not (gre? 1 0)]] (<=?) leq? # muls two balanced ternary numbers (can introduce leading 0s) -mul [[1 +0 neg pos zero]] - neg [sub (up-zero 0) 1] - pos [add (up-zero 0) 1] - zero [up-zero 0] +mul [[1 (+0) neg pos zero]] + neg [(^=0) - 1] + pos [(^=0) + 1] + zero [^=0] (*) mul smul [[strip (mul 1 0)]] -:test (eq? (mul +42 +0) +0) (T) -:test (eq? (mul -1 +42) -42) (T) -:test (eq? (mul +3 +11) +33) (T) -:test (eq? (mul +42 -4) -168) (T) +:test (((+42) * (+0)) =? (+0)) (T) +:test (((-1) * (+42)) =? (-42)) (T) +:test (((+3) * (+11)) =? (+33)) (T) +:test (((+42) * (-4)) =? (-168)) (T) |