module Data.Parameterized.Context
(
#ifdef UNSAFE_OPS
module Data.Parameterized.Context.Unsafe
#else
module Data.Parameterized.Context.Safe
#endif
, singleton
, toVector
, pattern (:>)
, pattern Empty
, CtxEmbedding(..)
, ExtendContext(..)
, ExtendContext'(..)
, ApplyEmbedding(..)
, ApplyEmbedding'(..)
, identityEmbedding
, extendEmbeddingRightDiff
, extendEmbeddingRight
, extendEmbeddingBoth
, ctxeSize
, ctxeAssignment
, Idx
, getCtx
, setCtx
, field
, natIndex
, natIndexProxy
, CurryAssignment
, CurryAssignmentClass(..)
) where
import Prelude hiding (null)
import GHC.TypeLits (Nat, type ())
import Control.Lens hiding (Index, view, (:>), Empty)
import qualified Data.Vector as V
import qualified Data.Vector.Mutable as MV
#ifdef UNSAFE_OPS
import Data.Parameterized.Context.Unsafe
#else
import Data.Parameterized.Context.Safe
#endif
import Data.Parameterized.TraversableFC
singleton :: f tp -> Assignment f (EmptyCtx ::> tp)
singleton = (empty :>)
toVector :: Assignment f tps -> (forall tp . f tp -> e) -> V.Vector e
toVector a f = V.create $ do
vm <- MV.new (sizeInt (size a))
forIndexM (size a) $ \i -> do
MV.write vm (indexVal i) (f (a ! i))
return vm
data CtxEmbedding (ctx :: Ctx k) (ctx' :: Ctx k)
= CtxEmbedding { _ctxeSize :: Size ctx'
, _ctxeAssignment :: Assignment (Index ctx') ctx
}
ctxeSize :: Simple Lens (CtxEmbedding ctx ctx') (Size ctx')
ctxeSize = lens _ctxeSize (\s v -> s { _ctxeSize = v })
ctxeAssignment :: Lens (CtxEmbedding ctx1 ctx') (CtxEmbedding ctx2 ctx')
(Assignment (Index ctx') ctx1) (Assignment (Index ctx') ctx2)
ctxeAssignment = lens _ctxeAssignment (\s v -> s { _ctxeAssignment = v })
class ApplyEmbedding (f :: Ctx k -> *) where
applyEmbedding :: CtxEmbedding ctx ctx' -> f ctx -> f ctx'
class ApplyEmbedding' (f :: Ctx k -> k' -> *) where
applyEmbedding' :: CtxEmbedding ctx ctx' -> f ctx v -> f ctx' v
class ExtendContext (f :: Ctx k -> *) where
extendContext :: Diff ctx ctx' -> f ctx -> f ctx'
class ExtendContext' (f :: Ctx k -> k' -> *) where
extendContext' :: Diff ctx ctx' -> f ctx v -> f ctx' v
instance ApplyEmbedding' Index where
applyEmbedding' ctxe idx = (ctxe ^. ctxeAssignment) ! idx
instance ExtendContext' Index where
extendContext' = extendIndex'
identityEmbedding :: Size ctx -> CtxEmbedding ctx ctx
identityEmbedding sz = CtxEmbedding sz (generate sz id)
extendEmbeddingRightDiff :: forall ctx ctx' ctx''.
Diff ctx' ctx''
-> CtxEmbedding ctx ctx'
-> CtxEmbedding ctx ctx''
extendEmbeddingRightDiff diff (CtxEmbedding sz' assgn) = CtxEmbedding (extSize sz' diff) updated
where
updated :: Assignment (Index ctx'') ctx
updated = fmapFC (extendIndex' diff) assgn
extendEmbeddingRight :: CtxEmbedding ctx ctx' -> CtxEmbedding ctx (ctx' ::> tp)
extendEmbeddingRight = extendEmbeddingRightDiff knownDiff
extendEmbeddingBoth :: forall ctx ctx' tp. CtxEmbedding ctx ctx' -> CtxEmbedding (ctx ::> tp) (ctx' ::> tp)
extendEmbeddingBoth ctxe = updated & ctxeAssignment %~ flip extend (nextIndex (ctxe ^. ctxeSize))
where
updated :: CtxEmbedding ctx (ctx' ::> tp)
updated = extendEmbeddingRight ctxe
pattern Empty :: () => ctx ~ EmptyCtx => Assignment f ctx
pattern Empty <- (view -> AssignEmpty)
where Empty = empty
infixl :>
pattern (:>) :: () => ctx' ~ (ctx ::> tp) => Assignment f ctx -> f tp -> Assignment f ctx'
pattern (:>) a v <- (view -> AssignExtend a v)
where a :> v = extend a v
#if MIN_VERSION_base(4,10,0)
#endif
getCtx :: forall n ctx f r. Idx n ctx r => Assignment f ctx -> f r
getCtx asgn = asgn ! natIndex @n
setCtx :: forall n ctx f r. Idx n ctx r => f r -> Assignment f ctx -> Assignment f ctx
setCtx = update (natIndex @n)
field :: forall n ctx f r. Idx n ctx r => Lens' (Assignment f ctx) (f r)
field f = adjustM f (natIndex @n)
type Idx n ctx r = (ValidIx n ctx, Idx' (FromLeft ctx n) ctx r)
natIndex :: forall n ctx r. Idx n ctx r => Index ctx r
natIndex = natIndex' @_ @(FromLeft ctx n)
natIndexProxy :: forall n ctx r proxy. Idx n ctx r => proxy n -> Index ctx r
natIndexProxy _ = natIndex @n
class KnownContext ctx => Idx' (n :: Nat) (ctx :: Ctx k) (r :: k) | n ctx -> r where
natIndex' :: Index ctx r
instance KnownContext xs => Idx' 0 (xs '::> x) x where
natIndex' = lastIndex knownSize
instance (KnownContext xs, Idx' (n1) xs r) =>
Idx' n (xs '::> x) r where
natIndex' = skip (natIndex' @_ @(n1))
type family CurryAssignment (ctx :: Ctx k) (f :: k -> *) (x :: *) :: * where
CurryAssignment EmptyCtx f x = x
CurryAssignment (ctx ::> a) f x = CurryAssignment ctx f (f a -> x)
class CurryAssignmentClass (ctx :: Ctx k) where
curryAssignment :: (Assignment f ctx -> x) -> CurryAssignment ctx f x
uncurryAssignment :: CurryAssignment ctx f x -> (Assignment f ctx -> x)
instance CurryAssignmentClass EmptyCtx where
curryAssignment k = k empty
uncurryAssignment k _ = k
instance CurryAssignmentClass ctx => CurryAssignmentClass (ctx ::> a) where
curryAssignment k = curryAssignment (\asgn a -> k (asgn :> a))
uncurryAssignment k asgn =
case view asgn of
AssignExtend asgn' x -> uncurryAssignment k asgn' x