aop-prelude-0.3.0.2: prelude for Algebra of Programming

Safe HaskellNone
LanguageHaskell2010

AOPPrelude

Documentation

(.) :: (b -> c) -> (a -> b) -> a -> c infixr 9 Source #

const :: a -> b -> a Source #

id :: a -> a Source #

outl :: (a, b) -> a Source #

outr :: (a, b) -> b Source #

swap :: (a, b) -> (b, a) Source #

assocl :: (a, (b, c)) -> ((a, b), c) Source #

assocr :: ((a, b), c) -> (a, (b, c)) Source #

dupl :: (a, (b, c)) -> ((a, b), (a, c)) Source #

dupr :: ((a, b), c) -> ((a, c), (b, c)) Source #

pair :: (a -> b, a -> c) -> a -> (b, c) Source #

cross :: (a -> c, b -> d) -> (a, b) -> (c, d) Source #

cond :: (a -> Bool) -> (a -> b, a -> b) -> a -> b Source #

curry :: ((a, b) -> c) -> a -> b -> c Source #

uncurry :: (a -> b -> c) -> (a, b) -> c Source #

false :: a -> Bool Source #

true :: a -> Bool Source #

(&&) :: Bool -> Bool -> Bool infixr 3 Source #

(||) :: Bool -> Bool -> Bool infixr 2 Source #

not :: Bool -> Bool Source #

leq :: Ord a => (a, a) -> Bool Source #

less :: Ord a => (a, a) -> Bool Source #

eql :: Ord a => (a, a) -> Bool Source #

neq :: Ord a => (a, a) -> Bool Source #

gtr :: Ord a => (a, a) -> Bool Source #

geq :: Ord a => (a, a) -> Bool Source #

meet :: (a -> Bool, a -> Bool) -> a -> Bool Source #

join :: (a -> Bool, a -> Bool) -> a -> Bool Source #

wok :: ((b, a) -> c) -> (a, b) -> c Source #

zero :: Num a => t -> a Source #

succ :: Num a => a -> a Source #

pred :: Num a => a -> a Source #

plus :: Num a => (a, a) -> a Source #

minus :: Num a => (a, a) -> a Source #

times :: Num a => (a, a) -> a Source #

divide :: Fractional a => (a, a) -> a Source #

negative :: (Ord a, Num a) => a -> Bool Source #

positive :: (Ord a, Num a) => a -> Bool Source #

(++) :: [a] -> [a] -> [a] infixr 5 Source #

null :: [a] -> Bool Source #

nil :: t -> [a] Source #

wrap :: a -> [a] Source #

cons :: (a, [a]) -> [a] Source #

cat :: ([a], [a]) -> [a] Source #

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

snoc :: ([a], a) -> [a] Source #

head :: [a] -> a Source #

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

split :: [a] -> (a, [a]) Source #

last :: [a] -> a Source #

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

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

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

splits :: [a] -> [([a], [a])] Source #

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

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

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

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

minlist :: ((a, a) -> Bool) -> [a] -> a Source #

bmin :: ((a, a) -> Bool) -> (a, a) -> a Source #

maxlist :: ((a, a) -> Bool) -> [a] -> a Source #

bmax :: ((a, a) -> Bool) -> (a, a) -> a Source #

thinlist :: ((a, a) -> Bool) -> [a] -> [a] Source #

length :: Num a => [t] -> a Source #

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

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

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

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

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

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

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

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

merge :: ((a, a) -> Bool) -> ([a], [a]) -> [a] Source #

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

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

ord :: Char -> Int #

chr :: Int -> Char #

(==) :: Eq a => a -> a -> Bool #

(/=) :: Eq a => a -> a -> Bool #

(<=) :: Ord a => a -> a -> Bool #

(<) :: Ord a => a -> a -> Bool #

(>=) :: Ord a => a -> a -> Bool #

(>) :: Ord a => a -> a -> Bool #

(+) :: Num a => a -> a -> a #

(-) :: Num a => a -> a -> a #

