Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Handle :: *
- stdin :: Handle
- stdout :: Handle
- stderr :: Handle
- class Packed c where
- type Chunk = ByteString
- chunkSize :: Chunk -> Int
- readChunk :: String -> IO Chunk
- writeChunk :: String -> Chunk -> IO ()
- readHChunk :: Handle -> IO Chunk
- readHNChunk :: Handle -> Int -> IO Chunk
- writeHChunk :: Handle -> Chunk -> IO ()
- type Bytes = ByteString
- bytesSize :: Bytes -> Int
- readBytes :: String -> IO Bytes
- writeBytes :: String -> Bytes -> IO ()
- readHBytes :: Handle -> IO Bytes
- readHNBytes :: Handle -> Int -> IO Bytes
- writeHBytes :: Handle -> Bytes -> IO ()
- readString :: String -> IO String
- writeString :: String -> String -> IO ()
- readHString :: Handle -> IO String
- writeHString :: Handle -> String -> IO ()
- appendString :: String -> String -> IO ()
- data Void
- type (:*:) a b = (a, b)
- type (:+:) a b = Either a b
- type Tuple2 = (,)
- type Tuple3 = (,,)
- type Tuple4 = (,,,)
- type Tuple5 = (,,,,)
- type Tuple6 = (,,,,,)
- type Tuple7 = (,,,,,,)
- type Tuple8 = (,,,,,,,)
- type Tuple9 = (,,,,,,,,)
- type Union2 = Either
- data Union3 a b c
- data Union4 a b c d
- data Union5 a b c d e
- data Union6 a b c d e f
- data Union7 a b c d e f g
- data Union8 a b c d e f g h
- data Union9 a b c d e f g h i
- class Semigroup m where
- class Semigroup m => Monoid m where
- class Monoid m => Disjonctive m where
- class Monoid m => Semiring m where
- class Semiring m => Ring m where
- class (Ring m, Disjonctive m) => Invertible m where
- class (Semigroup a, Semigroup b) => SubSemi a b where
- class Unit f where
- newtype Endo k a = Endo {
- runEndo :: k a a
- newtype StrictEndo a = StrictEndo {
- runStrictEndo :: a -> a
- newtype Dual m = Dual {
- getDual :: m
- newtype Product a = Product {
- getProduct :: a
- newtype OrdList a = OrdList {
- getOrdList :: [a]
- newtype Interleave a = Interleave {
- runInterleave :: [a]
- newtype Accum a = Accum {}
- newtype Max a = Max {
- getMax :: a
- newtype Min a = Min {
- getMin :: a
- newtype Id a = Id {
- getId :: a
- class Deductive k where
- class Deductive k => Category k where
- (<<<) :: Category k => k b c -> k a b -> k a c
- (>>>) :: Category k => k a b -> k b c -> k a c
- (+++) :: Split k => (a -> k c c) -> (b -> k d d) -> (a :+: b) -> k (c, d) (c, d)
- class Category k => Choice k where
- class Category k => Split k where
- type Constraint a = a -> a
- c'listOf :: Constraint a -> Constraint [a]
- c'list :: Constraint [a]
- c'void :: Constraint Void
- c'int :: Constraint Int
- c'char :: Constraint Char
- c'string :: Constraint String
- c'float :: Constraint Float
- c'_ :: Constraint a
- const :: Unit m => a -> m a
- (&) :: a -> (a -> b) -> b
- fix :: (a -> a) -> a
- uncurry0 :: a -> () -> a
- uncurry :: (a -> b -> c) -> (a, b) -> c
- uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d
- uncurry4 :: (a -> b -> c -> d -> e) -> (a, b, c, d) -> e
- first :: Split k => k a b -> k (a, c) (b, c)
- second :: Split k => k a b -> k (c, a) (c, b)
- ifThenElse :: Bool -> a -> a -> a
- bool :: a -> a -> Bool -> a
- extreme :: Bounded a => Bool -> a
- guard :: (Unit m, Monoid (m ())) => Bool -> m ()
- fail :: String -> a
- error :: String -> a
- unit :: Unit m => m ()
- when :: Unit m => Bool -> m () -> m ()
- unless :: Unit m => Bool -> m () -> m ()
- tailSafe :: [a] -> [a]
- headDef :: a -> [a] -> a
- fromMaybe :: a -> Maybe a -> a
- rmod :: (RealFloat m, Invertible m) => m -> m -> m
- inRange :: Ord t => t -> t -> t -> Bool
- swap :: (a, b) -> (b, a)
- comparing :: Ord a => (b -> a) -> b -> b -> Ordering
- inOrder :: Ord t => t -> t -> (t, t, Bool)
- insertOrd :: Ord t => t -> [t] -> [t]
- invertOrd :: Ordering -> Ordering
- data Assoc k a = Assoc k a
- assoc :: a -> Assoc a a
- newtype Range a = Range (a, a)
- amb :: IO a -> IO a -> IO a
- unamb :: a -> a -> a
- module Prelude
- class IsString a where
Raw data
Haskell defines operations to read and write characters from and to files,
represented by values of type Handle
. Each value of this type is a
handle: a record used by the Haskell run-time system to manage I/O
with file system objects. A handle has at least the following properties:
- whether it manages input or output or both;
- whether it is open, closed or semi-closed;
- whether the object is seekable;
- whether buffering is disabled, or enabled on a line or block basis;
- a buffer (whose length may be zero).
Most handles will also have a current I/O position indicating where the next
input or output operation will occur. A handle is readable if it
manages only input or both input and output; likewise, it is writable if
it manages only output or both input and output. A handle is open when
first allocated.
Once it is closed it can no longer be used for either input or output,
though an implementation cannot re-use its storage while references
remain to it. Handles are in the Show
and Eq
classes. The string
produced by showing a handle is system dependent; it should include
enough information to identify the handle for debugging. A handle is
equal according to ==
only to itself; no attempt
is made to compare the internal state of different handles for equality.
type Chunk = ByteString Source #
type Bytes = ByteString Source #
Basic union and product types
Show Void Source # | |
Monoid Void Source # | |
Semigroup Void Source # | |
Monoid a => SubSemi a Void Source # | |
Isomorphic Bool Bool (Maybe a) (Maybe Void) Source # | |
Isomorphic a b (Void, a) (Void, b) Source # | |
Monad m => MonadError Void (ListT m) Source # | |
Monad m => MonadError Void (LogicT m) Source # | |
Ord a => OrderedMap (Set a) a Void Source # | |
Ord a => DataMap (Set a) a Void Source # | |
Traversable m => Traversable (RWST Void w Void m) Source # | |
Foldable m => Foldable (RWST Void w Void m) Source # | |
type Tuple9 = (,,,,,,,,) Source #
Trav3 x y (Union3 a b x) (Union3 a b y) Source # | |
Trav2 x y (Union3 a x b) (Union3 a y b) Source # | |
Trav1 x y (Union3 x a b) (Union3 y a b) Source # | |
(Eq c, Eq b, Eq a) => Eq (Union3 a b c) Source # | |
(Ord c, Ord b, Ord a) => Ord (Union3 a b c) Source # | |
(Read c, Read b, Read a) => Read (Union3 a b c) Source # | |
(Show c, Show b, Show a) => Show (Union3 a b c) Source # | |
Trav4 x y (Union4 a b c x) (Union4 a b c y) Source # | |
Trav3 x y (Union4 a b x c) (Union4 a b y c) Source # | |
Trav2 x y (Union4 a x b c) (Union4 a y b c) Source # | |
Trav1 x y (Union4 x a b c) (Union4 y a b c) Source # | |
(Eq d, Eq c, Eq b, Eq a) => Eq (Union4 a b c d) Source # | |
(Ord d, Ord c, Ord b, Ord a) => Ord (Union4 a b c d) Source # | |
(Read d, Read c, Read b, Read a) => Read (Union4 a b c d) Source # | |
(Show d, Show c, Show b, Show a) => Show (Union4 a b c d) Source # | |
data Union5 a b c d e Source #
Trav5 x y (Union5 a b c d x) (Union5 a b c d y) Source # | |
Trav4 x y (Union5 a b c x d) (Union5 a b c y d) Source # | |
Trav3 x y (Union5 a b x c d) (Union5 a b y c d) Source # | |
Trav2 x y (Union5 a x b c d) (Union5 a y b c d) Source # | |
Trav1 x y (Union5 x a b c d) (Union5 y a b c d) Source # | |
(Eq e, Eq d, Eq c, Eq b, Eq a) => Eq (Union5 a b c d e) Source # | |
(Ord e, Ord d, Ord c, Ord b, Ord a) => Ord (Union5 a b c d e) Source # | |
(Read e, Read d, Read c, Read b, Read a) => Read (Union5 a b c d e) Source # | |
(Show e, Show d, Show c, Show b, Show a) => Show (Union5 a b c d e) Source # | |
data Union6 a b c d e f Source #
Trav6 x y (Union6 a b c d e x) (Union6 a b c d e y) Source # | |
Trav5 x y (Union6 a b c d x e) (Union6 a b c d y e) Source # | |
Trav4 x y (Union6 a b c x d e) (Union6 a b c y d e) Source # | |
Trav3 x y (Union6 a b x c d e) (Union6 a b y c d e) Source # | |
Trav2 x y (Union6 a x b c d e) (Union6 a y b c d e) Source # | |
Trav1 x y (Union6 x a b c d e) (Union6 y a b c d e) Source # | |
(Eq f, Eq e, Eq d, Eq c, Eq b, Eq a) => Eq (Union6 a b c d e f) Source # | |
(Ord f, Ord e, Ord d, Ord c, Ord b, Ord a) => Ord (Union6 a b c d e f) Source # | |
(Read f, Read e, Read d, Read c, Read b, Read a) => Read (Union6 a b c d e f) Source # | |
(Show f, Show e, Show d, Show c, Show b, Show a) => Show (Union6 a b c d e f) Source # | |
data Union7 a b c d e f g Source #
Trav7 x y (Union7 a b c d e f x) (Union7 a b c d e f y) Source # | |
Trav6 x y (Union7 a b c d e x f) (Union7 a b c d e y f) Source # | |
Trav5 x y (Union7 a b c d x e f) (Union7 a b c d y e f) Source # | |
Trav4 x y (Union7 a b c x d e f) (Union7 a b c y d e f) Source # | |
Trav3 x y (Union7 a b x c d e f) (Union7 a b y c d e f) Source # | |
Trav2 x y (Union7 a x b c d e f) (Union7 a y b c d e f) Source # | |
Trav1 x y (Union7 x a b c d e f) (Union7 y a b c d e f) Source # | |
(Eq g, Eq f, Eq e, Eq d, Eq c, Eq b, Eq a) => Eq (Union7 a b c d e f g) Source # | |
(Ord g, Ord f, Ord e, Ord d, Ord c, Ord b, Ord a) => Ord (Union7 a b c d e f g) Source # | |
(Read g, Read f, Read e, Read d, Read c, Read b, Read a) => Read (Union7 a b c d e f g) Source # | |
(Show g, Show f, Show e, Show d, Show c, Show b, Show a) => Show (Union7 a b c d e f g) Source # | |
data Union8 a b c d e f g h Source #
Trav8 x y (Union8 a b c d e f g x) (Union8 a b c d e f g y) Source # | |
Trav7 x y (Union8 a b c d e f x g) (Union8 a b c d e f y g) Source # | |
Trav6 x y (Union8 a b c d e x f g) (Union8 a b c d e y f g) Source # | |
Trav5 x y (Union8 a b c d x e f g) (Union8 a b c d y e f g) Source # | |
Trav4 x y (Union8 a b c x d e f g) (Union8 a b c y d e f g) Source # | |
Trav3 x y (Union8 a b x c d e f g) (Union8 a b y c d e f g) Source # | |
Trav2 x y (Union8 a x b c d e f g) (Union8 a y b c d e f g) Source # | |
Trav1 x y (Union8 x a b c d e f g) (Union8 y a b c d e f g) Source # | |
(Eq h, Eq g, Eq f, Eq e, Eq d, Eq c, Eq b, Eq a) => Eq (Union8 a b c d e f g h) Source # | |
(Ord h, Ord g, Ord f, Ord e, Ord d, Ord c, Ord b, Ord a) => Ord (Union8 a b c d e f g h) Source # | |
(Read h, Read g, Read f, Read e, Read d, Read c, Read b, Read a) => Read (Union8 a b c d e f g h) Source # | |
(Show h, Show g, Show f, Show e, Show d, Show c, Show b, Show a) => Show (Union8 a b c d e f g h) Source # | |
data Union9 a b c d e f g h i Source #
Trav9 x y (Union9 a b c d e f g h x) (Union9 a b c d e f g h y) Source # | |
Trav8 x y (Union9 a b c d e f g x h) (Union9 a b c d e f g y h) Source # | |
Trav7 x y (Union9 a b c d e f x g h) (Union9 a b c d e f y g h) Source # | |
Trav6 x y (Union9 a b c d e x f g h) (Union9 a b c d e y f g h) Source # | |
Trav5 x y (Union9 a b c d x e f g h) (Union9 a b c d y e f g h) Source # | |
Trav4 x y (Union9 a b c x d e f g h) (Union9 a b c y d e f g h) Source # | |
Trav3 x y (Union9 a b x c d e f g h) (Union9 a b y c d e f g h) Source # | |
Trav2 x y (Union9 a x b c d e f g h) (Union9 a y b c d e f g h) Source # | |
Trav1 x y (Union9 x a b c d e f g h) (Union9 y a b c d e f g h) Source # | |
(Eq i, Eq h, Eq g, Eq f, Eq e, Eq d, Eq c, Eq b, Eq a) => Eq (Union9 a b c d e f g h i) Source # | |
(Ord i, Ord h, Ord g, Ord f, Ord e, Ord d, Ord c, Ord b, Ord a) => Ord (Union9 a b c d e f g h i) Source # | |
(Read i, Read h, Read g, Read f, Read e, Read d, Read c, Read b, Read a) => Read (Union9 a b c d e f g h i) Source # | |
(Show i, Show h, Show g, Show f, Show e, Show d, Show c, Show b, Show a) => Show (Union9 a b c d e f g h i) Source # | |
Basic group and ring structure
Classes
class Semigroup m where Source #
The class of all types that have a binary operation. Note that the operation isn't necesarily commutative (in the case of lists, for example)
class Semigroup m => Monoid m where Source #
A monoid is a semigroup with a null element such that zero + a == a + zero == a
class Monoid m => Disjonctive m where Source #
Disjonctive Bool Source # | |
Disjonctive Double Source # | |
Disjonctive Float Source # | |
Disjonctive Int Source # | |
Disjonctive Integer Source # | |
Disjonctive Ordering Source # | |
Disjonctive Rational Source # | |
(Disjonctive a, Disjonctive b) => Disjonctive ((:*:) a b) Source # | |
(Ord b, Ord a) => Disjonctive (Bimap a b) Source # | |
class Monoid m => Semiring m where Source #
Semiring Bool Source # | |
Semiring Double Source # | |
Semiring Float Source # | |
Semiring Int Source # | |
Semiring Integer Source # | |
Semiring Rational Source # | |
Monoid a => Semiring [a] Source # | |
Monoid a => Semiring (Maybe a) Source # | |
Semiring m => Semiring (Dual m) Source # | |
(Ord a, Bounded a) => Semiring (Min a) Source # | |
(Ord a, Bounded a) => Semiring (Max a) Source # | |
Ord t => Semiring (Time t) Source # | The Time ring where |
(Semiring a, Semiring b) => Semiring ((:*:) a b) Source # | |
Semiring (f a) => Semiring (Backwards f a) Source # | |
Semigroup a => Semiring (LogicT m a) Source # | |
(Semigroup a, Semigroup b, Ord b, Ord a) => Semiring (Bimap a b) Source # | |
Semiring (m (a, Void, Void)) => Semiring (ReaderT r m a) Source # | |
Semiring (m (a, s, Void)) => Semiring (StateT s m a) Source # | |
Semiring (m (a, Void, w)) => Semiring (WriterT w m a) Source # | |
(Semigroup e, Ord a, Ord b) => Semiring (Relation e a b) Source # | |
Semiring (m (a, s, w)) => Semiring (RWST r w s m a) Source # | |
class Semiring m => Ring m where Source #
Ring Bool Source # | |
Ring Double Source # | |
Ring Float Source # | |
Ring Int Source # | |
Ring Integer Source # | |
Ring Rational Source # | |
Monoid a => Ring [a] Source # | |
Monoid a => Ring (Maybe a) Source # | |
Ring m => Ring (Dual m) Source # | |
(Ord a, Bounded a) => Ring (Min a) Source # | |
(Ord a, Bounded a) => Ring (Max a) Source # | |
Ord t => Ring (Time t) Source # | |
(Ring a, Ring b) => Ring ((:*:) a b) Source # | |
Ring (f a) => Ring (Backwards f a) Source # | |
Monoid a => Ring (LogicT m a) Source # | |
Ring (m (a, Void, Void)) => Ring (ReaderT r m a) Source # | |
Ring (m (a, s, Void)) => Ring (StateT s m a) Source # | |
Ring (m (a, Void, w)) => Ring (WriterT w m a) Source # | |
Ring (m (a, s, w)) => Ring (RWST r w s m a) Source # | |
class (Ring m, Disjonctive m) => Invertible m where Source #
Common monoids
Control monoids
A monoid on category endomorphisms under composition
Meta-monoids
The dual of a monoid is the same as the original, with arguments reversed
The Product monoid
Product | |
|
Accumulating monoids
An ordered list. The semigroup instance merges two lists so that the result remains in ascending order.
OrdList | |
|
newtype Interleave a Source #
Interleave | |
|
Monoid (Interleave a) Source # | |
Semigroup (Interleave a) Source # | |
A monoid on Maybes, where the sum is the leftmost non-Nothing value.
The Max monoid, where (+) =~ max
Isomorphic a b (Max a) (Max b) Source # | |
Bounded a => Bounded (Max a) Source # | |
Eq a => Eq (Max a) Source # | |
Ord a => Ord (Max a) Source # | |
Show a => Show (Max a) Source # | |
(Ord a, Bounded a) => Ring (Max a) Source # | |
(Ord a, Bounded a) => Semiring (Max a) Source # | |
(Ord a, Bounded a) => Monoid (Max a) Source # | |
Ord a => Semigroup (Max a) Source # | |
The Min monoid, where (+) =~ min
Bounded a => Bounded (Min a) Source # | |
Eq a => Eq (Min a) Source # | |
Ord a => Ord (Min a) Source # | |
Show a => Show (Min a) Source # | |
(Ord a, Bounded a) => Ring (Min a) Source # | |
(Ord a, Bounded a) => Semiring (Min a) Source # | |
(Ord a, Bounded a) => Monoid (Min a) Source # | |
Ord a => Semigroup (Min a) Source # | |
The Identity Functor
Fundamental control operations
Splitting and Choosing
Expression-level type constraints
type Constraint a = a -> a Source #
c'listOf :: Constraint a -> Constraint [a] Source #
c'list :: Constraint [a] Source #
c'void :: Constraint Void Source #
c'int :: Constraint Int Source #
c'char :: Constraint Char Source #
c'_ :: Constraint a Source #
Miscellaneous functions
ifThenElse :: Bool -> a -> a -> a Source #
rmod :: (RealFloat m, Invertible m) => m -> m -> m infixl 7 Source #
Lazily ordering values
comparing :: Ord a => (b -> a) -> b -> b -> Ordering #
comparing p x y = compare (p x) (p y)
Useful combinator for use in conjunction with the xxxBy
family
of functions from Data.List, for example:
... sortBy (comparing fst) ...
Assoc k a |
Ranges
A range of shape (min,max) of ordered values.
Such ranges may be multiplied to create n-dimensional ranges for which equivalence means sharing an n-dimensional subrange. They may be very useful in creating Maps that partition an n-dimensional space in which we may query for subrange membership with logarithmic complexity for any point P (a point is a subrange of volume 0, or `(pure x0,...,pure xn) where (x0,..,xn) = p`).
Indeed, a point is equivalent to a range iff it belongs to that range.
Range (a, a) |
Parallel short-circuit evaluation
The rest is imported from the Prelude
module Prelude
Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).
fromString :: String -> a #