module Data.TypeMap.Internal.Vector where
import Data.Vector (Vector)
import qualified Data.Vector as Vector
import Data.TypeMap.Internal.Unsafe
newtype TypeVector d = TypeVector (Vector Any)
empty :: TypeVector '[]
empty = TypeVector Vector.empty
index
:: forall a d
. KnownNat (Index a d)
=> TypeVector d -> Lookup a d
index = unsafeIndex @a (Vector.!)
cons
:: forall a d b
. b -> TypeVector d -> TypeVector ('(a, b) ': d)
cons = unsafeCons Vector.cons
(<|)
:: forall a d b
. b -> TypeVector d -> TypeVector ('(a, b) ': d)
(<|) = cons
infixr 5 <|, `cons`
snoc
:: forall a d b
. (Last d ~ '(a, b))
=> TypeVector (Init d) -> b -> TypeVector d
snoc = unsafeSnoc @a Vector.snoc
(|>)
:: forall a d b
. (Last d ~ '(a, b))
=> TypeVector (Init d) -> b -> TypeVector d
(|>) = snoc
infixr 5 |>, `snoc`