Skip to content

Commit 946aed6

Browse files
committed
Give Op0 a mandatory name
1 parent 6888af7 commit 946aed6

File tree

5 files changed

+38
-35
lines changed

5 files changed

+38
-35
lines changed

app/Main.hs

+7-7
Original file line numberDiff line numberDiff line change
@@ -7,19 +7,19 @@ import Autotool.Parser.Relation (parseIntRelation)
77
import Autotool.Data.Parallel.LazyTree (treesP)
88
main = do
99
let
10-
r = parseIntRelation "{(1,1),(1,2),(2,1)}"
10+
r = Op0 "r" $ parseIntRelation "{(1,1),(1,2),(2,1)}"
1111
-- s = Set "S" [ V(1 , 3), V(2 , 1), V(2 , 2) ]
12-
s = parseIntRelation "{(1,3),(2,1),(2,2)}"
12+
s = Op0 "s" $ parseIntRelation "{(1,3),(2,1),(2,2)}"
1313
-- t = S[ V(1 , 2) , V(2 , 3) ]
1414
t = parseIntRelation "{(1,3),(2,3)}"
15-
ops = [(+), (&), (-), (*), Op0 r, Op0 s]
15+
ops = [(+), (&), (-), (*), r, s]
1616
-- result = Node2 Subtr (Node2 Compose (Node0 r) (Node2 Subtr (Node0 s) (Node0 r))) (Node0 s)
1717
result = Node (-) [
1818
Node (*) [
19-
Node (Op0 r) [],
20-
Node (-) [ Node (Op0 s) [], Node (Op0 r) [] ]
19+
Node r [],
20+
Node (-) [ Node s [], Node r [] ]
2121
],
22-
Node (Op0 s) []
22+
Node s []
2323
]
2424
ts = treesP ops
2525
st = let f a
@@ -28,5 +28,5 @@ main = do
2828
| otherwise = show a
2929
in showTreeFn f
3030
-- mapM_ (putStrLn . st) ts
31-
print $ solve ops t
31+
putStrLn $ showTree $ solve ops t
3232

src/Autotool/Data/LazyTree.hs

+6-6
Original file line numberDiff line numberDiff line change
@@ -21,9 +21,9 @@ module Autotool.Data.LazyTree
2121
import Data.Tree (foldTree, levels, Tree(Node) )
2222
import Debug.Trace (traceShow, traceShowId)
2323

24-
data Op a = Op0 a | Op1 String (a -> a) | Op2 String (a -> a -> a)
24+
data Op a = Op0 String a | Op1 String (a -> a) | Op2 String (a -> a -> a)
2525

26-
isOp0 (Op0 _) = True
26+
isOp0 (Op0 _ _) = True
2727
isOp0 _ = False
2828

2929
isOp1 (Op1 _ _) = True
@@ -33,20 +33,20 @@ isOp2 (Op2 _ _) = True
3333
isOp2 _ = False
3434

3535
eval :: Op a -> [a] -> a
36-
eval (Op0 a) _ = a
36+
eval (Op0 _ a) _ = a
3737
eval (Op1 _ f) [a] = f a
3838
eval (Op2 _ f) [a,b] = f a b
3939

4040
evalTree = foldTree eval
4141

4242
instance (Eq a) => Eq (Op a) where
43-
(Op0 a) == (Op0 b) = a == b
43+
(Op0 _ a) == (Op0 _ b) = a == b
4444
(Op1 a _) == (Op1 b _) = a == b
4545
(Op2 a _) == (Op2 b _) = a == b
4646
_ == _ = False
4747

4848
instance (Show a) => Show (Op a) where
49-
show (Op0 a) = show a
49+
show (Op0 s _) = s
5050
show (Op1 s _) = s
5151
show (Op2 s _) = s
5252

@@ -135,6 +135,6 @@ showTree = showTreeFn show
135135
showTreeFn :: (Show a) => (a -> String) -> Tree (Op a) -> String
136136
showTreeFn showValue = foldTree f
137137
where
138-
f (Op0 a) _ = showValue a
138+
f (Op0 s _) _ = s
139139
f (Op1 s _) [a] = s ++ "(" ++ a ++ ")"
140140
f (Op2 s _) [a,b] = "(" ++ a ++ ") " ++ s ++ " (" ++ b ++ ")"

src/Autotool/Data/NestedSet.hs

+4-1
Original file line numberDiff line numberDiff line change
@@ -4,8 +4,10 @@ import Data.Set (Set, empty, fromList, toList, insert)
44
import qualified Data.Set as S
55
import Data.List (intercalate)
66

7+
-- | Recursive sum type of 'either a value or a set of Ts'
78
data T a = V a | S (Set (T a)) deriving (Eq, Ord, Show)
89

10+
-- | A Data.Set of type (T a)
911
type NSet a = Set (T a)
1012

1113
-- for internal (e. g. parser) use
@@ -17,8 +19,8 @@ set = S
1719

1820
unwrap :: T a -> NSet a
1921
unwrap (S s) = s
20-
--
2122

23+
ø :: Set a
2224
ø = empty
2325

