Skip to content

Commit d68033e

Browse files
committed
rename:
1 parent 8f2cc22 commit d68033e

File tree

4 files changed

+90
-90
lines changed

4 files changed

+90
-90
lines changed

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -121,7 +121,7 @@ library
121121
LambdaBuffers.Compiler.NamingCheck
122122
LambdaBuffers.Compiler.ProtoCompat
123123
LambdaBuffers.Compiler.ProtoCompat.FromProto
124-
LambdaBuffers.Compiler.ProtoCompat.SILEq
124+
LambdaBuffers.Compiler.ProtoCompat.SILId
125125
LambdaBuffers.Compiler.ProtoCompat.Types
126126
LambdaBuffers.Compiler.TypeClassCheck
127127
LambdaBuffers.Compiler.TypeClassCheck.Compat

lambda-buffers-compiler/src/LambdaBuffers/Compiler/ProtoCompat/SILEq.hs

Lines changed: 0 additions & 45 deletions
This file was deleted.
Lines changed: 45 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,45 @@
1+
{-# LANGUAGE DefaultSignatures #-}
2+
{-# LANGUAGE UndecidableInstances #-}
3+
4+
module LambdaBuffers.Compiler.ProtoCompat.SILId (
5+
(=:=),
6+
SILId (silId),
7+
) where
8+
9+
import Data.Bifunctor (Bifunctor (bimap))
10+
import Data.Map qualified as M
11+
import Data.Set qualified as S
12+
import Data.Text (Text)
13+
import Generics.SOP (All2, Generic (Code, from, to), Proxy (..), hcmap, mapII)
14+
15+
{- | SourceInfo Less ID.
16+
A TypeClass that provides id for types with SourceInfo - where SI is defaulted - therefore ignored.
17+
-}
18+
class Eq a => SILId a where
19+
silId :: a -> a
20+
default silId :: (Generic a, All2 SILId (Code a)) => a -> a
21+
silId = gsilId
22+
23+
gsilId :: (Generic a, All2 SILId (Code a)) => a -> a
24+
gsilId = to . hcmap (Proxy :: Proxy SILId) (mapII silId) . from
25+
26+
{- | Equality without SourceInfo.
27+
If the type does not contain SourceInfo then: (==) = (=:=).
28+
-}
29+
(=:=) :: SILId a => a -> a -> Bool
30+
(=:=) a b = silId a == silId b
31+
32+
instance SILId a => SILId [a] where
33+
silId = fmap silId
34+
35+
instance SILId Int where
36+
silId = id
37+
38+
instance SILId Text where
39+
silId = id
40+
41+
instance (Ord k, SILId k, SILId v) => SILId (M.Map k v) where
42+
silId = M.fromList . fmap (bimap silId silId) . M.toList
43+
44+
instance (Ord a, SILId a) => SILId (S.Set a) where
45+
silId = S.fromList . fmap silId . S.toList

0 commit comments

Comments
 (0)