static-tensor-0.2.0.0: Tensors of statically known size

Copyright(C) 2017 Alexey Vagarenko
LicenseBSD-style (see LICENSE)
MaintainerAlexey Vagarenko (vagarenko@gmail.com)
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.List.Unrolled

Description

This module provides unrollable versions of functions on lists.

Classes in this module are assumed to be closed. You should not create new instances for them.

Synopsis

Documentation

class Append (n :: Nat) where Source #

Append two lists. Type param l is the length of the left list.

Minimal complete definition

append

Methods

append :: [a] -> [a] -> [a] Source #

Instances

Append ((-) n 1) => Append n Source # 

Methods

append :: [a] -> [a] -> [a] Source #

Append 0 Source # 

Methods

append :: [a] -> [a] -> [a] Source #

class Drop (n :: Nat) where Source #

Drop n elements from a list.

Minimal complete definition

drop

Methods

drop :: [a] -> [a] Source #

Instances

Drop ((-) n 1) => Drop n Source # 

Methods

drop :: [a] -> [a] Source #

Drop 0 Source # 

Methods

drop :: [a] -> [a] Source #

class Take (n :: Nat) where Source #

Take n elements from a list

Minimal complete definition

take

Methods

take :: [a] -> [a] Source #

Instances

Take ((-) n 1) => Take n Source # 

Methods

take :: [a] -> [a] Source #

Take 0 Source # 

Methods

take :: [a] -> [a] Source #

splitAt :: forall (n :: Nat) a. (Take n, Drop n) => [a] -> ([a], [a]) Source #

Split list at n-th element.

class ChunksOf (n :: Nat) (c :: Nat) where Source #

Split list into chunks of the given length c. n is length of the list.

Minimal complete definition

chunksOf

Methods

chunksOf :: [a] -> [[a]] Source #

Instances

(Take c, Drop c, ChunksOf ((-) n 1) c) => ChunksOf n c Source # 

Methods

chunksOf :: [a] -> [[a]] Source #

ChunksOf n 0 Source # 

Methods

chunksOf :: [a] -> [[a]] Source #

ChunksOf 0 c Source # 

Methods

chunksOf :: [a] -> [[a]] Source #

ChunksOf 0 0 Source # 

Methods

chunksOf :: [a] -> [[a]] Source #

type family ChunksCount (len :: Nat) (clen :: Nat) where ... Source #

Number of resulting chunks when list of length len split by chunks of length clen.

Equations

ChunksCount 0 _ = 0 
ChunksCount _ 0 = 0 
ChunksCount l c = If (l <=? c) 1 (1 + ChunksCount (l - c) c) 

class Zip (n :: Nat) where Source #

Zip 2 lists together. Type param n is the length of the first list.

Minimal complete definition

zip

Methods

zip :: [a] -> [b] -> [(a, b)] Source #

Instances

Zip ((-) n 1) => Zip n Source # 

Methods

zip :: [a] -> [b] -> [(a, b)] Source #

Zip 0 Source # 

Methods

zip :: [a] -> [b] -> [(a, b)] Source #

class Zip3 (n :: Nat) where Source #

Zip 3 lists together. Type param n is the length of the first list.

Minimal complete definition

zip3

Methods

zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] Source #

Instances

Zip3 ((-) n 1) => Zip3 n Source # 

Methods

zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] Source #

Zip3 0 Source # 

Methods

zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] Source #

class ZipWith (n :: Nat) where Source #

Zip 2 lists together using given function. Type param n is the length of the first list.

Minimal complete definition

zipWith

Methods

zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] Source #

Instances

ZipWith ((-) n 1) => ZipWith n Source # 

Methods

zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] Source #

ZipWith 0 Source # 

Methods

zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] Source #

class Unzip (n :: Nat) where Source #

Unzip a list. Type param n is the length of the list.

Minimal complete definition

unzip

Methods

unzip :: [(a, b)] -> ([a], [b]) Source #

Instances

Unzip ((-) n 1) => Unzip n Source # 

Methods

unzip :: [(a, b)] -> ([a], [b]) Source #

Unzip 0 Source # 

Methods

unzip :: [(a, b)] -> ([a], [b]) Source #

class Filter (n :: Nat) where Source #

Filter list with given predicate. Type param n is the length of the list.

Minimal complete definition

filter

Methods

filter :: (a -> Bool) -> [a] -> [a] Source #

Instances

Filter ((-) n 1) => Filter n Source # 

Methods

filter :: (a -> Bool) -> [a] -> [a] Source #

Filter 0 Source # 

Methods

filter :: (a -> Bool) -> [a] -> [a] Source #

