Skip to content

Commit 3fabbb5

Browse files
authored
Expose GSubst module within Internal (#60)
* move GSubst into a separate module
1 parent 045764b commit 3fabbb5

File tree

4 files changed

+69
-42
lines changed

4 files changed

+69
-42
lines changed

Changelog.md

+2
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,8 @@
44
* Add GHC 9.8 to CI matrix
55
* Bump base >= 4.9
66
* Remove `tested-with: 7.x` in `unbound-generics.cabal`. We removed CI testing with GHC 7.x last year.
7+
* Move GSubst from `Unbound.Generics.LocallyNameless.Subst` into a separate `Internal` module that is exported. Now users can write their own generic traversals.
8+
Thanks Bohdan Liesnikov (liesnikov)
79

810
# 0.4.3
911

Original file line numberDiff line numberDiff line change
@@ -0,0 +1,60 @@
1+
-- |
2+
-- Module : Unbound.Generics.LocallyNameless.Subst
3+
-- Copyright : (c) 2014, Aleksey Kliger
4+
-- License : BSD3 (See LICENSE)
5+
-- Maintainer : Aleksey Kliger
6+
-- Stability : experimental
7+
--
8+
-- A typeclass for generic structural substitution.
9+
10+
{-# LANGUAGE
11+
FlexibleInstances
12+
, MultiParamTypeClasses
13+
, TypeOperators
14+
#-}
15+
16+
module Unbound.Generics.LocallyNameless.Internal.GSubst (
17+
GSubst(..)
18+
) where
19+
20+
import GHC.Generics
21+
22+
import Unbound.Generics.LocallyNameless.Name
23+
import Unbound.Generics.LocallyNameless.Alpha
24+
25+
---- generic structural substitution.
26+
27+
class GSubst b f where
28+
gsubst :: Name b -> b -> f c -> f c
29+
gsubsts :: [(Name b, b)] -> f c -> f c
30+
gsubstBvs :: AlphaCtx -> [b] -> f c -> f c
31+
32+
instance GSubst b f => GSubst b (M1 i c f) where
33+
gsubst nm val = M1 . gsubst nm val . unM1
34+
gsubsts ss = M1 . gsubsts ss . unM1
35+
gsubstBvs c b = M1 . gsubstBvs c b . unM1
36+
37+
instance GSubst b U1 where
38+
gsubst _nm _val _ = U1
39+
gsubsts _ss _ = U1
40+
gsubstBvs _c _b _ = U1
41+
42+
instance GSubst b V1 where
43+
gsubst _nm _val = id
44+
gsubsts _ss = id
45+
gsubstBvs _c _b = id
46+
47+
instance (GSubst b f, GSubst b g) => GSubst b (f :*: g) where
48+
gsubst nm val (f :*: g) = gsubst nm val f :*: gsubst nm val g
49+
gsubsts ss (f :*: g) = gsubsts ss f :*: gsubsts ss g
50+
gsubstBvs c b (f :*: g) = gsubstBvs c b f :*: gsubstBvs c b g
51+
52+
instance (GSubst b f, GSubst b g) => GSubst b (f :+: g) where
53+
gsubst nm val (L1 f) = L1 $ gsubst nm val f
54+
gsubst nm val (R1 g) = R1 $ gsubst nm val g
55+
56+
gsubsts ss (L1 f) = L1 $ gsubsts ss f
57+
gsubsts ss (R1 g) = R1 $ gsubsts ss g
58+
59+
gsubstBvs c b (L1 f) = L1 $ gsubstBvs c b f
60+
gsubstBvs c b (R1 g) = R1 $ gsubstBvs c b g

src/Unbound/Generics/LocallyNameless/Subst.hs

+6-42
Original file line numberDiff line numberDiff line change
@@ -63,13 +63,14 @@ import Unbound.Generics.LocallyNameless.Ignore
6363
import Unbound.Generics.LocallyNameless.Bind
6464
import Unbound.Generics.LocallyNameless.Rebind
6565
import Unbound.Generics.LocallyNameless.Rec
66+
import Unbound.Generics.LocallyNameless.Internal.GSubst
6667

6768
-- | See 'isVar'
6869
data SubstName a b where
6970
SubstName :: (a ~ b) => Name a -> SubstName a b
7071

71-
-- | See 'isCoerceVar'
72-
data SubstCoerce a b where
72+
-- | See 'isCoerceVar'
73+
data SubstCoerce a b where
7374
SubstCoerce :: Name b -> (b -> Maybe a) -> SubstCoerce a b
7475

7576
-- | Immediately substitute for the bound variables of a pattern
@@ -92,7 +93,7 @@ class Subst b a where
9293
isvar :: a -> Maybe (SubstName a b)
9394
isvar _ = Nothing
9495

95-
-- | This is an alternative version to 'isvar', useable in the case
96+
-- | This is an alternative version to 'isvar', useable in the case
9697
-- that the substituted argument doesn't have *exactly* the same type
9798
-- as the term it should be substituted into.
9899
-- The default implementation always returns 'Nothing'.
@@ -118,7 +119,7 @@ class Subst b a where
118119
| all (isFreeName . fst) ss =
119120
case (isvar x :: Maybe (SubstName a b)) of
120121
Just (SubstName m) | Just (_, u) <- find ((==m) . fst) ss -> u
121-
_ -> case isCoerceVar x :: Maybe (SubstCoerce a b) of
122+
_ -> case isCoerceVar x :: Maybe (SubstCoerce a b) of
122123
Just (SubstCoerce m f) | Just (_, u) <- find ((==m) . fst) ss -> maybe x id (f u)
123124
_ -> to $ gsubsts ss (from x)
124125
| otherwise =
@@ -135,48 +136,11 @@ class Subst b a where
135136
Just (SubstName (Bn j k)) | ctxLevel ctx == j, fromInteger k < length bs -> bs !! fromInteger k
136137
_ -> to $ gsubstBvs ctx bs (from x)
137138

138-
---- generic structural substitution.
139-
140-
class GSubst b f where
141-
gsubst :: Name b -> b -> f c -> f c
142-
gsubsts :: [(Name b, b)] -> f c -> f c
143-
gsubstBvs :: AlphaCtx -> [b] -> f c -> f c
144-
145139
instance Subst b c => GSubst b (K1 i c) where
146140
gsubst nm val = K1 . subst nm val . unK1
147141
gsubsts ss = K1 . substs ss . unK1
148142
gsubstBvs ctx b = K1 . substBvs ctx b . unK1
149143

150-
instance GSubst b f => GSubst b (M1 i c f) where
151-
gsubst nm val = M1 . gsubst nm val . unM1
152-
gsubsts ss = M1 . gsubsts ss . unM1
153-
gsubstBvs c b = M1 . gsubstBvs c b . unM1
154-
155-
instance GSubst b U1 where
156-
gsubst _nm _val _ = U1
157-
gsubsts _ss _ = U1
158-
gsubstBvs _c _b _ = U1
159-
160-
instance GSubst b V1 where
161-
gsubst _nm _val = id
162-
gsubsts _ss = id
163-
gsubstBvs _c _b = id
164-
165-
instance (GSubst b f, GSubst b g) => GSubst b (f :*: g) where
166-
gsubst nm val (f :*: g) = gsubst nm val f :*: gsubst nm val g
167-
gsubsts ss (f :*: g) = gsubsts ss f :*: gsubsts ss g
168-
gsubstBvs c b (f :*: g) = gsubstBvs c b f :*: gsubstBvs c b g
169-
170-
instance (GSubst b f, GSubst b g) => GSubst b (f :+: g) where
171-
gsubst nm val (L1 f) = L1 $ gsubst nm val f
172-
gsubst nm val (R1 g) = R1 $ gsubst nm val g
173-
174-
gsubsts ss (L1 f) = L1 $ gsubsts ss f
175-
gsubsts ss (R1 g) = R1 $ gsubsts ss g
176-
177-
gsubstBvs c b (L1 f) = L1 $ gsubstBvs c b f
178-
gsubstBvs c b (R1 g) = R1 $ gsubstBvs c b g
179-
180144
-- these have a Generic instance, but
181145
-- it's self-refential (ie: Rep Int = D1 (C1 (S1 (Rec0 Int))))
182146
-- so our structural GSubst instances get stuck in an infinite loop.
@@ -187,7 +151,7 @@ instance Subst b Char where subst _ _ = id ; substs _ = id ; substBvs _ _ = id
187151
instance Subst b Float where subst _ _ = id ; substs _ = id ; substBvs _ _ = id
188152
instance Subst b Double where subst _ _ = id ; substs _ = id ; substBvs _ _ = id
189153

190-
-- huh, apparently there's no instance Generic Integer.
154+
-- huh, apparently there's no instance Generic Integer.
191155
instance Subst b Integer where subst _ _ = id ; substs _ = id ; substBvs _ _ = id
192156

193157
instance (Subst c a, Subst c b) => Subst c (a,b)

unbound-generics.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -44,6 +44,7 @@ library
4444
Unbound.Generics.LocallyNameless.Operations
4545
Unbound.Generics.LocallyNameless.Unsafe
4646
Unbound.Generics.LocallyNameless.Internal.Fold
47+
Unbound.Generics.LocallyNameless.Internal.GSubst
4748
Unbound.Generics.LocallyNameless.Internal.Iso
4849
Unbound.Generics.LocallyNameless.Internal.Lens
4950
Unbound.Generics.LocallyNameless.Rec

0 commit comments

Comments
 (0)