prelude-generalize-0.4: Another kind of alternate Prelude file

Safe HaskellSafe-Infered

Prelude.Generalize

Synopsis

Documentation

module Prelude

bool :: x -> x -> Bool -> xSource

(<>>=) :: (Functor m, Monad m) => m a -> (a -> m b) -> m aSource

(!!) :: (Copeanoid i, Foldable t) => t x -> i -> xSource

tail :: MonadLogic m => m x -> m xSource

length :: (Peanoid i, Foldable t) => t x -> iSource

filter :: MonadPlus m => (x -> Bool) -> 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

(++) :: MonadPlus m => m a -> m a -> m aSource

iterate :: Alternative f => (x -> x) -> x -> f xSource

church :: Copeanoid i => i -> (x -> x) -> x -> xSource

unfoldr :: Alternative f => (b -> Maybe (a, b)) -> b -> f aSource

convList :: (Alternative f, Foldable t) => t x -> f xSource

head :: Foldable t => t x -> 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

findIndex :: (Peanoid i, Alternative f, Foldable t) => (a -> Bool) -> t a -> f iSource

option :: Alternative f => x -> f x -> f xSource

cycle :: Alternative f => f x -> f xSource

mcycle :: Monoid x => x -> xSource

repeat :: Alternative f => x -> f xSource

replicate :: (Copeanoid i, Alternative f) => i -> x -> f xSource

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

(>>==) :: (Functor m, MonadPlus m, Foldable f) => m x -> (x -> f y) -> m ySource

groupBy :: (Foldable t, Alternative f, Alternative g) => (a -> a -> Bool) -> t a -> f (g a)Source

lefts :: [Either a b] -> [a]

Extracts from a list of Either all the Left elements All the Left elements are extracted in order.

rights :: [Either a b] -> [b]

Extracts from a list of Either all the Right elements All the Right elements are extracted in order.

partitionEithers :: [Either a b] -> ([a], [b])

Partitions a list of Either into two lists All the Left elements are extracted, in order, to the first component of the output. Similarly the Right elements are extracted to the second component of the output.

null :: Foldable t => t x -> BoolSource

unnull :: Foldable t => t x -> BoolSource

module Data.Bits

module Data.Int

module Data.Word

class Swap f whereSource

Methods

swap :: f x y -> f y xSource

Instances

(.:) :: (Category cat, Functor f) => cat b c -> f (cat a b) -> f (cat a c)Source

