Safe Haskell | Safe-Infered |
---|
- module Control.Applicative
- module Control.Monad.Logic
- module Prelude
- module Control.Comonad
- module Data.Foldable
- module Data.Monoid
- bool :: x -> x -> Bool -> x
- (<>>=) :: (Functor m, Monad m) => m a -> (a -> m b) -> m a
- (!!) :: (Copeanoid i, Foldable t) => t x -> i -> x
- tail :: MonadLogic m => m x -> m x
- length :: (Peanoid i, Foldable t) => t x -> i
- filter :: MonadPlus m => (x -> Bool) -> m x -> m x
- consA :: Alternative f => x -> f x -> f x
- snocA :: Alternative f => x -> f x -> f x
- liftPair :: Applicative f => (f x, f y) -> f (x, y)
- class Peanoid x where
- class Copeanoid x where
- fair :: MonadLogic m => m (m x) -> m x
- (++) :: MonadPlus m => m a -> m a -> m a
- module Data.Functor.Identity
- iterate :: Alternative f => (x -> x) -> x -> f x
- church :: Copeanoid i => i -> (x -> x) -> x -> x
- unfoldr :: Alternative f => (b -> Maybe (a, b)) -> b -> f a
- convList :: (Alternative f, Foldable t) => t x -> f x
- head :: Foldable t => t x -> x
- drop :: (Copeanoid i, MonadLogic m) => i -> m x -> m x
- take :: (Copeanoid i, MonadLogic m) => i -> m x -> m x
- find :: (Alternative f, Foldable t) => (a -> Bool) -> t a -> f a
- takeWhile :: MonadLogic m => (x -> Bool) -> m x -> m x
- dropWhile :: MonadLogic m => (x -> Bool) -> m x -> m x
- tails :: MonadLogic m => m x -> m (m x)
- findIndex :: (Peanoid i, Alternative f, Foldable t) => (a -> Bool) -> t a -> f i
- module Control.Category
- module Control.Arrow
- option :: Alternative f => x -> f x -> f x
- cycle :: Alternative f => f x -> f x
- mcycle :: Monoid x => x -> x
- repeat :: Alternative f => x -> f x
- replicate :: (Copeanoid i, Alternative f) => i -> x -> f x
- module Data.Traversable
- count :: (Copeanoid i, Applicative f, Alternative g, Traversable g) => i -> f x -> f (g x)
- choice :: (Foldable t, Alternative f) => t (f x) -> f x
- mreplicate :: (Copeanoid i, Monoid x) => i -> x -> x
- (>>==) :: (Functor m, MonadPlus m, Foldable f) => m x -> (x -> f y) -> m y
- groupBy :: (Foldable t, Alternative f, Alternative g) => (a -> a -> Bool) -> t a -> f (g a)
- lefts :: [Either a b] -> [a]
- rights :: [Either a b] -> [b]
- partitionEithers :: [Either a b] -> ([a], [b])
- null :: Foldable t => t x -> Bool
- unnull :: Foldable t => t x -> Bool
- module Data.Bits
- module Data.Int
- module Data.Word
- class Swap f where
- swap :: f x y -> f y x
- data Peano
- atLeast :: Copeanoid i => i -> Peano -> Bool
- (.:) :: (Category cat, Functor f) => cat b c -> f (cat a b) -> f (cat a c)
- (.::) :: (Category cat, Functor f, Functor g) => cat b c -> f (g (cat a b)) -> f (g (cat a c))
- (.:::) :: (Category cat, Functor f, Functor g, Functor h) => cat b c -> f (g (h (cat a b))) -> f (g (h (cat a c)))
- bind2 :: Monad m => (x -> y -> m a) -> m x -> m y -> m a
- bind3 :: Monad m => (x -> y -> z -> m a) -> m x -> m y -> m z -> m a
- (!!!) :: (Copeanoid i, Foldable t, Alternative f) => t x -> i -> f x
- transEnum :: (Enum t, Enum u) => t -> u
- transInt :: (Integral t, Integral u) => t -> u
- low8bits :: (Integral t, Bits t) => t -> Word8
- modifyBit :: Bits a => Bool -> a -> Int -> a
- getBits :: (Bits t, Integral t, Integral u) => Int -> Int -> t -> u
- transPeano :: (Copeanoid i, Peanoid o) => i -> o
- type family Part1M x y :: *
- class Part1 x where
- type family Part2M x y :: *
- class Part1 x => Part2 x where
- type family Part3M x y :: *
- class Part2 x => Part3 x where
- type family Part4M x y :: *
- class Part3 x => Part4 x where
- type family Part5M x y :: *
- class Part4 x => Part5 x where
- type family Part6M x y :: *
- class Part5 x => Part6 x where
- class QuestionMarkOp x y z | x y -> z, x z -> y where
- selectItems :: [x] -> [Bool] -> [x]
- selectBits :: (Bits x, Integral x) => x -> x -> x
- hGetByte :: Handle -> IO Word8
- hPutByte :: Handle -> Word8 -> IO ()
- module System.IO
- (>>=||) :: Monad m => m (a, b) -> (a -> b -> m z) -> m z
- (>>=|||) :: Monad m => m (a, b, c) -> (a -> b -> c -> m z) -> m z
- (>>=|\/) :: Monad m => m (a, b, c, d) -> (a -> b -> c -> d -> m z) -> m z
- (>>=\/) :: Monad m => m (a, b, c, d, e) -> (a -> b -> c -> d -> e -> m z) -> m z
- azero :: (Applicative f, Monoid x) => f x
- aplus :: (Applicative f, Monoid x) => f x -> f x -> f x
- concat :: (MonadPlus m, Foldable f) => m (f x) -> m x
- on :: (b -> b -> c) -> (a -> b) -> a -> a -> c
- sortBy :: (a -> a -> Ordering) -> [a] -> [a]
- sort :: Ord a => [a] -> [a]
- intersperse :: MonadLogic m => x -> m x -> m x
- intersperse' :: MonadLogic m => x -> m x -> m x
- intercalate :: MonadLogic m => m x -> m (m x) -> m x
- stripPrefix :: Eq a => [a] -> [a] -> Maybe [a]
- stripPrefixBy :: (a -> a -> Bool) -> [a] -> [a] -> Maybe [a]
- isPrefixOf :: Eq a => [a] -> [a] -> Bool
- isSuffixOf :: Eq a => [a] -> [a] -> Bool
- isInfixOf :: Eq a => [a] -> [a] -> Bool
- (\\) :: (MonadLogic m, Foldable t, Eq b) => m b -> t b -> m b
- nub :: Eq a => [a] -> [a]
- nubBy :: (a -> a -> Bool) -> [a] -> [a]
- deleteF :: MonadLogic m => (x -> Bool) -> m x -> m x
- delete :: (Eq x, MonadLogic m) => x -> m x -> m x
- group :: (Alternative g, Alternative f, Foldable t, Eq a) => t a -> f (g a)
- insert :: Ord a => a -> [a] -> [a]
- insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a]
- intersect :: Eq a => [a] -> [a] -> [a]
- intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]
- partition :: (a -> Bool) -> [a] -> ([a], [a])
- permutations :: [a] -> [[a]]
- subsequences :: [a] -> [[a]]
- transpose :: [[a]] -> [[a]]
- union :: Eq a => [a] -> [a] -> [a]
- unionBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]
- unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d])
- unzip5 :: [(a, b, c, d, e)] -> ([a], [b], [c], [d], [e])
- unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f])
- unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g])
- zip4 :: [a] -> [b] -> [c] -> [d] -> [(a, b, c, d)]
- zip5 :: [a] -> [b] -> [c] -> [d] -> [e] -> [(a, b, c, d, e)]
- zip6 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [(a, b, c, d, e, f)]
- zip7 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [(a, b, c, d, e, f, g)]
- zipWith4 :: (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e]
- zipWith5 :: (a -> b -> c -> d -> e -> f) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f]
- zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g]
- zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h]
- lcomp :: (Foldable t, Category c) => t (c x x) -> c x x
- rcomp :: (Foldable t, Category c) => t (c x x) -> c x x
- loeb :: (Function a (f b) b, Functor f) => f a -> f b
- class Function f i o | f -> i o where
- ($) :: f -> i -> o
- spanList :: ([a] -> Bool) -> [a] -> ([a], [a])
- breakList :: ([a] -> Bool) -> [a] -> ([a], [a])
- split :: (Alternative f, Eq a) => [a] -> [a] -> f [a]
- replace :: Eq a => [a] -> [a] -> [a] -> [a]
- subIndex :: (Peanoid i, Alternative f, Eq a) => [a] -> [a] -> f i
Documentation
module Control.Applicative
module Control.Monad.Logic
module Prelude
module Control.Comonad
module Data.Foldable
module Data.Monoid
tail :: MonadLogic m => m x -> m xSource
consA :: Alternative f => x -> f x -> f xSource
snocA :: Alternative f => x -> f x -> f xSource
liftPair :: Applicative f => (f x, f y) -> f (x, y)Source
fair :: MonadLogic m => m (m x) -> m xSource
module Data.Functor.Identity
iterate :: Alternative f => (x -> x) -> x -> f xSource
unfoldr :: Alternative f => (b -> Maybe (a, b)) -> b -> f aSource
convList :: (Alternative f, Foldable t) => t x -> f xSource
drop :: (Copeanoid i, MonadLogic m) => i -> m x -> m xSource
take :: (Copeanoid i, MonadLogic m) => i -> m x -> m xSource
find :: (Alternative f, Foldable t) => (a -> Bool) -> t a -> f aSource
takeWhile :: MonadLogic m => (x -> Bool) -> m x -> m xSource
dropWhile :: MonadLogic m => (x -> Bool) -> m x -> m xSource
tails :: MonadLogic m => m x -> m (m x)Source
module Control.Category
module Control.Arrow
option :: Alternative f => x -> f x -> f xSource
cycle :: Alternative f => f x -> f xSource
repeat :: Alternative f => x -> f xSource
replicate :: (Copeanoid i, Alternative f) => i -> x -> f xSource
module Data.Traversable
count :: (Copeanoid i, Applicative f, Alternative g, Traversable g) => i -> f x -> f (g x)Source
choice :: (Foldable t, Alternative f) => t (f x) -> f xSource
mreplicate :: (Copeanoid i, Monoid x) => i -> x -> xSource
groupBy :: (Foldable t, Alternative f, Alternative g) => (a -> a -> Bool) -> t a -> f (g a)Source
partitionEithers :: [Either a b] -> ([a], [b])
module Data.Bits
module Data.Int
module Data.Word
(.::) :: (Category cat, Functor f, Functor g) => cat b c -> f (g (cat a b)) -> f (g (cat a c))Source
(.:::) :: (Category cat, Functor f, Functor g, Functor h) => cat b c -> f (g (h (cat a b))) -> f (g (h (cat a c)))Source
(!!!) :: (Copeanoid i, Foldable t, Alternative f) => t x -> i -> f xSource
transPeano :: (Copeanoid i, Peanoid o) => i -> oSource
class QuestionMarkOp x y z | x y -> z, x z -> y whereSource
QuestionMarkOp Bool (a, a) a | |
QuestionMarkOp Ordering (a, a, a) a | |
QuestionMarkOp [x] (a, x -> [x] -> a) a | |
QuestionMarkOp (Maybe x) (a, x -> a) a | |
QuestionMarkOp (Identity x) (x -> a) a | |
QuestionMarkOp (Either l r) (l -> a, r -> a) a | |
QuestionMarkOp (x, y) (x -> y -> a) a | |
QuestionMarkOp (x, y, z) (x -> y -> z -> a) a |
selectItems :: [x] -> [Bool] -> [x]Source
selectBits :: (Bits x, Integral x) => x -> x -> xSource
module System.IO
azero :: (Applicative f, Monoid x) => f xSource
aplus :: (Applicative f, Monoid x) => f x -> f x -> f xSource
on :: (b -> b -> c) -> (a -> b) -> a -> a -> c
intersperse :: MonadLogic m => x -> m x -> m xSource
intersperse' :: MonadLogic m => x -> m x -> m xSource
intercalate :: MonadLogic m => m x -> m (m x) -> m xSource
stripPrefix :: Eq a => [a] -> [a] -> Maybe [a]
The stripPrefix
function drops the given prefix from a list.
It returns Nothing
if the list did not start with the prefix
given, or Just
the list after the prefix, if it does.
stripPrefix "foo" "foobar" == Just "bar" stripPrefix "foo" "foo" == Just "" stripPrefix "foo" "barfoo" == Nothing stripPrefix "foo" "barfoobaz" == Nothing
stripPrefixBy :: (a -> a -> Bool) -> [a] -> [a] -> Maybe [a]Source
isPrefixOf :: Eq a => [a] -> [a] -> Bool
The isPrefixOf
function takes two lists and returns True
iff the first list is a prefix of the second.
isSuffixOf :: Eq a => [a] -> [a] -> Bool
The isSuffixOf
function takes two lists and returns True
iff the first list is a suffix of the second.
Both lists must be finite.
(\\) :: (MonadLogic m, Foldable t, Eq b) => m b -> t b -> m bSource
deleteF :: MonadLogic m => (x -> Bool) -> m x -> m xSource
delete :: (Eq x, MonadLogic m) => x -> m x -> m xSource
group :: (Alternative g, Alternative f, Foldable t, Eq a) => t a -> f (g a)Source
insert :: Ord a => a -> [a] -> [a]
The insert
function takes an element and a list and inserts the
element into the list at the last position where it is still less
than or equal to the next element. In particular, if the list
is sorted before the call, the result will also be sorted.
It is a special case of insertBy
, which allows the programmer to
supply their own comparison function.
intersect :: Eq a => [a] -> [a] -> [a]
The intersect
function takes the list intersection of two lists.
For example,
[1,2,3,4] `intersect` [2,4,6,8] == [2,4]
If the first list contains duplicates, so will the result.
[1,2,2,3,4] `intersect` [6,4,4,2] == [2,2,4]
It is a special case of intersectBy
, which allows the programmer to
supply their own equality test.
intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]
The intersectBy
function is the non-overloaded version of intersect
.
partition :: (a -> Bool) -> [a] -> ([a], [a])
The partition
function takes a predicate a list and returns
the pair of lists of elements which do and do not satisfy the
predicate, respectively; i.e.,
partition p xs == (filter p xs, filter (not . p) xs)
permutations :: [a] -> [[a]]
The permutations
function returns the list of all permutations of the argument.
permutations "abc" == ["abc","bac","cba","bca","cab","acb"]
subsequences :: [a] -> [[a]]
The subsequences
function returns the list of all subsequences of the argument.
subsequences "abc" == ["","a","b","ab","c","ac","bc","abc"]
transpose :: [[a]] -> [[a]]
The transpose
function transposes the rows and columns of its argument.
For example,
transpose [[1,2,3],[4,5,6]] == [[1,4],[2,5],[3,6]]
union :: Eq a => [a] -> [a] -> [a]
The union
function returns the list union of the two lists.
For example,
"dog" `union` "cow" == "dogcw"
Duplicates, and elements of the first list, are removed from the
the second list, but if the first list contains duplicates, so will
the result.
It is a special case of unionBy
, which allows the programmer to supply
their own equality test.
unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d])
unzip5 :: [(a, b, c, d, e)] -> ([a], [b], [c], [d], [e])
unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f])
unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g])
zip4 :: [a] -> [b] -> [c] -> [d] -> [(a, b, c, d)]
zip5 :: [a] -> [b] -> [c] -> [d] -> [e] -> [(a, b, c, d, e)]
zip6 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [(a, b, c, d, e, f)]
zip7 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [(a, b, c, d, e, f, g)]
zipWith4 :: (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e]
zipWith5 :: (a -> b -> c -> d -> e -> f) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f]
zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g]
zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h]
class Function f i o | f -> i o whereSource
Function f i o => Function [f] [i] [o] | |
Function (i -> o) i o | |
(Function f1 i1 o, Function f2 i2 o) => Function (Either f1 f2) (i1, i2) o | |
(Function f1 i1 o1, Function f2 i2 o2) => Function (f1, f2) (i1, i2) (o1, o2) | |
Function (Kleisli m i o) i (m o) | |
(Function f1 i1 o1, Function f2 i2 o2, Function f3 i3 o3) => Function (f1, f2, f3) (i1, i2, i3) (o1, o2, o3) |
split :: (Alternative f, Eq a) => [a] -> [a] -> f [a]Source
subIndex :: (Peanoid i, Alternative f, Eq a) => [a] -> [a] -> f iSource