Skip to content

Commit 0e15158

Browse files
committed
refactor: bring in the infoless
1 parent d68033e commit 0e15158

File tree

4 files changed

+155
-48
lines changed

4 files changed

+155
-48
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.SILId
124+
LambdaBuffers.Compiler.ProtoCompat.InfoLess
125125
LambdaBuffers.Compiler.ProtoCompat.Types
126126
LambdaBuffers.Compiler.TypeClassCheck
127127
LambdaBuffers.Compiler.TypeClassCheck.Compat

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

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,9 +3,9 @@
33
module LambdaBuffers.Compiler.ProtoCompat (
44
module FromProto,
55
module Types,
6-
module SILEq,
6+
module InfoLess,
77
) where
88

99
import LambdaBuffers.Compiler.ProtoCompat.FromProto as FromProto
10-
import LambdaBuffers.Compiler.ProtoCompat.SILEq as SILEq
10+
import LambdaBuffers.Compiler.ProtoCompat.InfoLess as InfoLess
1111
import LambdaBuffers.Compiler.ProtoCompat.Types as Types
Lines changed: 152 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,152 @@
1+
{-# LANGUAGE DefaultSignatures #-}
2+
{-# LANGUAGE UndecidableInstances #-}
3+
4+
module LambdaBuffers.Compiler.ProtoCompat.InfoLess (
5+
InfoLess,
6+
withInfoLess,
7+
withInfoLessF,
8+
mkInfoLess,
9+
) where
10+
11+
import Data.Bifunctor (Bifunctor (bimap))
12+
import Data.Default (Default (def))
13+
import Data.Map qualified as M
14+
import Data.Set qualified as S
15+
import Data.Text (Text)
16+
import Generics.SOP (All2, Generic (Code, from, to), Proxy (..), hcmap, mapII)
17+
import LambdaBuffers.Compiler.ProtoCompat.Types (
18+
ClassDef,
19+
ClassName,
20+
CompilerError,
21+
CompilerInput,
22+
CompilerResult,
23+
ConstrName,
24+
Constraint,
25+
Constructor,
26+
Field,
27+
FieldName,
28+
ForeignClassRef,
29+
ForeignRef,
30+
InferenceErr,
31+
InstanceClause,
32+
Kind,
33+
KindCheckErr,
34+
KindCheckError,
35+
KindRefType,
36+
KindType,
37+
LBName,
38+
LocalClassRef,
39+
LocalRef,
40+
Module,
41+
ModuleName,
42+
ModuleNamePart,
43+
Product,
44+
Record,
45+
SourceInfo,
46+
SourcePosition,
47+
Sum,
48+
Tuple,
49+
Ty,
50+
TyAbs,
51+
TyApp,
52+
TyArg,
53+
TyBody,
54+
TyClassRef,
55+
TyDef,
56+
TyName,
57+
TyRef,
58+
TyVar,
59+
VarName,
60+
defSourceInfo,
61+
)
62+
63+
-- | InfoLess newtype. Constructor is not exported to not allow the construction of types with the Info. InfoLess a can only be constructed via its class instance and deconstructed using the exported function.
64+
newtype InfoLess a = InfoLess {unsafeInfoLess :: a}
65+
deriving stock (Show, Eq, Ord)
66+
deriving stock (Functor, Traversable, Foldable)
67+
68+
{- | SourceInfo Less ID.
69+
A TypeClass that provides id for types with SourceInfo - where SI is defaulted - therefore ignored. Not exported for obvious unsafe reasons.
70+
-}
71+
class Eq a => SILId a where
72+
silId :: a -> a
73+
default silId :: (Generic a, All2 SILId (Code a)) => a -> a
74+
silId = gsilId
75+
76+
-- | Make InfoLess Datatype.
77+
mkInfoLess :: SILId a => a -> InfoLess a
78+
mkInfoLess = InfoLess . silId
79+
80+
gsilId :: (Generic a, All2 SILId (Code a)) => a -> a
81+
gsilId = to . hcmap (Proxy :: Proxy SILId) (mapII silId) . from
82+
83+
-- | Work with Info Less.
84+
withInfoLess :: SILId a => InfoLess a -> (a -> b) -> b
85+
withInfoLess (InfoLess a) f = f . unsafeInfoLess . mkInfoLess $ a
86+
87+
-- | Work with Info Less - functor way.
88+
withInfoLessF :: forall f {a} {b}. SILId a => InfoLess a -> (a -> f b) -> f b
89+
withInfoLessF (InfoLess a) f = f . unsafeInfoLess . mkInfoLess $ a
90+
91+
instance SILId a => SILId [a] where
92+
silId = fmap silId
93+
94+
instance SILId Int where
95+
silId = id
96+
97+
instance SILId Text where
98+
silId = id
99+
100+
instance (Ord k, SILId k, SILId v) => SILId (M.Map k v) where
101+
silId = M.fromList . fmap (bimap silId silId) . M.toList
102+
103+
instance (Ord a, SILId a) => SILId (S.Set a) where
104+
silId = S.fromList . fmap silId . S.toList
105+
106+
instance SILId SourceInfo where
107+
silId = const def
108+
109+
instance Default SourceInfo where
110+
def = defSourceInfo
111+
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

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

Lines changed: 0 additions & 45 deletions
This file was deleted.

0 commit comments

Comments
 (0)