basement-0.0.5: Foundation scrap box of array & string

LicenseBSD-style
MaintainerHaskell Foundation
Safe HaskellNone
LanguageHaskell2010

Basement.Sized.Block

Description

A Nat-sized version of Block

Documentation

data BlockN (n :: Nat) a Source #

Instances

(NatWithinBound (CountOf ty) n, KnownNat n, PrimType ty) => TryFrom (Block ty) (BlockN n ty) Source # 

Methods

tryFrom :: Block ty -> Maybe (BlockN n ty) Source #

(NatWithinBound (CountOf ty) n, KnownNat n, PrimType ty) => TryFrom (UArray ty) (BlockN n ty) Source # 

Methods

tryFrom :: UArray ty -> Maybe (BlockN n ty) Source #

(NatWithinBound (CountOf ty) n, KnownNat n, PrimType ty) => TryFrom (Array ty) (BlockN n ty) Source # 

Methods

tryFrom :: Array ty -> Maybe (BlockN n ty) Source #

PrimType a => Eq (BlockN n a) Source # 

Methods

(==) :: BlockN n a -> BlockN n a -> Bool #

(/=) :: BlockN n a -> BlockN n a -> Bool #

(Show a, PrimType a) => Show (BlockN n a) Source # 

Methods

showsPrec :: Int -> BlockN n a -> ShowS #

show :: BlockN n a -> String #

showList :: [BlockN n a] -> ShowS #

NormalForm (BlockN n a) Source # 

Methods

toNormalForm :: BlockN n a -> () Source #

(NatWithinBound Int n, PrimType ty) => From (BlockN n ty) (Array ty) Source # 

Methods

from :: BlockN n ty -> Array ty Source #

(NatWithinBound Int n, PrimType ty) => From (BlockN n ty) (UArray ty) Source # 

Methods

from :: BlockN n ty -> UArray ty Source #

From (BlockN n ty) (Block ty) Source # 

Methods

from :: BlockN n ty -> Block ty Source #

data MutableBlockN (n :: Nat) ty st Source #

toBlockN :: forall n ty. (PrimType ty, KnownNat n, Countable ty n) => Block ty -> Maybe (BlockN n ty) Source #

toBlock :: BlockN n ty -> Block ty Source #

singleton :: PrimType ty => ty -> BlockN 1 ty Source #

replicate :: forall n ty. (KnownNat n, Countable ty n, PrimType ty) => ty -> BlockN n ty Source #

thaw :: (KnownNat n, PrimMonad prim, PrimType ty) => BlockN n ty -> prim (MutableBlockN n ty (PrimState prim)) Source #

freeze :: (PrimMonad prim, PrimType ty, Countable ty n) => MutableBlockN n ty (PrimState prim) -> prim (BlockN n ty) Source #

index :: forall i n ty. PrimType ty => BlockN n ty -> Offset ty -> ty Source #

indexStatic :: forall i n ty. (KnownNat i, CmpNat i n ~ LT, PrimType ty, Offsetable ty i) => BlockN n ty -> ty Source #

map :: (PrimType a, PrimType b) => (a -> b) -> BlockN n a -> BlockN n b Source #

foldl' :: PrimType ty => (a -> ty -> a) -> a -> BlockN n ty -> a Source #

foldr :: PrimType ty => (ty -> a -> a) -> a -> BlockN n ty -> a Source #

cons :: PrimType ty => ty -> BlockN n ty -> BlockN (n + 1) ty Source #

snoc :: PrimType ty => BlockN n ty -> ty -> BlockN (n + 1) ty Source #

elem :: PrimType ty => ty -> BlockN n ty -> Bool Source #

sub :: forall i j n ty. ((i <=? n) ~ True, (j <=? n) ~ True, (i <=? j) ~ True, PrimType ty, KnownNat i, KnownNat j, Offsetable ty i, Offsetable ty j) => BlockN n ty -> BlockN (j - i) ty Source #

uncons :: forall n ty. (CmpNat 0 n ~ LT, PrimType ty, KnownNat n, Offsetable ty n) => BlockN n ty -> (ty, BlockN (n - 1) ty) Source #

unsnoc :: forall n ty. (CmpNat 0 n ~ LT, KnownNat n, PrimType ty, Offsetable ty n) => BlockN n ty -> (BlockN (n - 1) ty, ty) Source #

splitAt :: forall i n ty. (CmpNat i n ~ LT, PrimType ty, KnownNat i, Countable ty i) => BlockN n ty -> (BlockN i ty, BlockN (n - i) ty) Source #

all :: PrimType ty => (ty -> Bool) -> BlockN n ty -> Bool Source #

any :: PrimType ty => (ty -> Bool) -> BlockN n ty -> Bool Source #

find :: PrimType ty => (ty -> Bool) -> BlockN n ty -> Maybe ty Source #

reverse :: PrimType ty => BlockN n ty -> BlockN n ty Source #

sortBy :: PrimType ty => (ty -> ty -> Ordering) -> BlockN n ty -> BlockN n ty Source #

intersperse :: (CmpNat n 1 ~ GT, PrimType ty) => ty -> BlockN n ty -> BlockN ((n + n) - 1) ty Source #