(.::) :: (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

bind2 :: Monad m => (x -> y -> m a) -> m x -> m y -> m aSource

bind3 :: Monad m => (x -> y -> z -> m a) -> m x -> m y -> m z -> m aSource

(!!!) :: (Copeanoid i, Foldable t, Alternative f) => t x -> i -> f xSource

transEnum :: (Enum t, Enum u) => t -> uSource

transInt :: (Integral t, Integral u) => t -> uSource

low8bits :: (Integral t, Bits t) => t -> Word8Source

modifyBit :: Bits a => Bool -> a -> Int -> aSource

getBits :: (Bits t, Integral t, Integral u) => Int -> Int -> t -> uSource

transPeano :: (Copeanoid i, Peanoid o) => i -> oSource

type family Part1M x y :: *Source

class Part1 x whereSource

Associated Types

type Part1T x :: *Source

Methods

get1 :: x -> Part1T xSource

map1 :: (Part1T x -> y) -> x -> Part1M x ySource

Instances

Part1 (x, y) 
Part1 (a, b, c) 
Part1 (a, b, c, d) 
Part1 (a, b, c, d, e) 

type family Part2M x y :: *Source

class Part1 x => Part2 x whereSource

Associated Types

type Part2T x :: *Source

Methods

get2 :: x -> Part2T xSource

map2 :: (Part2T x -> y) -> x -> Part2M x ySource

Instances

Part2 (x, y) 
Part2 (a, b, c) 
Part2 (a, b, c, d) 
Part2 (a, b, c, d, e) 

type family Part3M x y :: *Source

class Part2 x => Part3 x whereSource

Associated Types

type Part3T x :: *Source

Methods

get3 :: x -> Part3T xSource

map3 :: (Part3T x -> y) -> x -> Part3M x ySource

Instances

Part3 (a, b, c) 
Part3 (a, b, c, d) 
Part3 (a, b, c, d, e) 

type family Part4M x y :: *Source

class Part3 x => Part4 x whereSource

Associated Types

type Part4T x :: *Source

Methods

get4 :: x -> Part4T xSource

map4 :: (Part4T x -> y) -> x -> Part4M x ySource

Instances

Part4 (a, b, c, d) 
Part4 (a, b, c, d, e) 

type family Part5M x y :: *Source

class Part4 x => Part5 x whereSource

Associated Types

type Part5T x :: *Source

Methods

get5 :: x -> Part5T xSource

map5 :: (Part5T x -> y) -> x -> Part5M x ySource

Instances

Part5 (a, b, c, d, e) 

type family Part6M x y :: *Source

class Part5 x => Part6 x whereSource

Associated Types

type Part6T x :: *Source

Methods

get6 :: x -> Part6T xSource

map6 :: (Part6T x -> y) -> x -> Part6M x ySource

class QuestionMarkOp x y z | x y -> z, x z -> y whereSource

Methods

(?) :: x -> y -> zSource

idQMO :: x ~ z => ySource

Instances

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

(>>=||) :: Monad m => m (a, b) -> (a -> b -> m z) -> m zSource

(>>=|||) :: Monad m => m (a, b, c) -> (a -> b -> c -> m z) -> m zSource

(>>=|\/) :: Monad m => m (a, b, c, d) -> (a -> b -> c -> d -> m z) -> m zSource

(>>=\/) :: Monad m => m (a, b, c, d, e) -> (a -> b -> c -> d -> e -> m z) -> m zSource

azero :: (Applicative f, Monoid x) => f xSource

aplus :: (Applicative f, Monoid x) => f x -> f x -> f xSource

concat :: (MonadPlus m, Foldable f) => m (f x) -> m xSource

on :: (b -> b -> c) -> (a -> b) -> a -> a -> c

(*) `on` f = \x y -> f x * f y.

Typical usage: sortBy (compare `on` fst).

Algebraic properties:

  • (*) `on` id = (*) (if (*) ∉ {⊥, const ⊥})
  • ((*) `on` f) `on` g = (*) `on` (f . g)
  • flip on f . flip on g = flip on (g . f)

sortBy :: (a -> a -> Ordering) -> [a] -> [a]

The sortBy function is the non-overloaded version of sort.

sort :: Ord a => [a] -> [a]

The sort function implements a stable sorting algorithm. It is a special case of sortBy, which allows the programmer to supply their own comparison function.

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.

isInfixOf :: Eq a => [a] -> [a] -> Bool

The isInfixOf function takes two lists and returns True iff the first list is contained, wholly and intact, anywhere within the second.

Example:

isInfixOf "Haskell" "I really like Haskell." == True
isInfixOf "Ial" "I really like Haskell." == False

(\\) :: (MonadLogic m, Foldable t, Eq b) => m b -> t b -> m bSource

nub :: Eq a => [a] -> [a]

O(n^2). The nub function removes duplicate elements from a list. In particular, it keeps only the first occurrence of each element. (The name nub means `essence'.) It is a special case of nubBy, which allows the programmer to supply their own equality test.

nubBy :: (a -> a -> Bool) -> [a] -> [a]

The nubBy function behaves just like nub, except it uses a user-supplied equality predicate instead of the overloaded == function.

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.

insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a]

The non-overloaded version of insert.

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.

unionBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]

The unionBy function is the non-overloaded version of union.

unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d])

The unzip4 function takes a list of quadruples and returns four lists, analogous to unzip.

unzip5 :: [(a, b, c, d, e)] -> ([a], [b], [c], [d], [e])

The unzip5 function takes a list of five-tuples and returns five lists, analogous to unzip.

unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f])

The unzip6 function takes a list of six-tuples and returns six lists, analogous to unzip.

unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g])

The unzip7 function takes a list of seven-tuples and returns seven lists, analogous to unzip.

zip4 :: [a] -> [b] -> [c] -> [d] -> [(a, b, c, d)]

The zip4 function takes four lists and returns a list of quadruples, analogous to zip.

zip5 :: [a] -> [b] -> [c] -> [d] -> [e] -> [(a, b, c, d, e)]

The zip5 function takes five lists and returns a list of five-tuples, analogous to zip.

zip6 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [(a, b, c, d, e, f)]

The zip6 function takes six lists and returns a list of six-tuples, analogous to zip.

zip7 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [(a, b, c, d, e, f, g)]

The zip7 function takes seven lists and returns a list of seven-tuples, analogous to zip.

zipWith4 :: (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e]

The zipWith4 function takes a function which combines four elements, as well as four lists and returns a list of their point-wise combination, analogous to zipWith.

zipWith5 :: (a -> b -> c -> d -> e -> f) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f]

The zipWith5 function takes a function which combines five elements, as well as five lists and returns a list of their point-wise combination, analogous to zipWith.

zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g]

The zipWith6 function takes a function which combines six elements, as well as six lists and returns a list of their point-wise combination, analogous to zipWith.

zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h]

The zipWith7 function takes a function which combines seven elements, as well as seven lists and returns a list of their point-wise combination, analogous to zipWith.

lcomp :: (Foldable t, Category c) => t (c x x) -> c x xSource

rcomp :: (Foldable t, Category c) => t (c x x) -> c x xSource

loeb :: (Function a (f b) b, Functor f) => f a -> f bSource

class Function f i o | f -> i o whereSource

Methods

($) :: f -> i -> oSource

Instances

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) 

spanList :: ([a] -> Bool) -> [a] -> ([a], [a])Source

breakList :: ([a] -> Bool) -> [a] -> ([a], [a])Source

split :: (Alternative f, Eq a) => [a] -> [a] -> f [a]Source

replace :: Eq a => [a] -> [a] -> [a] -> [a]Source

subIndex :: (Peanoid i, Alternative f, Eq a) => [a] -> [a] -> f iSource