(/) :: Fractional a => a -> a -> a #

div :: Integral a => a -> a -> a #

mod :: Integral a => a -> a -> a #

(*) :: Num a => a -> a -> a #

negate :: Num a => a -> a #

primPrint :: Show a => a -> IO () Source #

strict :: (a -> b) -> a -> b Source #

error :: HasCallStack => [Char] -> a #

show :: Show a => a -> String #

flip :: (a -> b -> c) -> b -> a -> c Source #

type String = [Char] #

class Num a #

Minimal complete definition

(+), (*), abs, signum, fromInteger, (negate | (-))

Instances
Num Int 
Instance details

Defined in GHC.Num

Methods

(+) :: Int -> Int -> Int #

(-) :: Int -> Int -> Int #

(*) :: Int -> Int -> Int #

negate :: Int -> Int #

abs :: Int -> Int

signum :: Int -> Int

fromInteger :: Integer -> Int

Num Integer 
Instance details

Defined in GHC.Num

Methods

(+) :: Integer -> Integer -> Integer #

(-) :: Integer -> Integer -> Integer #

(*) :: Integer -> Integer -> Integer #

negate :: Integer -> Integer #

abs :: Integer -> Integer

signum :: Integer -> Integer

fromInteger :: Integer -> Integer

Num Natural 
Instance details

Defined in GHC.Num

Num Word 
Instance details

Defined in GHC.Num

Methods

(+) :: Word -> Word -> Word #

(-) :: Word -> Word -> Word #

(*) :: Word -> Word -> Word #

negate :: Word -> Word #

abs :: Word -> Word

signum :: Word -> Word

fromInteger :: Integer -> Word

Integral a => Num (Ratio a) 
Instance details

Defined in GHC.Real

Methods

(+) :: Ratio a -> Ratio a -> Ratio a #

(-) :: Ratio a -> Ratio a -> Ratio a #

(*) :: Ratio a -> Ratio a -> Ratio a #

negate :: Ratio a -> Ratio a #

abs :: Ratio a -> Ratio a

signum :: Ratio a -> Ratio a

fromInteger :: Integer -> Ratio a

class Num a => Fractional a #

Minimal complete definition

fromRational, (recip | (/))

Instances
Integral a => Fractional (Ratio a) 
Instance details

Defined in GHC.Real

Methods

(/) :: Ratio a -> Ratio a -> Ratio a #

recip :: Ratio a -> Ratio a

fromRational :: Rational -> Ratio a

class Show a #

Minimal complete definition

showsPrec | show

Instances
Show Bool 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Bool -> ShowS

show :: Bool -> String #

showList :: [Bool] -> ShowS

Show Char 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Char -> ShowS

show :: Char -> String #

showList :: [Char] -> ShowS

Show Int 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Int -> ShowS

show :: Int -> String #

showList :: [Int] -> ShowS

Show Integer 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Integer -> ShowS

show :: Integer -> String #

showList :: [Integer] -> ShowS

Show Natural 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Natural -> ShowS

show :: Natural -> String #

showList :: [Natural] -> ShowS

Show Ordering 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Ordering -> ShowS

show :: Ordering -> String #

showList :: [Ordering] -> ShowS

Show Word 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Word -> ShowS

show :: Word -> String #

showList :: [Word] -> ShowS

Show RuntimeRep 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> RuntimeRep -> ShowS

show :: RuntimeRep -> String #

showList :: [RuntimeRep] -> ShowS

Show VecCount 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> VecCount -> ShowS

show :: VecCount -> String #

showList :: [VecCount] -> ShowS

Show VecElem 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> VecElem -> ShowS

show :: VecElem -> String #

showList :: [VecElem] -> ShowS

Show CallStack 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> CallStack -> ShowS

show :: CallStack -> String #

showList :: [CallStack] -> ShowS

Show () 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> () -> ShowS

show :: () -> String #

showList :: [()] -> ShowS

Show TyCon 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> TyCon -> ShowS

