fixed-length-0.2.1: Lists with statically known length based on non-empty package.

Safe HaskellSafe
LanguageHaskell98

Data.FixedLength

Documentation

data T n a Source #

Instances
Natural n => Functor (T n) Source # 
Instance details

Defined in Data.FixedLength

Methods

fmap :: (a -> b) -> T n a -> T n b #

(<$) :: a -> T n b -> T n a #

Natural n => Applicative (T n) Source # 
Instance details

Defined in Data.FixedLength

Methods

pure :: a -> T n a #

(<*>) :: T n (a -> b) -> T n a -> T n b #

liftA2 :: (a -> b -> c) -> T n a -> T n b -> T n c #

(*>) :: T n a -> T n b -> T n b #

(<*) :: T n a -> T n b -> T n a #

Natural n => Foldable (T n) Source # 
Instance details

Defined in Data.FixedLength

Methods

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

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

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

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

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

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

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

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

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

null :: T n a -> Bool #

length :: T n a -> Int #

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

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

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

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

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

Natural n => Traversable (T n) Source # 
Instance details

Defined in Data.FixedLength

Methods

traverse :: Applicative f => (a -> f b) -> T n a -> f (T n b) #

sequenceA :: Applicative f => T n (f a) -> f (T n a) #

mapM :: Monad m => (a -> m b) -> T n a -> m (T n b) #

sequence :: Monad m => T n (m a) -> m (T n a) #

(Natural n, Eq a) => Eq (T n a) Source # 
Instance details

Defined in Data.FixedLength

Methods

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

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

(Natural n, Show a) => Show (T n a) Source # 
Instance details

Defined in Data.FixedLength

Methods

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

show :: T n a -> String #

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

(Natural n, Storable a) => Storable (T n a) Source # 
Instance details

Defined in Data.FixedLength

Methods

sizeOf :: T n a -> Int #

alignment :: T n a -> Int #

peekElemOff :: Ptr (T n a) -> Int -> IO (T n a) #

pokeElemOff :: Ptr (T n a) -> Int -> T n a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (T n a) #

pokeByteOff :: Ptr b -> Int -> T n a -> IO () #

peek :: Ptr (T n a) -> IO (T n a) #

poke :: Ptr (T n a) -> T n a -> IO () #

type family Position n :: * Source #

Instances
type Position Zero Source # 
Instance details

Defined in Data.FixedLength

type Position (Succ n) Source # 
Instance details

Defined in Data.FixedLength

type Position (Succ n) = Succ (Position n)

type family List n :: * -> * Source #

Instances
type List Zero Source # 
Instance details

Defined in Data.FixedLength

type List Zero = T
type List (Succ n) Source # 
Instance details

Defined in Data.FixedLength

type List (Succ n) = T (List n)

type family Length (f :: * -> *) Source #

Instances
type Length T Source # 
Instance details

Defined in Data.FixedLength

type Length T = Zero
type Length (T f) Source # 
Instance details

Defined in Data.FixedLength

type Length (T f) = Succ (Length f)

data Index n Source #

Instances
Natural n => Eq (Index n) Source # 
Instance details

Defined in Data.FixedLength

Methods

(==) :: Index n -> Index n -> Bool #

(/=) :: Index n -> Index n -> Bool #

Natural n => Ord (Index n) Source # 
Instance details

Defined in Data.FixedLength

Methods

compare :: Index n -> Index n -> Ordering #

(<) :: Index n -> Index n -> Bool #

(<=) :: Index n -> Index n -> Bool #

(>) :: Index n -> Index n -> Bool #

(>=) :: Index n -> Index n -> Bool #

max :: Index n -> Index n -> Index n #

min :: Index n -> Index n -> Index n #

data Zero Source #

Instances
Eq Zero Source # 
Instance details

Defined in Data.FixedLength

Methods

(==) :: Zero -> Zero -> Bool #

(/=) :: Zero -> Zero -> Bool #

Ord Zero Source # 
Instance details

Defined in Data.FixedLength

Methods

compare :: Zero -> Zero -> Ordering #

(<) :: Zero -> Zero -> Bool #

(<=) :: Zero -> Zero -> Bool #

(>) :: Zero -> Zero -> Bool #

(>=) :: Zero -> Zero -> Bool #

max :: Zero -> Zero -> Zero #

min :: Zero -> Zero -> Zero #

data Succ pos Source #

Constructors

Stop 
Succ pos 
Instances
Eq pos => Eq (Succ pos) Source # 
Instance details

Defined in Data.FixedLength

Methods

(==) :: Succ pos -> Succ pos -> Bool #

(/=) :: Succ pos -> Succ pos -> Bool #

Ord pos => Ord (Succ pos) Source # 
Instance details

Defined in Data.FixedLength

Methods

compare :: Succ pos -> Succ pos -> Ordering #

(<) :: Succ pos -> Succ pos -> Bool #

(<=) :: Succ pos -> Succ pos -> Bool #

(>) :: Succ pos -> Succ pos -> Bool #

(>=) :: Succ pos -> Succ pos -> Bool #

max :: Succ pos -> Succ pos -> Succ pos #

min :: Succ pos -> Succ pos -> Succ pos #

Show pos => Show (Succ pos) Source # 
Instance details

Defined in Data.FixedLength

Methods

showsPrec :: Int -> Succ pos -> ShowS #

show :: Succ pos -> String #

showList :: [Succ pos] -> ShowS #

toList :: Natural n => T n a -> [a] Source #

showsPrec :: (Natural n, Show a) => Int -> T n a -> ShowS Source #

map :: Natural n => (a -> b) -> T n a -> T n b Source #

zipWith :: Natural n => (a -> b -> c) -> T n a -> T n b -> T n c Source #

sequenceA :: (Applicative f, Natural n) => T n (f a) -> f (T n a) Source #

repeat :: Natural n => a -> T n a Source #

index :: Natural n => Index n -> T n a -> a Source #

update :: Natural n => (a -> a) -> Index n -> T n a -> T n a Source #

indices :: Natural n => T n (Index n) Source #

type GE1 n = Succ n Source #

type GE2 n = Succ (GE1 n) Source #

type GE3 n = Succ (GE2 n) Source #

type GE4 n = Succ (GE3 n) Source #

type GE5 n = Succ (GE4 n) Source #

type GE6 n = Succ (GE5 n) Source #

type GE7 n = Succ (GE6 n) Source #

type GE8 n = Succ (GE7 n) Source #

fromFixedList :: List n a -> T n a Source #

toFixedList :: T n a -> List n a Source #

(!:) :: a -> T n a -> T (Succ n) a infixr 5 Source #

singleton :: a -> T U1 a Source #

viewL :: T (Succ n) a -> (a, T n a) Source #

switchL :: (a -> T n a -> b) -> T (Succ n) a -> b Source #

head :: Positive n => T n a -> a Source #

tail :: T (Succ n) a -> T n a Source #

switchEnd :: b -> T Zero a -> b Source #

type family Curried n a b Source #

Instances
type Curried Zero a b Source # 
Instance details

Defined in Data.FixedLength

type Curried Zero a b = b
type Curried (Succ n) a b Source # 
Instance details

Defined in Data.FixedLength

type Curried (Succ n) a b = a -> Curried n a b

curry :: Natural n => (T n a -> b) -> Curried n a b Source #

uncurry :: Natural n => Curried n a b -> T n a -> b Source #

minimum :: (Positive n, Ord a) => T n a -> a Source #

maximum :: (Positive n, Ord a) => T n a -> a Source #