copilot-core-3.3: An intermediate representation for Copilot.
Safe HaskellSafe
LanguageHaskell2010

Copilot.Core.Type.Array

Description

Implementation of an array that uses type literals to store length. No explicit indexing is used for the input data. Supports arbitrary nesting of arrays.

Synopsis

Documentation

data Array (n :: Nat) t Source #

Implementation of an array that uses type literals to store length.

Instances

Instances details
Foldable (Array n) Source # 
Instance details

Defined in Copilot.Core.Type.Array

Methods

fold :: Monoid m => Array n m -> m #

foldMap :: Monoid m => (a -> m) -> Array n a -> m #

foldMap' :: Monoid m => (a -> m) -> Array n a -> m #

foldr :: (a -> b -> b) -> b -> Array n a -> b #

foldr' :: (a -> b -> b) -> b -> Array n a -> b #

foldl :: (b -> a -> b) -> b -> Array n a -> b #

foldl' :: (b -> a -> b) -> b -> Array n a -> b #

foldr1 :: (a -> a -> a) -> Array n a -> a #

foldl1 :: (a -> a -> a) -> Array n a -> a #

toList :: Array n a -> [a] #

null :: Array n a -> Bool #

length :: Array n a -> Int #

elem :: Eq a => a -> Array n a -> Bool #

maximum :: Ord a => Array n a -> a #

minimum :: Ord a => Array n a -> a #

sum :: Num a => Array n a -> a #

product :: Num a => Array n a -> a #

Show t => Show (Array n t) Source # 
Instance details

Defined in Copilot.Core.Type.Array

Methods

showsPrec :: Int -> Array n t -> ShowS #

show :: Array n t -> String #

showList :: [Array n t] -> ShowS #

(Typeable t, Typed t, KnownNat n, Flatten t (InnerType t), Typed (InnerType t)) => Typed (Array n t) Source # 
Instance details

Defined in Copilot.Core.Type

Flatten a b => Flatten (Array n a) b Source #

Flattening of nested arrays.

Instance details

Defined in Copilot.Core.Type.Array

Methods

flatten :: forall (n0 :: Nat). Array n0 (Array n a) -> [b] Source #

array :: forall n t. KnownNat n => [t] -> Array n t Source #

Smart array constructor that only type checks if the length of the given list matches the length of the array at type level.

flatten :: Flatten a b => Array n a -> [b] Source #

Flatten an array to a list.

size :: forall a n b. (Flatten a b, b ~ InnerType a) => Array n a -> Int Source #

Total number of elements in a possibly nested array.

class Flatten a b Source #

Flattening or conversion of arrays to lists.

Minimal complete definition

flatten

Instances

Instances details
Flatten a a Source #

Flattening of plain arrays.

Instance details

Defined in Copilot.Core.Type.Array

Methods

flatten :: forall (n :: Nat). Array n a -> [a] Source #

Flatten a b => Flatten (Array n a) b Source #

Flattening of nested arrays.

Instance details

Defined in Copilot.Core.Type.Array

Methods

flatten :: forall (n0 :: Nat). Array n0 (Array n a) -> [b] Source #

type family InnerType x where ... Source #

Association between an array and the type of the elements it contains.

Equations

InnerType (Array _ x) = InnerType x 
InnerType x = x 

arrayelems :: Array n a -> [a] Source #

Return the elemts of an array.