Skip to content

Commit 621a263

Browse files
committed
rename: InfoLessC
1 parent 0e15158 commit 621a263

File tree

2 files changed

+60
-103
lines changed

2 files changed

+60
-103
lines changed

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

Lines changed: 56 additions & 54 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-# LANGUAGE DefaultSignatures #-}
22
{-# LANGUAGE UndecidableInstances #-}
3+
{-# OPTIONS_GHC -Wno-orphans #-}
34

45
module LambdaBuffers.Compiler.ProtoCompat.InfoLess (
56
InfoLess,
@@ -68,85 +69,86 @@ newtype InfoLess a = InfoLess {unsafeInfoLess :: a}
6869
{- | SourceInfo Less ID.
6970
A TypeClass that provides id for types with SourceInfo - where SI is defaulted - therefore ignored. Not exported for obvious unsafe reasons.
7071
-}
71-
class Eq a => SILId a where
72+
class Eq a => InfoLessC a where
7273
silId :: a -> a
73-
default silId :: (Generic a, All2 SILId (Code a)) => a -> a
74+
default silId :: (Generic a, All2 InfoLessC (Code a)) => a -> a
7475
silId = gsilId
7576

7677
-- | Make InfoLess Datatype.
77-
mkInfoLess :: SILId a => a -> InfoLess a
78+
mkInfoLess :: InfoLessC a => a -> InfoLess a
7879
mkInfoLess = InfoLess . silId
7980

80-
gsilId :: (Generic a, All2 SILId (Code a)) => a -> a
81-
gsilId = to . hcmap (Proxy :: Proxy SILId) (mapII silId) . from
81+
gsilId :: (Generic a, All2 InfoLessC (Code a)) => a -> a
82+
gsilId = to . hcmap (Proxy :: Proxy InfoLessC) (mapII silId) . from
8283

8384
-- | Work with Info Less.
84-
withInfoLess :: SILId a => InfoLess a -> (a -> b) -> b
85+
withInfoLess :: InfoLessC a => InfoLess a -> (a -> b) -> b
8586
withInfoLess (InfoLess a) f = f . unsafeInfoLess . mkInfoLess $ a
8687

8788
-- | Work with Info Less - functor way.
88-
withInfoLessF :: forall f {a} {b}. SILId a => InfoLess a -> (a -> f b) -> f b
89+
withInfoLessF :: forall f {a} {b}. InfoLessC a => InfoLess a -> (a -> f b) -> f b
8990
withInfoLessF (InfoLess a) f = f . unsafeInfoLess . mkInfoLess $ a
9091

91-
instance SILId a => SILId [a] where
92+
instance InfoLessC a => InfoLessC [a] where
9293
silId = fmap silId
9394

94-
instance SILId Int where
95+
instance InfoLessC Int where
9596
silId = id
9697

97-
instance SILId Text where
98+
instance InfoLessC Text where
9899
silId = id
99100

100-
instance (Ord k, SILId k, SILId v) => SILId (M.Map k v) where
101+
instance (Ord k, InfoLessC k, InfoLessC v) => InfoLessC (M.Map k v) where
102+
silId :: forall k v. (Ord k, InfoLessC k, InfoLessC v) => M.Map k v -> M.Map k v
101103
silId = M.fromList . fmap (bimap silId silId) . M.toList
102104

103-
instance (Ord a, SILId a) => SILId (S.Set a) where
105+
instance (Ord a, InfoLessC a) => InfoLessC (S.Set a) where
104106
silId = S.fromList . fmap silId . S.toList
105107

106-
instance SILId SourceInfo where
108+
instance InfoLessC SourceInfo where
107109
silId = const def
108110

109111
instance Default SourceInfo where
110112
def = defSourceInfo
111113

112-
instance SILId SourcePosition
113-
instance SILId LBName
114-
instance SILId TyName
115-
instance SILId ConstrName
116-
instance SILId ModuleName
117-
instance SILId ModuleNamePart
118-
instance SILId VarName
119-
instance SILId FieldName
120-
instance SILId ClassName
121-
instance SILId Kind
122-
instance SILId KindType
123-
instance SILId KindRefType
124-
instance SILId TyVar
125-
instance SILId Ty
126-
instance SILId TyApp
127-
instance SILId ForeignRef
128-
instance SILId LocalRef
129-
instance SILId TyRef
130-
instance SILId TyDef
131-
instance SILId TyAbs
132-
instance SILId TyArg
133-
instance SILId TyBody
134-
instance SILId Constructor
135-
instance SILId Sum
136-
instance SILId Field
137-
instance SILId Record
138-
instance SILId Tuple
139-
instance SILId Product
140-
instance SILId ForeignClassRef
141-
instance SILId LocalClassRef
142-
instance SILId TyClassRef
143-
instance SILId ClassDef
144-
instance SILId InstanceClause
145-
instance SILId Constraint
146-
instance SILId Module
147-
instance SILId InferenceErr
148-
instance SILId KindCheckErr
149-
instance SILId CompilerInput
150-
instance SILId KindCheckError
151-
instance SILId CompilerError
152-
instance SILId CompilerResult
114+
instance InfoLessC SourcePosition
115+
instance InfoLessC LBName
116+
instance InfoLessC TyName
117+
instance InfoLessC ConstrName
118+
instance InfoLessC ModuleName
119+
instance InfoLessC ModuleNamePart
120+
instance InfoLessC VarName
121+
instance InfoLessC FieldName
122+
instance InfoLessC ClassName
123+
instance InfoLessC Kind
124+
instance InfoLessC KindType
125+
instance InfoLessC KindRefType
126+
instance InfoLessC TyVar
127+
instance InfoLessC Ty
128+
instance InfoLessC TyApp
129+
instance InfoLessC ForeignRef
130+
instance InfoLessC LocalRef
131+
instance InfoLessC TyRef
132+
instance InfoLessC TyDef
133+
instance InfoLessC TyAbs
134+
instance InfoLessC TyArg
135+
instance InfoLessC TyBody
136+
instance InfoLessC Constructor
137+
instance InfoLessC Sum
138+
instance InfoLessC Field
139+
instance InfoLessC Record
140+
instance InfoLessC Tuple
141+
instance InfoLessC Product
142+
instance InfoLessC ForeignClassRef
143+
instance InfoLessC LocalClassRef
144+
instance InfoLessC TyClassRef
145+
instance InfoLessC ClassDef
146+
instance InfoLessC InstanceClause
147+
instance InfoLessC Constraint
148+
instance InfoLessC Module
149+
instance InfoLessC InferenceErr
150+
instance InfoLessC KindCheckErr
151+
instance InfoLessC CompilerInput
152+
instance InfoLessC KindCheckError
153+
instance InfoLessC CompilerError
154+
instance InfoLessC CompilerResult

0 commit comments

Comments
 (0)