Skip to content

Commit 9ea8c18

Browse files
committed
Ported over Solve module, cleaned it up, wrote tests for it
1 parent 45577f0 commit 9ea8c18

File tree

5 files changed

+416
-18
lines changed

5 files changed

+416
-18
lines changed

lambda-buffers-compiler/lambda-buffers-compiler.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -117,6 +117,7 @@ library
117117
LambdaBuffers.Compiler.TypeClass.Pat
118118
LambdaBuffers.Compiler.TypeClass.Pretty
119119
LambdaBuffers.Compiler.TypeClass.Rules
120+
LambdaBuffers.Compiler.TypeClass.Solve
120121
LambdaBuffers.Compiler.TypeClassCheck
121122

122123
hs-source-dirs: src

lambda-buffers-compiler/src/LambdaBuffers/Compiler/TypeClass/Pretty.hs

Lines changed: 4 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,3 @@
1-
{-# LANGUAGE OverloadedLabels #-}
21
{-# LANGUAGE OverloadedStrings #-}
32
-- orphans are the whole point of this module!
43
{-# OPTIONS_GHC -Wno-orphans #-}
@@ -10,14 +9,13 @@ module LambdaBuffers.Compiler.TypeClass.Pretty (
109
(<///>),
1110
) where
1211

13-
import Control.Lens ((^.))
1412
import Data.Generics.Labels ()
1513
import LambdaBuffers.Compiler.ProtoCompat qualified as P
1614
import LambdaBuffers.Compiler.TypeClass.Pat (Pat (AppP, DecP, ModuleName, Name, Nil, Opaque, ProdP, RecP, RefP, SumP, VarP, (:*), (:=)), patList)
1715
import LambdaBuffers.Compiler.TypeClass.Rules (
1816
Class (Class),
1917
Constraint (C),
20-
Instance,
18+
FQClassName (FQClassName),
2119
Rule ((:<=)),
2220
)
2321
import Prettyprinter (
@@ -34,21 +32,16 @@ import Prettyprinter (
3432
(<+>),
3533
)
3634

37-
instance Pretty P.TyClassRef where
38-
pretty = \case
39-
P.ForeignCI (P.ForeignClassRef cn mn _) -> pretty mn <> "." <> pretty (cn ^. #name)
40-
P.LocalCI (P.LocalClassRef cn _) -> pretty (cn ^. #name)
41-
42-
instance Pretty P.ModuleName where
43-
pretty (P.ModuleName pts _) = hcat . punctuate "." $ map (\x -> pretty $ x ^. #name) pts
35+
instance Pretty FQClassName where
36+
pretty (FQClassName cn mnps) = hcat (punctuate "." . map pretty $ mnps) <> pretty cn
4437

4538
instance Pretty Class where
4639
pretty (Class nm _) = pretty nm
4740

4841
instance Pretty Constraint where
4942
pretty (C cls p) = pretty cls <+> pretty p
5043

51-
instance Pretty Instance where
44+
instance Pretty Rule where
5245
pretty (c :<= []) = pretty c
5346
pretty (c :<= cs) = pretty c <+> "<=" <+> list (pretty <$> cs)
5447

lambda-buffers-compiler/src/LambdaBuffers/Compiler/TypeClass/Rules.hs

Lines changed: 18 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -5,16 +5,22 @@ module LambdaBuffers.Compiler.TypeClass.Rules (
55
Class (..),
66
Constraint (..),
77
Rule (..),
8-
type Instance,
8+
FQClassName (..),
99
mapPat,
10+
ruleHeadPat,
11+
ruleHeadClass,
1012
) where
1113

12-
import LambdaBuffers.Compiler.ProtoCompat qualified as P
14+
import Data.Text (Text)
15+
1316
import LambdaBuffers.Compiler.TypeClass.Pat (Pat)
1417

18+
data FQClassName = FQClassName {cName :: Text, cModule :: [Text]}
19+
deriving stock (Show, Eq, Ord)
20+
1521
data Class = Class
16-
{ name :: P.TyClassRef
17-
, supers :: [Class]
22+
{ cname :: FQClassName
23+
, csupers :: [Class]
1824
}
1925
deriving stock (Show, Eq, Ord)
2026

@@ -33,9 +39,15 @@ data Rule where
3339
deriving stock (Show, Eq, Ord)
3440
infixl 7 :<=
3541

36-
type Instance = Rule
37-
3842
{- Map over the Pats inside of an Rule
3943
-}
4044
mapPat :: (Pat -> Pat) -> Rule -> Rule
4145
mapPat f (C c ty :<= is) = C c (f ty) :<= map (\(C cx p) -> C cx (f p)) is
46+
47+
{- Extract the inner Pat from a Rule head
48+
-}
49+
ruleHeadPat :: Rule -> Pat
50+
ruleHeadPat (C _ p :<= _) = p
51+
52+
ruleHeadClass :: Rule -> Class
53+
ruleHeadClass (C c _ :<= _) = c
Lines changed: 145 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,145 @@
1+
{-# LANGUAGE LambdaCase #-}
2+
3+
module LambdaBuffers.Compiler.TypeClass.Solve (solve) where
4+
5+
import Data.List (foldl', sortBy)
6+
import Data.Text (Text)
7+
import LambdaBuffers.Compiler.TypeClass.Pat (
8+
Pat (AppP, DecP, ProdP, RecP, RefP, SumP, VarP, (:*), (:=)),
9+
matches,
10+
)
11+
import LambdaBuffers.Compiler.TypeClass.Rules (
12+
Class (csupers),
13+
Constraint (C),
14+
Rule ((:<=)),
15+
mapPat,
16+
ruleHeadClass,
17+
ruleHeadPat,
18+
)
19+
20+
import Data.Set qualified as S
21+
22+
{- Variable substitution. Given a string that represents a variable name,
23+
and a type to instantiate variables with that name to, performs the
24+
instantiation
25+
-}
26+
subV :: Text -> Pat -> Pat -> Pat
27+
subV varNm t = \case
28+
var@(VarP v) -> if v == varNm then t else var
29+
x :* xs -> subV varNm t x :* subV varNm t xs
30+
l := x -> subV varNm t l := subV varNm t x
31+
ProdP xs -> ProdP (subV varNm t xs)
32+
RecP xs -> RecP (subV varNm t xs)
33+
SumP xs -> SumP (subV varNm t xs)
34+
AppP t1 t2 -> AppP (subV varNm t t1) (subV varNm t t2)
35+
RefP n x -> RefP (subV varNm t n) (subV varNm t x)
36+
DecP a b c -> DecP (subV varNm t a) (subV varNm t b) (subV varNm t c)
37+
other -> other
38+
39+
{- Performs substitution on an entire instance (the first argument) given the
40+
concrete types from a Pat (the second argument).
41+
Note that ONLY PatVars which occur in the Instance *HEAD* are replaced, though they
42+
are replaced in the instance superclasses as well (if they occur there).
43+
-}
44+
subst :: Rule -> Pat -> Rule
45+
subst cst@(C _ t :<= _) ty = mapPat (go (getSubs t ty)) cst
46+
where
47+
go :: [(Text, Pat)] -> Pat -> Pat
48+
go subs tty =
49+
let noflip p1 p2 = uncurry subV p2 p1
50+
in foldl' noflip tty subs
51+
52+
{- Given two patterns (which are hopefully structurally similar), gather a list of all substitutions
53+
from the PatVars in the first argument to the concrete types (hopefully!) in the second argument
54+
-}
55+
getSubs :: Pat -> Pat -> [(Text, Pat)] -- should be a set, whatever
56+
getSubs (VarP s) t = [(s, t)]
57+
getSubs (x :* xs) (x' :* xs') = getSubs x x' <> getSubs xs xs'
58+
getSubs (l := t) (l' := t') = getSubs l l' <> getSubs t t'
59+
getSubs (ProdP xs) (ProdP xs') = getSubs xs xs'
60+
getSubs (RecP xs) (RecP xs') = getSubs xs xs'
61+
getSubs (SumP xs) (SumP xs') = getSubs xs xs'
62+
getSubs (AppP t1 t2) (AppP t1' t2') = getSubs t1 t1' <> getSubs t2 t2'
63+
getSubs (RefP n t) (RefP n' t') = getSubs n n' <> getSubs t t'
64+
getSubs (DecP a b c) (DecP a' b' c') = getSubs a a' <> getSubs b b' <> getSubs c c'
65+
getSubs _ _ = []
66+
67+
-- should be vastly more efficient than Data.List.Nub
68+
deduplicate :: Ord a => [a] -> [a]
69+
deduplicate = S.toList . S.fromList
70+
71+
-- is the first pattern a substitution instance of the second
72+
isSubstitutionOf :: Pat -> Pat -> Bool
73+
isSubstitutionOf p1 p2 = matches p2 p1
74+
75+
compareSpecificity :: Pat -> Pat -> Ordering
76+
compareSpecificity p1 p2
77+
| p1
78+
`isSubstitutionOf` p2
79+
&& p2
80+
`isSubstitutionOf` p1 =
81+
EQ
82+
| p1 `isSubstitutionOf` p2 = LT
83+
| otherwise = GT
84+
85+
sortOnSpecificity :: Pat -> Class -> [Rule] -> [Rule]
86+
sortOnSpecificity p c ps =
87+
sortBy (\a1 a2 -> compareSpecificity (ruleHeadPat a1) (ruleHeadPat a2)) $
88+
filter matchPatAndClass ps
89+
where
90+
matchPatAndClass :: Rule -> Bool
91+
matchPatAndClass r =
92+
ruleHeadClass r == c
93+
&& ruleHeadPat r
94+
`matches` p
95+
96+
mostSpecificInstance :: Pat -> Class -> [Rule] -> Maybe Rule
97+
mostSpecificInstance p c ps = case sortOnSpecificity p c ps of
98+
[] -> Nothing
99+
(x : _) -> Just x
100+
101+
{- Given a list of instances (the initial scope), determines whether we can derive
102+
an instance of the Class argument for the Pat argument. A result of [] indicates that there are
103+
no remaining subgoals and that the constraint has been solved.
104+
NOTE: At the moment this handles superclasses differently than you might expect -
105+
instead of assuming that the superclasses for all in-scope classes are defined,
106+
we check that those constraints can be solved before affirmatively judging that the
107+
target constraint has been solved. I *think* that makes sense in this context (whereas in Haskell
108+
it doesn't b/c it's *impossible* to have `instance Foo X` if the definition of Foo is
109+
`class Bar y => Foo y` without an `instance Bar X`)
110+
-}
111+
solve ::
112+
[Rule] -> -- all instance rules in scope. WE ASSUME THESE HAVE ALREADY BEEN GENERATED, SOMEWHERE
113+
Constraint -> -- constraint we're trying to solve
114+
[Constraint] -- subgoals that cannot be solved for w/ the current rule set
115+
solve inScope cst@(C c pat) =
116+
-- First, we look for the most specific instance...
117+
case mostSpecificInstance pat c inScope of
118+
-- If there isn't one, we return only the constraint we were trying to solve
119+
Nothing -> [cst]
120+
-- If there is, we substitute the argument of the constraint to be solved into the matching rules
121+
Just rule -> case subst rule pat of
122+
-- If there are no additional constraints on the rule, we try to solve the superclasses
123+
C _ p :<= [] -> case csupers c of
124+
[] -> []
125+
xs -> solveClassesFor p xs
126+
-- If there are additional constraints on the rule, we try to solve them
127+
C _ _ :<= is -> case concatMap (solve inScope) is of
128+
-- If we succeed at solving the additional constraints on the rule, we try to solve the supers
129+
[] -> solveClassesFor pat (csupers c)
130+
-- We deduplicate the list of unsolvable subgoals
131+
xs -> deduplicate xs
132+
where
133+
-- NOTE(@bladyjoker): The version w/ flip is more performant...
134+
-- Given a Pat and a list of Classes, attempt to solve the constraints
135+
-- constructed from the Pat and each Class
136+
solveClassesFor :: Pat -> [Class] -> [Constraint]
137+
solveClassesFor p =
138+
deduplicate -- multiple constraints could emit the same subgoal which is bad
139+
. concatMap
140+
( solve inScope
141+
. ( \cls ->
142+
let classConstraint = C cls p
143+
in classConstraint
144+
)
145+
)

0 commit comments

Comments
 (0)