class Map (n :: Nat) where Source #

Apply function to all elements of a list. Type param n is the length of the list.

Minimal complete definition

map

Methods

map :: (a -> b) -> [a] -> [b] Source #

Instances

Map ((-) n 1) => Map n Source # 

Methods

map :: (a -> b) -> [a] -> [b] Source #

Map 0 Source # 

Methods

map :: (a -> b) -> [a] -> [b] Source #

class All (n :: Nat) where Source #

Check if all elements of the list satisfy the predicate. Type param n is the length of the list.

Minimal complete definition

all

Methods

all :: (a -> Bool) -> [a] -> Bool Source #

Instances

All ((-) n 1) => All n Source # 

Methods

all :: (a -> Bool) -> [a] -> Bool Source #

All 0 Source # 

Methods

all :: (a -> Bool) -> [a] -> Bool Source #

class Foldr (n :: Nat) where Source #

Right fold of a list of length n.

Minimal complete definition

foldr

Methods

foldr :: (a -> b -> b) -> b -> [a] -> b Source #

Instances

Foldr ((-) n 1) => Foldr n Source # 

Methods

foldr :: (a -> b -> b) -> b -> [a] -> b Source #

Foldr 0 Source # 

Methods

foldr :: (a -> b -> b) -> b -> [a] -> b Source #

class Foldr1 (n :: Nat) where Source #

Right fold of a list of length n with no base element.

Minimal complete definition

foldr1

Methods

foldr1 :: (a -> a -> a) -> [a] -> a Source #

Instances

Foldr1 ((-) n 1) => Foldr1 n Source # 

Methods

foldr1 :: (a -> a -> a) -> [a] -> a Source #

Foldr1 1 Source # 

Methods

foldr1 :: (a -> a -> a) -> [a] -> a Source #

class Foldl (n :: Nat) where Source #

Left fold of a list of length n.

Minimal complete definition

foldl

Methods

foldl :: (b -> a -> b) -> b -> [a] -> b Source #

Instances

Foldl ((-) n 1) => Foldl n Source # 

Methods

foldl :: (b -> a -> b) -> b -> [a] -> b Source #

Foldl 0 Source # 

Methods

foldl :: (b -> a -> b) -> b -> [a] -> b Source #

class Foldl1 (n :: Nat) where Source #

Right fold of a list of length n with no base element.

Minimal complete definition

foldl1

Methods

foldl1 :: (a -> a -> a) -> [a] -> a Source #

Instances

Foldl1 ((-) n 1) => Foldl1 n Source # 

Methods

foldl1 :: (a -> a -> a) -> [a] -> a Source #

Foldl1 1 Source # 

Methods

foldl1 :: (a -> a -> a) -> [a] -> a Source #

foldMap :: forall (n :: Nat) m a. FoldMap n m => (a -> m) -> [a] -> m Source #

Map each element of the list of length n to a monoid, and combine the results.

type FoldMap (n :: Nat) m = (Monoid m, Foldr n) Source #

Constraint of the foldMap function.

sum :: forall (n :: Nat) a. Sum n a => [a] -> a Source #

Sum of the elements of the list of length n.

type Sum (n :: Nat) a = (Foldr n, Num a) Source #

Constraint of the sum function.

class Replicate (n :: Nat) where Source #

Fill the list of length n with the same values.

Minimal complete definition

replicate

Methods

replicate :: a -> [a] Source #

Instances

Replicate ((-) n 1) => Replicate n Source # 

Methods

replicate :: a -> [a] Source #

Replicate 0 Source # 

Methods

replicate :: a -> [a] Source #

class EnumFromN (n :: Nat) where Source #

Enumeration of length n starting from given value.

Minimal complete definition

enumFromN

Methods

enumFromN Source #

Arguments

:: Num a 
=> a

Starting value.

-> [a] 

Instances

EnumFromN ((-) n 1) => EnumFromN n Source # 

Methods

enumFromN :: Num a => a -> [a] Source #

EnumFromN 0 Source # 

Methods

enumFromN :: Num a => a -> [a] Source #

class EnumFromStepN (n :: Nat) where Source #

Enumeration of length n starting from given value with given step.

Minimal complete definition

enumFromStepN

Methods

enumFromStepN Source #

Arguments

:: Num a 
=> a

Starting value.

-> a

Step.

-> [a] 

Instances

EnumFromStepN ((-) n 1) => EnumFromStepN n Source # 

Methods

enumFromStepN :: Num a => a -> a -> [a] Source #

EnumFromStepN 0 Source # 

Methods

enumFromStepN :: Num a => a -> a -> [a] Source #