11{-# LANGUAGE TypeFamilies #-}
22
3+ -- | An abstraction of the monoidal LSM API, instantiated by both the real
4+ -- implementation and a model (see "Database.LSMTree.Model.IO.Monoidal").
35module Database.LSMTree.Class.Monoidal (
4- IsSession (.. )
6+ C
7+ , C_
8+ , IsSession (.. )
59 , SessionArgs (.. )
610 , withSession
711 , IsTableHandle (.. )
@@ -10,21 +14,25 @@ module Database.LSMTree.Class.Monoidal (
1014 , withTableDuplicate
1115 , withTableMerge
1216 , withCursor
17+ , module Types
1318 ) where
1419
1520import Control.Monad.Class.MonadThrow (MonadThrow (.. ))
1621import Data.Kind (Constraint , Type )
1722import Data.Typeable (Proxy (Proxy ), Typeable )
1823import qualified Data.Vector as V
24+ import Data.Void (Void )
1925import Database.LSMTree.Class.Normal (IsSession (.. ),
2026 SessionArgs (.. ), withSession )
21- import Database.LSMTree.Common (IOLike , Labellable (.. ), Range (.. ),
22- SerialiseKey , SerialiseValue , SnapshotName )
23- import qualified Database.LSMTree.ModelIO.Monoidal as M
24- import Database.LSMTree.Monoidal (LookupResult (.. ), QueryResult (.. ),
25- ResolveValue , Update (.. ))
27+ import Database.LSMTree.Common as Types (IOLike , Labellable (.. ),
28+ Range (.. ), SerialiseKey , SerialiseValue , SnapshotName )
29+ import Database.LSMTree.Monoidal as Types (LookupResult (.. ),
30+ QueryResult (.. ), ResolveValue , Update (.. ))
2631import qualified Database.LSMTree.Monoidal as R
2732
33+ -- | Model-specific constraints
34+ type C k v blob = (C_ k , C_ v , C_ blob )
35+ type C_ a = (Show a , Eq a , Typeable a )
2836
2937-- | Class abstracting over table handle operations.
3038--
@@ -35,13 +43,17 @@ class (IsSession (Session h)) => IsTableHandle h where
3543 type Cursor h :: (Type -> Type ) -> Type -> Type -> Type
3644
3745 new ::
38- IOLike m
46+ ( IOLike m
47+ , C k v Void
48+ )
3949 => Session h m
4050 -> TableConfig h
4151 -> m (h m k v )
4252
4353 close ::
44- IOLike m
54+ ( IOLike m
55+ , C k v Void
56+ )
4557 => h m k v
4658 -> m ()
4759
@@ -50,6 +62,7 @@ class (IsSession (Session h)) => IsTableHandle h where
5062 , ResolveValue v
5163 , SerialiseKey k
5264 , SerialiseValue v
65+ , C k v Void
5366 )
5467 => h m k v
5568 -> V. Vector k
@@ -60,6 +73,7 @@ class (IsSession (Session h)) => IsTableHandle h where
6073 , ResolveValue v
6174 , SerialiseKey k
6275 , SerialiseValue v
76+ , C k v Void
6377 )
6478 => h m k v
6579 -> Range k
@@ -68,13 +82,16 @@ class (IsSession (Session h)) => IsTableHandle h where
6882 newCursor ::
6983 ( IOLike m
7084 , SerialiseKey k
85+ , C k v Void
7186 )
7287 => Maybe k
7388 -> h m k v
7489 -> m (Cursor h m k v )
7590
7691 closeCursor ::
77- IOLike m
92+ ( IOLike m
93+ , C k v Void
94+ )
7895 => proxy h
7996 -> Cursor h m k v
8097 -> m ()
@@ -84,6 +101,7 @@ class (IsSession (Session h)) => IsTableHandle h where
84101 , ResolveValue v
85102 , SerialiseKey k
86103 , SerialiseValue v
104+ , C k v Void
87105 )
88106 => proxy h
89107 -> Int
@@ -95,6 +113,7 @@ class (IsSession (Session h)) => IsTableHandle h where
95113 , SerialiseKey k
96114 , SerialiseValue v
97115 , ResolveValue v
116+ , C k v Void
98117 )
99118 => h m k v
100119 -> V. Vector (k , Update v )
@@ -105,6 +124,7 @@ class (IsSession (Session h)) => IsTableHandle h where
105124 , SerialiseKey k
106125 , SerialiseValue v
107126 , ResolveValue v
127+ , C k v Void
108128 )
109129 => h m k v
110130 -> V. Vector (k , v )
@@ -115,6 +135,7 @@ class (IsSession (Session h)) => IsTableHandle h where
115135 , SerialiseKey k
116136 , SerialiseValue v
117137 , ResolveValue v
138+ , C k v Void
118139 )
119140 => h m k v
120141 -> V. Vector k
@@ -125,6 +146,7 @@ class (IsSession (Session h)) => IsTableHandle h where
125146 , SerialiseKey k
126147 , SerialiseValue v
127148 , ResolveValue v
149+ , C k v Void
128150 )
129151 => h m k v
130152 -> V. Vector (k , v )
@@ -136,8 +158,7 @@ class (IsSession (Session h)) => IsTableHandle h where
136158 , ResolveValue v
137159 , SerialiseKey k
138160 , SerialiseValue v
139- -- Model-specific constraints
140- , Typeable k , Typeable v
161+ , C k v Void
141162 )
142163 => SnapshotName
143164 -> h m k v
@@ -148,22 +169,24 @@ class (IsSession (Session h)) => IsTableHandle h where
148169 , Labellable (k , v )
149170 , SerialiseKey k
150171 , SerialiseValue v
151- -- Model-specific constraints
152- , Typeable k , Typeable v
172+ , C k v Void
153173 )
154174 => Session h m
155175 -> SnapshotName
156176 -> m (h m k v )
157177
158178 duplicate ::
159- IOLike m
179+ ( IOLike m
180+ , C k v Void
181+ )
160182 => h m k v
161183 -> m (h m k v )
162184
163185 merge ::
164186 ( IOLike m
165187 , ResolveValue v
166188 , SerialiseValue v
189+ , C k v Void
167190 )
168191 => h m k v
169192 -> h m k v
@@ -172,6 +195,7 @@ class (IsSession (Session h)) => IsTableHandle h where
172195withTableNew :: forall h m k v a .
173196 ( IOLike m
174197 , IsTableHandle h
198+ , C k v Void
175199 )
176200 => Session h m
177201 -> TableConfig h
@@ -185,7 +209,7 @@ withTableOpen :: forall h m k v a.
185209 , SerialiseKey k
186210 , SerialiseValue v
187211 , Labellable (k , v )
188- , Typeable k , Typeable v
212+ , C k v Void
189213 )
190214 => Session h m
191215 -> SnapshotName
@@ -196,6 +220,7 @@ withTableOpen sesh snap = bracket (open sesh snap) close
196220withTableDuplicate :: forall h m k v a .
197221 ( IOLike m
198222 , IsTableHandle h
223+ , C k v Void
199224 )
200225 => h m k v
201226 -> (h m k v -> m a )
@@ -207,6 +232,7 @@ withTableMerge :: forall h m k v a.
207232 , IsTableHandle h
208233 , SerialiseValue v
209234 , ResolveValue v
235+ , C k v Void
210236 )
211237 => h m k v
212238 -> h m k v
@@ -218,42 +244,14 @@ withCursor :: forall h m k v a.
218244 ( IOLike m
219245 , IsTableHandle h
220246 , SerialiseKey k
247+ , C k v Void
221248 )
222249 => Maybe k
223250 -> h m k v
224251 -> (Cursor h m k v -> m a )
225252 -> m a
226253withCursor offset hdl = bracket (newCursor offset hdl) (closeCursor (Proxy @ h ))
227254
228- {- ------------------------------------------------------------------------------
229- Model instance
230- -------------------------------------------------------------------------------}
231-
232- instance IsTableHandle M. TableHandle where
233- type Session M. TableHandle = M. Session
234- type TableConfig M. TableHandle = M. TableConfig
235- type Cursor M. TableHandle = M. Cursor
236-
237- new = M. new
238- close = M. close
239- lookups = flip M. lookups
240- updates = flip M. updates
241- inserts = flip M. inserts
242- deletes = flip M. deletes
243- mupserts = flip M. mupserts
244-
245- rangeLookup = flip M. rangeLookup
246-
247- newCursor = M. newCursor
248- closeCursor _ = M. closeCursor
249- readCursor _ = M. readCursor
250-
251- snapshot = M. snapshot
252- open = M. open
253-
254- duplicate = M. duplicate
255- merge = M. merge
256-
257255{- ------------------------------------------------------------------------------
258256 Real instance
259257-------------------------------------------------------------------------------}
0 commit comments