show :: TyCon -> String #

showList :: [TyCon] -> ShowS

Show Module 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Module -> ShowS

show :: Module -> String #

showList :: [Module] -> ShowS

Show TrName 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> TrName -> ShowS

show :: TrName -> String #

showList :: [TrName] -> ShowS

Show KindRep 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> KindRep -> ShowS

show :: KindRep -> String #

showList :: [KindRep] -> ShowS

Show TypeLitSort 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> TypeLitSort -> ShowS

show :: TypeLitSort -> String #

showList :: [TypeLitSort] -> ShowS

Show SrcLoc 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> SrcLoc -> ShowS

show :: SrcLoc -> String #

showList :: [SrcLoc] -> ShowS

Show a => Show [a] 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> [a] -> ShowS

show :: [a] -> String #

showList :: [[a]] -> ShowS

Show a => Show (Maybe a) 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Maybe a -> ShowS

show :: Maybe a -> String #

showList :: [Maybe a] -> ShowS

Show a => Show (Ratio a) 
Instance details

Defined in GHC.Real

Methods

showsPrec :: Int -> Ratio a -> ShowS

show :: Ratio a -> String #

showList :: [Ratio a] -> ShowS

Show a => Show (NonEmpty a) 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> NonEmpty a -> ShowS

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS

(Show a, Show b) => Show (a, b) 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b) -> ShowS

show :: (a, b) -> String #

showList :: [(a, b)] -> ShowS

(Show a, Show b, Show c) => Show (a, b, c) 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c) -> ShowS

show :: (a, b, c) -> String #

showList :: [(a, b, c)] -> ShowS

(Show a, Show b, Show c, Show d) => Show (a, b, c, d) 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d) -> ShowS

show :: (a, b, c, d) -> String #

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

(Show a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e) 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e) -> ShowS

show :: (a, b, c, d, e) -> String #

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

(Show a, Show b, Show c, Show d, Show e, Show f) => Show (a, b, c, d, e, f) 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f) -> ShowS

show :: (a, b, c, d, e, f) -> String #

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

(Show a, Show b, Show c, Show d, Show e, Show f, Show g) => Show (a, b, c, d, e, f, g) 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g) -> ShowS

show :: (a, b, c, d, e, f, g) -> String #

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

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h) => Show (a, b, c, d, e, f, g, h) 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h) -> ShowS

show :: (a, b, c, d, e, f, g, h) -> String #

showList :: [(a, b, c, d, e, f, g, h)] -> ShowS

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i) => Show (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i) -> ShowS

show :: (a, b, c, d, e, f, g, h, i) -> String #

showList :: [(a, b, c, d, e, f, g, h, i)] -> ShowS

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j) => Show (a, b, c, d, e, f, g, h, i, j) 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j) -> ShowS

show :: (a, b, c, d, e, f, g, h, i, j) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j)] -> ShowS

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k) => Show (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k) -> ShowS

show :: (a, b, c, d, e, f, g, h, i, j, k) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> ShowS

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l) => Show (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l) -> ShowS

show :: (a, b, c, d, e, f, g, h, i, j, k, l) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> ShowS

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> ShowS

show :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> ShowS

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> ShowS

show :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> ShowS

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n, Show o) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> ShowS

show :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> ShowS

data Natural #

Instances
Eq Natural 
Instance details

Defined in GHC.Natural

Methods

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

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

Integral Natural 
Instance details

Defined in GHC.Real

Num Natural 
Instance details

Defined in GHC.Num

Ord Natural 
Instance details

Defined in GHC.Natural

Methods

compare :: Natural -> Natural -> Ordering

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

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

(>) :: Natural -> Natural -> Bool #

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

max :: Natural -> Natural -> Natural

min :: Natural -> Natural -> Natural

Real Natural 
Instance details

Defined in GHC.Real

Methods

toRational :: Natural -> Rational

Show Natural 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Natural -> ShowS

show :: Natural -> String #

showList :: [Natural] -> ShowS