Skip to content

Commit a26f724

Browse files
alt-romesNadiaYvette
authored andcommitted
Make Language a type synonym
1 parent 4aa01db commit a26f724

File tree

8 files changed

+4
-15
lines changed

8 files changed

+4
-15
lines changed

TODO

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
[ ] Newtype over ClassId and abstract implementation. Only way to get ClassIds is through representation and adding
12
[ ] Freeze/Unfreeze implementation of Union Find with unboxed vectors
23
[ ] Point out module should be imported qualified, and rename emptyEG to just `empty`
34
[ ] Point out that we have pure functional e-graphs!!

src/Data/Equality/Language.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE FlexibleContexts #-}
2+
{-# LANGUAGE ConstraintKinds #-}
23
{-|
34
45
Defines 'Language', which is the required constraint on /expressions/ that are
@@ -38,5 +39,5 @@ import Data.Functor.Classes
3839
-- e-graphs), note that it must satisfy the other class constraints. In
3940
-- particular an 'Data.Equality.Analysis.Analysis' must be defined for the
4041
-- language.
41-
class (Traversable l, Ord1 l) => Language l where
42+
type Language l = (Traversable l, Ord1 l)
4243

test/Invariants.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,7 @@ import Sym
3737
-- TODO: Use type level symbol to define the analysis
3838
type role SimpleExpr nominal
3939
newtype SimpleExpr l = SE (Expr l)
40-
deriving (Functor, Foldable, Traversable, Show1, Eq1, Ord1, Language)
40+
deriving (Functor, Foldable, Traversable, Show1, Eq1, Ord1)
4141

4242
-- | When a rewrite of type "x":=c where x is a pattern variable and c is a
4343
-- constant is used in equality saturation of any expression, all e-classes

test/Lambda.hs

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -112,9 +112,6 @@ instance Analysis FreeVars Lambda where
112112

113113
joinA = (<>)
114114

115-
116-
instance Language Lambda
117-
118115
instance Num (Fix Lambda) where
119116
fromInteger = Fix . Num . fromInteger
120117
(+) a b = Fix $ Add a b

test/SimpleSym.hs

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,6 @@ import Text.Show.Deriving
1717
import Data.Equality.Utils
1818
import Data.Equality.Matching
1919
import Data.Equality.Saturation
20-
import Data.Equality.Language
2120
import Data.Equality.Analysis
2221
import Data.Equality.Graph.Lens ((^.), _data)
2322

@@ -34,8 +33,6 @@ deriveEq1 ''SymExpr
3433
deriveOrd1 ''SymExpr
3534
deriveShow1 ''SymExpr
3635

37-
instance Language SymExpr
38-
3936
instance Analysis (Maybe Double) SymExpr where
4037
makeA = \case
4138
Const x -> Just x

test/Sym.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -60,8 +60,6 @@ deriveEq1 ''Expr
6060
deriveOrd1 ''Expr
6161
deriveShow1 ''Expr
6262

63-
instance Language Expr
64-
6563
instance IsString (Fix Expr) where
6664
fromString = Fix . Sym
6765

test/T1.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -100,8 +100,6 @@ instance Floating (Pattern TreeF) where
100100
l ** r = undefined
101101
logBase l r = undefined
102102

103-
instance Language TreeF
104-
105103
cost :: CostFunction TreeF Int
106104
cost = \case
107105
ConstF _ -> 5

test/T2.hs

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,6 @@ import Prelude hiding (not)
1111
import Test.Tasty.HUnit
1212
import Data.Deriving
1313
import Data.Equality.Matching
14-
import Data.Equality.Language
1514
import Data.Equality.Extraction
1615
import Data.Equality.Saturation
1716

@@ -26,8 +25,6 @@ deriveEq1 ''Lang
2625
deriveOrd1 ''Lang
2726
deriveShow1 ''Lang
2827

29-
instance Language Lang
30-
3128
x, y :: Pattern Lang
3229
x = "x"
3330
y = "y"

0 commit comments

Comments
 (0)