2426
øN :: (Ord a) => Int -> NSet a
@@ -39,6 +41,7 @@ a ++. s = insert (S $ fromList $ map V a) s
3941
(&.) :: (Ord a) => NSet a -> NSet a -> NSet a
4042
infixr 2 &.
4143
a &. s = insert (S a) s
44+
--
4245

4346
powerSet :: (Ord a) => NSet a -> NSet a
4447
powerSet s = S.map S $ S.powerSet s

test/Autotool/Solver/RelationsSpec.hs

+13-13
Original file line numberDiff line numberDiff line change
@@ -12,34 +12,34 @@ spec = do
1212
describe "relations" $ do
1313
it "finds term w/ a target value from a set of relations and operations on them (1)" $
1414
let
15-
r = parseIntRelation "{(1,1),(1,2),(2,1)}"
16-
s = parseIntRelation "{(1,3),(2,1),(2,2)}"
15+
r = Op0 "r" $ parseIntRelation "{(1,1),(1,2),(2,1)}"
16+
s = Op0 "s" $ parseIntRelation "{(1,3),(2,1),(2,2)}"
1717
t = parseIntRelation "{(1,3),(2,3)}"
18-
ops = [(+), (&), (-), (*), Op0 r, Op0 s]
18+
ops = [(+), (&), (-), (*), r, s]
1919
result =
2020
Node (-) [
2121
Node (*) [
22-
Node (Op0 r) [],
23-
Node (Op0 s) []
22+
Node r [],
23+
Node s []
2424
],
25-
Node (Op0 r) []
25+
Node r []
2626
]
2727
in solve ops t `shouldBe` result
2828
it "finds term w/ a target value from a set of relations and operations on them (2)" $
2929
let
30-
r = parseIntRelation "{(1 , 4) , (2 , 4) , (3 , 2) , (4 , 1)}"
31-
s = parseIntRelation "{(1 , 4) , (2 , 2) , (2 , 3) , (4 , 4)}"
30+
r = Op0 "r" parseIntRelation "{(1 , 4) , (2 , 4) , (3 , 2) , (4 , 1)}"
31+
s = Op0 "s" parseIntRelation "{(1 , 4) , (2 , 2) , (2 , 3) , (4 , 4)}"
3232
t = parseIntRelation "{(1 , 1) , (1 , 4) , (2 , 1) , (2 , 2) , (2 , 4) , (4 , 1) , (4 , 4)}"
33-
ops = [(+), (&), (-), (*), Op0 r, Op0 s]
33+
ops = [(+), (&), (-), (*), r, s]
3434
result =
3535
Node (*) [
36-
Node (Op0 s) [],
36+
Node s [],
3737
Node (*) [
3838
Node (+) [
39-
Node (Op0 s) [],
40-
Node (Op0 r) []
39+
Node s [],
40+
Node r []
4141
],
42-
Node (Op0 r) []
42+
Node r []
4343
]
4444
]
4545
in solve ops t `shouldBe` result

test/Autotool/Solver/SetsSpec.hs

+8-8
Original file line numberDiff line numberDiff line change
@@ -12,17 +12,17 @@ spec = do
1212
describe "sets" $ do
1313
it "finds term w/ a target value from a set of sets and operations on them (1)" $
1414
let
15-
a = parseIntSet "{1, 2}"
16-
b = parseIntSet "{{3}}"
15+
a = Op0 "a" $ parseIntSet "{1, 2}"
16+
b = Op0 "b" $ parseIntSet "{{3}}"
1717
r = parseIntSet "{{}, {1, 2, {3}}, {1, {3}}, {2, {3}}, {{3}}}"
18-
ops = [(-), (+), (&), pow, Op0 a, Op0 b]
19-
result = Node (-) [Node pow [Node (+) [Node (Op0 a) [], Node (Op0 b) []] ], Node (-) [Node pow [Node (Op0 a) []], Node pow [Node (Op0 b) []]] ]
18+
ops = [(-), (+), (&), pow, a, b]
19+
result = Node (-) [Node pow [Node (+) [Node a [], Node b []] ], Node (-) [Node pow [Node a []], Node pow [Node b []]] ]
2020
in solve ops r `shouldBe` result
2121
it "finds term w/ a target value from a set of sets and operations on them (2)" $
2222
let
23-
a = parseIntSet "{{3, {}}}"
24-
b = parseIntSet "{3, {1, {}, {2}}}"
23+
a = Op0 "a" $ parseIntSet "{{3, {}}}"
24+
b = Op0 "b" $ parseIntSet "{3, {1, {}, {2}}}"
2525
r = parseIntSet "{{{3, {}}}}"
26-
ops = [(-), (+), (&), pow, Op0 a, Op0 b]
27-
result = Node (-) [ Node pow [Node (Op0 a) []], Node pow [Node (Op0 b) []] ]
26+
ops = [(-), (+), (&), pow, a, b]
27+
result = Node (-) [ Node pow [Node a []], Node pow [Node b []] ]
2828
in solve ops r `shouldBe` result

0 commit comments

Comments
 (0)