diff --git a/posts.yaml b/posts.yaml index 5bc5339..7951ad9 100644 --- a/posts.yaml +++ b/posts.yaml @@ -1,3 +1,6 @@ +- file: posts/safe-prelude-a-thuought-experiment.md + title: "safe-prelude: a thought experiment" + day: 2017-01-16 - file: posts/foldable-mapm-maybe-and-recursive-functions.md title: Foldable.mapM_, Maybe, and recursive functions day: 2017-01-10 diff --git a/posts/safe-prelude-a-thuought-experiment.md b/posts/safe-prelude-a-thuought-experiment.md new file mode 100644 index 0000000..d99ca04 --- /dev/null +++ b/posts/safe-prelude-a-thuought-experiment.md @@ -0,0 +1,111 @@ +This blog post is to share a very rough first stab at a new prelude I +played around with earlier this month. I haven't used it in any +significant way, and haven't spent more than a few hours on it +total. I wrote it because I knew it was the only way to get the idea +out of my head, and am sharing it in case anyone finds the idea +intriguing or useful. + +The project is available +[on Github at snoyberg/safe-prelude](https://github.com/snoyberg/safe-prelude#readme), +and I've +[uploaded the Haddocks for easier reading](/static/safe-prelude/SafePrelude.html) +(though, be warned, they aren't well organized at all). The rest of +this post is just a copy of the `README.md` file for the project. + +* * * + +This is a thought experiment in a different point in the alternative +prelude design space. After my +[blog post on readFile](http://www.snoyman.com/blog/2016/12/beware-of-readfile), +I realized I was unhappy with the polymorphic nature of `readFile` in +[classy-prelude](https://www.stackage.org/package/classy-prelude). Adding +that with +[Haskell Pitfalls](http://lorepub.com/post/2016-12-17-Haskell-Pitfalls) +I've been itching to try something else. I have a lot of hope for the +[foundation project](https://github.com/haskell-foundation/foundation#readme), +but wanted to play with this in the short term. + +## Choices + +* No partial functions, period. If a function can fail, its return + type must express that. (And for our purposes: `IO` functions with + runtime exceptions are _not_ partial.) +* Choose best in class libraries and promote them. `bytestring` and + `text` fit that bill, as an example. Full listing below. +* Regardless of the versions of underlying libraries, this package + will always export a consistent API, so that CPP usage should be + constrained to just inside this package. +* Use generalization (via type classes) when they are well + established. For example: `Foldable` and `Traversable` yes, + `MonoFoldable` no. + * _Controversial_ Avoid providing list-specific functions. This + connects to the parent point. Most of the time, I'd argue that + lists are _not_ the correct choice, and instead a `Vector` + should be used. There is no standard for sequence-like + typeclasses (though many exist), so we're not going to + generalize. But we're also not going to use a less efficient + representation. + + I was torn on this, but decided in favor of leaving out + functions initially, on the basis that it's easier to add + something in later rather than remove it. +* Encourage qualified imports with a consistent naming scheme. This is + a strong departure from classy-prelude, which tried to make it + unnecessary to use qualified imports. I'll save my feelings about + qualified imports for another time, this is just a pragmatic choice + given the other constraints. +* Export any non-conflicting and not-discouraged names from this + module that make sense, e.g. `ByteString`, `Text`, or `readIORef`. + +## Libraries + +This list may fall out of date, so check the `.cabal` file for a +current and complete listing. I'm keeping this here to include +reasoning for some libraries: + +* `bytestring` and `text`, despite some complaints, are clearly the + most popular representation for binary and textual data, + respectively +* `containers` and `unordered-containers` are both commonly used. Due + to lack of generalization, this library doesn't expose any functions + for working with their types, but they are common enough that adding + the dependency just for exposing the type name is worth it +* `safe-exceptions` hides the complexity of asynchronous exceptions, + and should be used in place of `Control.Exception` +* `transformers` and `mtl` are clear winners in the monad transformer + space, at least for now +* While young, `say` has been very useful for me in avoiding + interleaved output issues +* Others without real competitors: `deepseq`, `semigroups` + +Packages I considered but have not included yet: + +* `stm` is an obvious winner, and while I use it constantly, I'm not +convinced everyone else uses it as much as I do. Also, there are some +questions around generalizing its functions (e.g., `atomically` could +be in `MonadIO`), and I don't want to make that decision yet. + * `stm-chans` falls into this category too +* `async` is an amazing library, and in particular the `race`, + `concurrently`, and `Concurrently` bits are an easy win. I've left + it out for now due to questions of generalizing to + `MonadBaseControl` (see `lifted-async` and its `.Safe` module) +* Similar argument applies to `monad-unlift` +* I didn't bother with exposing the `Vector` type... because which one + would I expose? The `Vector` typeclass? Boxed `Vector`? Unboxed? I + could do the classy-prelude thing and define `type UVector = + Data.Vector.Unboxed.Vector`, but I'd rather not do such renamings. + +## Qualified imports + +Here are the recommend qualified imports when working with safe-prelude. + +```haskell +import qualified "bytestring" Data.ByteString as B +import qualified "bytestring" Data.ByteString.Lazy as BL +import qualified "text" Data.Text as T +import qualified "text" Data.Text.Lazy as TL +import qualified "containers" Data.Map.Strict as Map +import qualified "containers" Data.Set as Set +import qualified "unordered-containers" Data.HashMap.Strict as HashMap +import qualified "unordered-containers" Data.HashSet as HashSet +``` diff --git a/static/safe-prelude/LICENSE b/static/safe-prelude/LICENSE new file mode 100644 index 0000000..03ee2ef --- /dev/null +++ b/static/safe-prelude/LICENSE @@ -0,0 +1,21 @@ +MIT License + +Copyright (c) 2017 Michael Snoyman + +Permission is hereby granted, free of charge, to any person obtaining a copy +of this software and associated documentation files (the "Software"), to deal +in the Software without restriction, including without limitation the rights +to use, copy, modify, merge, publish, distribute, sublicense, and/or sell +copies of the Software, and to permit persons to whom the Software is +furnished to do so, subject to the following conditions: + +The above copyright notice and this permission notice shall be included in all +copies or substantial portions of the Software. + +THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR +IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, +FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE +AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER +LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, +OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE +SOFTWARE. diff --git a/static/safe-prelude/SafePrelude.html b/static/safe-prelude/SafePrelude.html new file mode 100644 index 0000000..20d9f36 --- /dev/null +++ b/static/safe-prelude/SafePrelude.html @@ -0,0 +1,731 @@ +SafePrelude

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Safe HaskellNone
LanguageHaskell2010

SafePrelude

Contents

Synopsis

Types

data Maybe a :: * -> * #

The Maybe type encapsulates an optional value. A value of type + Maybe a either contains a value of type a (represented as Just a), + or it is empty (represented as Nothing). Using Maybe is a good way to + deal with errors or exceptional cases without resorting to drastic + measures such as error.

The Maybe type is also a monad. It is a simple kind of error + monad, where all errors are represented by Nothing. A richer + error monad can be built using the Either type.

Constructors

Nothing 
Just a 

Instances

Monad Maybe 

Methods

(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b #

(>>) :: Maybe a -> Maybe b -> Maybe b #

return :: a -> Maybe a #

fail :: String -> Maybe a #

Functor Maybe 

Methods

fmap :: (a -> b) -> Maybe a -> Maybe b #

(<$) :: a -> Maybe b -> Maybe a #

Applicative Maybe 

Methods

pure :: a -> Maybe a #

(<*>) :: Maybe (a -> b) -> Maybe a -> Maybe b #

(*>) :: Maybe a -> Maybe b -> Maybe b #

(<*) :: Maybe a -> Maybe b -> Maybe a #

Foldable Maybe 

Methods

fold :: Monoid m => Maybe m -> m #

foldMap :: Monoid m => (a -> m) -> Maybe a -> m #

foldr :: (a -> b -> b) -> b -> Maybe a -> b #

foldr' :: (a -> b -> b) -> b -> Maybe a -> b #

foldl :: (b -> a -> b) -> b -> Maybe a -> b #

foldl' :: (b -> a -> b) -> b -> Maybe a -> b #

foldr1 :: (a -> a -> a) -> Maybe a -> a #

foldl1 :: (a -> a -> a) -> Maybe a -> a #

toList :: Maybe a -> [a] #

null :: Maybe a -> Bool #

length :: Maybe a -> Int #

elem :: Eq a => a -> Maybe a -> Bool #

maximum :: Ord a => Maybe a -> a #

minimum :: Ord a => Maybe a -> a #

sum :: Num a => Maybe a -> a #

product :: Num a => Maybe a -> a #

Traversable Maybe 

Methods

traverse :: Applicative f => (a -> f b) -> Maybe a -> f (Maybe b) #

sequenceA :: Applicative f => Maybe (f a) -> f (Maybe a) #

mapM :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b) #

sequence :: Monad m => Maybe (m a) -> m (Maybe a) #

Generic1 Maybe 

Associated Types

type Rep1 (Maybe :: * -> *) :: * -> * #

Methods

from1 :: Maybe a -> Rep1 Maybe a #

to1 :: Rep1 Maybe a -> Maybe a #

Alternative Maybe 

Methods

empty :: Maybe a #

(<|>) :: Maybe a -> Maybe a -> Maybe a #

some :: Maybe a -> Maybe [a] #

many :: Maybe a -> Maybe [a] #

MonadPlus Maybe 

Methods

mzero :: Maybe a #

mplus :: Maybe a -> Maybe a -> Maybe a #

MonadThrow Maybe 

Methods

throwM :: Exception e => e -> Maybe a #

Eq a => Eq (Maybe a) 

Methods

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

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

Ord a => Ord (Maybe a) 

Methods

compare :: Maybe a -> Maybe a -> Ordering #

(<) :: Maybe a -> Maybe a -> Bool #

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

(>) :: Maybe a -> Maybe a -> Bool #

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

max :: Maybe a -> Maybe a -> Maybe a #

min :: Maybe a -> Maybe a -> Maybe a #

Read a => Read (Maybe a) 
Show a => Show (Maybe a) 

Methods

showsPrec :: Int -> Maybe a -> ShowS #

show :: Maybe a -> String #

showList :: [Maybe a] -> ShowS #

Generic (Maybe a) 

Associated Types

type Rep (Maybe a) :: * -> * #

Methods

from :: Maybe a -> Rep (Maybe a) x #

to :: Rep (Maybe a) x -> Maybe a #

Semigroup a => Semigroup (Maybe a) 

Methods

(<>) :: Maybe a -> Maybe a -> Maybe a #

sconcat :: NonEmpty (Maybe a) -> Maybe a #

stimes :: Integral b => b -> Maybe a -> Maybe a #

Monoid a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to + http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be + turned into a monoid simply by adjoining an element e not in S + and defining e*e = e and e*s = s = s*e for all s ∈ S." Since + there is no "Semigroup" typeclass providing just mappend, we + use Monoid instead.

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

mconcat :: [Maybe a] -> Maybe a #

Lift a => Lift (Maybe a) 

Methods

lift :: Maybe a -> Q Exp #

NFData a => NFData (Maybe a) 

Methods

rnf :: Maybe a -> () #

Hashable a => Hashable (Maybe a) 

Methods

hashWithSalt :: Int -> Maybe a -> Int #

hash :: Maybe a -> Int #

SingI (Maybe a) (Nothing a) 

Methods

sing :: Sing (Nothing a) a

SingKind a (KProxy a) => SingKind (Maybe a) (KProxy (Maybe a)) 

Associated Types

type DemoteRep (KProxy (Maybe a)) (kparam :: KProxy (KProxy (Maybe a))) :: *

Methods

fromSing :: Sing (KProxy (Maybe a)) a -> DemoteRep (KProxy (Maybe a)) kparam

SingI a a1 => SingI (Maybe a) (Just a a1) 

Methods

sing :: Sing (Just a a1) a

type Rep1 Maybe 
type Rep (Maybe a) 
data Sing (Maybe a) 
data Sing (Maybe a) where
type (==) (Maybe k) a b 
type (==) (Maybe k) a b = EqMaybe k a b
type DemoteRep (Maybe a) (KProxy (Maybe a)) 
type DemoteRep (Maybe a) (KProxy (Maybe a)) = Maybe (DemoteRep a (KProxy a))

data Ordering :: * #

Constructors

LT 
EQ 
GT 

Instances

Bounded Ordering 
Enum Ordering 
Eq Ordering 
Ord Ordering 
Read Ordering 
Show Ordering 
Generic Ordering 

Associated Types

type Rep Ordering :: * -> * #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Semigroup Ordering 
Monoid Ordering 
Hashable Ordering 

Methods

hashWithSalt :: Int -> Ordering -> Int #

hash :: Ordering -> Int #

type Rep Ordering 
type Rep Ordering = D1 (MetaData "Ordering" "GHC.Types" "ghc-prim" False) ((:+:) (C1 (MetaCons "LT" PrefixI False) U1) ((:+:) (C1 (MetaCons "EQ" PrefixI False) U1) (C1 (MetaCons "GT" PrefixI False) U1)))
type (==) Ordering a b 
type (==) Ordering a b = EqOrdering a b

data Bool :: * #

Constructors

False 
True 

Instances

Bounded Bool 
Enum Bool 

Methods

succ :: Bool -> Bool #

pred :: Bool -> Bool #

toEnum :: Int -> Bool #

fromEnum :: Bool -> Int #

enumFrom :: Bool -> [Bool] #

enumFromThen :: Bool -> Bool -> [Bool] #

enumFromTo :: Bool -> Bool -> [Bool] #

enumFromThenTo :: Bool -> Bool -> Bool -> [Bool] #

Eq Bool 

Methods

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

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

Ord Bool 

Methods

compare :: Bool -> Bool -> Ordering #

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

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

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

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

max :: Bool -> Bool -> Bool #

min :: Bool -> Bool -> Bool #

Read Bool 
Show Bool 

Methods

showsPrec :: Int -> Bool -> ShowS #

show :: Bool -> String #

showList :: [Bool] -> ShowS #

Generic Bool 

Associated Types

type Rep Bool :: * -> * #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Lift Bool 

Methods

lift :: Bool -> Q Exp #

NFData Bool 

Methods

rnf :: Bool -> () #

Hashable Bool 

Methods

hashWithSalt :: Int -> Bool -> Int #

hash :: Bool -> Int #

SingI Bool False 

Methods

sing :: Sing False a

SingI Bool True 

Methods

sing :: Sing True a

SingKind Bool (KProxy Bool) 

Associated Types

type DemoteRep (KProxy Bool) (kparam :: KProxy (KProxy Bool)) :: *

Methods

fromSing :: Sing (KProxy Bool) a -> DemoteRep (KProxy Bool) kparam

type Rep Bool 
type Rep Bool = D1 (MetaData "Bool" "GHC.Types" "ghc-prim" False) ((:+:) (C1 (MetaCons "False" PrefixI False) U1) (C1 (MetaCons "True" PrefixI False) U1))
data Sing Bool 
data Sing Bool where
type (==) Bool a b 
type (==) Bool a b = EqBool a b
type DemoteRep Bool (KProxy Bool) 
type DemoteRep Bool (KProxy Bool) = Bool

data Char :: * #

The character type Char is an enumeration whose values represent +Unicode (or equivalently ISO/IEC 10646) characters (see +http://www.unicode.org/ for details). This set extends the ISO 8859-1 +(Latin-1) character set (the first 256 characters), which is itself an extension +of the ASCII character set (the first 128 characters). A character literal in +Haskell has type Char.

To convert a Char to or from the corresponding Int value defined +by Unicode, use toEnum and fromEnum from the +Enum class respectively (or equivalently ord and chr).

Instances

Bounded Char 
Enum Char 

Methods

succ :: Char -> Char #

pred :: Char -> Char #

toEnum :: Int -> Char #

fromEnum :: Char -> Int #

enumFrom :: Char -> [Char] #

enumFromThen :: Char -> Char -> [Char] #

enumFromTo :: Char -> Char -> [Char] #

enumFromThenTo :: Char -> Char -> Char -> [Char] #

Eq Char 

Methods

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

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

Ord Char 

Methods

compare :: Char -> Char -> Ordering #

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

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

(>) :: Char -> Char -> Bool #

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

max :: Char -> Char -> Char #

min :: Char -> Char -> Char #

Read Char 
Show Char 

Methods

showsPrec :: Int -> Char -> ShowS #

show :: Char -> String #

showList :: [Char] -> ShowS #

Lift Char 

Methods

lift :: Char -> Q Exp #

NFData Char 

Methods

rnf :: Char -> () #

Hashable Char 

Methods

hashWithSalt :: Int -> Char -> Int #

hash :: Char -> Int #

ErrorList Char 

Methods

listMsg :: String -> [Char] #

Functor (URec Char) 

Methods

fmap :: (a -> b) -> URec Char a -> URec Char b #

(<$) :: a -> URec Char b -> URec Char a #

IsString (Seq Char) 

Methods

fromString :: String -> Seq Char #

Foldable (URec Char) 

Methods

fold :: Monoid m => URec Char m -> m #

foldMap :: Monoid m => (a -> m) -> URec Char a -> m #

foldr :: (a -> b -> b) -> b -> URec Char a -> b #

foldr' :: (a -> b -> b) -> b -> URec Char a -> b #

foldl :: (b -> a -> b) -> b -> URec Char a -> b #

foldl' :: (b -> a -> b) -> b -> URec Char a -> b #

foldr1 :: (a -> a -> a) -> URec Char a -> a #

foldl1 :: (a -> a -> a) -> URec Char a -> a #

toList :: URec Char a -> [a] #

null :: URec Char a -> Bool #

length :: URec Char a -> Int #

elem :: Eq a => a -> URec Char a -> Bool #

maximum :: Ord a => URec Char a -> a #

minimum :: Ord a => URec Char a -> a #

sum :: Num a => URec Char a -> a #

product :: Num a => URec Char a -> a #

Traversable (URec Char) 

Methods

traverse :: Applicative f => (a -> f b) -> URec Char a -> f (URec Char b) #

sequenceA :: Applicative f => URec Char (f a) -> f (URec Char a) #

mapM :: Monad m => (a -> m b) -> URec Char a -> m (URec Char b) #

sequence :: Monad m => URec Char (m a) -> m (URec Char a) #

Generic1 (URec Char) 

Associated Types

type Rep1 (URec Char :: * -> *) :: * -> * #

Methods

from1 :: URec Char a -> Rep1 (URec Char) a #

to1 :: Rep1 (URec Char) a -> URec Char a #

Eq (URec Char p) 

Methods

(==) :: URec Char p -> URec Char p -> Bool #

(/=) :: URec Char p -> URec Char p -> Bool #

Ord (URec Char p) 

Methods

compare :: URec Char p -> URec Char p -> Ordering #

(<) :: URec Char p -> URec Char p -> Bool #

(<=) :: URec Char p -> URec Char p -> Bool #

(>) :: URec Char p -> URec Char p -> Bool #

(>=) :: URec Char p -> URec Char p -> Bool #

max :: URec Char p -> URec Char p -> URec Char p #

min :: URec Char p -> URec Char p -> URec Char p #

Show (URec Char p) 

Methods

showsPrec :: Int -> URec Char p -> ShowS #

show :: URec Char p -> String #

showList :: [URec Char p] -> ShowS #

Generic (URec Char p) 

Associated Types

type Rep (URec Char p) :: * -> * #

Methods

from :: URec Char p -> Rep (URec Char p) x #

to :: Rep (URec Char p) x -> URec Char p #

data URec Char

Used for marking occurrences of Char#

data URec Char = UChar {}
type Rep1 (URec Char) 
type Rep1 (URec Char) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UChar" PrefixI True) (S1 (MetaSel (Just Symbol "uChar#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UChar))
type Rep (URec Char p) 
type Rep (URec Char p) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UChar" PrefixI True) (S1 (MetaSel (Just Symbol "uChar#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UChar))

data IO a :: * -> * #

A value of type IO a is a computation which, when performed, +does some I/O before returning a value of type a.

There is really only one way to "perform" an I/O action: bind it to +Main.main in your program. When your program is run, the I/O will +be performed. It isn't possible to perform I/O from an arbitrary +function, unless that function is itself in the IO monad and called +at some point, directly or indirectly, from Main.main.

IO is a monad, so IO actions can be combined using either the do-notation +or the >> and >>= operations from the Monad class.

Instances

Monad IO 

Methods

(>>=) :: IO a -> (a -> IO b) -> IO b #

(>>) :: IO a -> IO b -> IO b #

return :: a -> IO a #

fail :: String -> IO a #

Functor IO 

Methods

fmap :: (a -> b) -> IO a -> IO b #

(<$) :: a -> IO b -> IO a #

Applicative IO 

Methods

pure :: a -> IO a #

(<*>) :: IO (a -> b) -> IO a -> IO b #

(*>) :: IO a -> IO b -> IO b #

(<*) :: IO a -> IO b -> IO a #

MonadIO IO 

Methods

liftIO :: IO a -> IO a #

Alternative IO 

Methods

empty :: IO a #

(<|>) :: IO a -> IO a -> IO a #

some :: IO a -> IO [a] #

many :: IO a -> IO [a] #

MonadPlus IO 

Methods

mzero :: IO a #

mplus :: IO a -> IO a -> IO a #

MonadThrow IO 

Methods

throwM :: Exception e => e -> IO a #

MonadCatch IO 

Methods

catch :: Exception e => IO a -> (e -> IO a) -> IO a #

MonadMask IO 

Methods

mask :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

uninterruptibleMask :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

Quasi IO 
Monoid a => Monoid (IO a) 

Methods

mempty :: IO a #

mappend :: IO a -> IO a -> IO a #

mconcat :: [IO a] -> IO a #

data Either a b :: * -> * -> * #

The Either type represents values with two possibilities: a value of +type Either a b is either Left a or Right b.

The Either type is sometimes used to represent a value which is +either correct or an error; by convention, the Left constructor is +used to hold an error value and the Right constructor is used to +hold a correct value (mnemonic: "right" also means "correct").

Examples

The type Either String Int is the type of values which can be either +a String or an Int. The Left constructor can be used only on +Strings, and the Right constructor can be used only on Ints:

>>> let s = Left "foo" :: Either String Int
+>>> s
+Left "foo"
+>>> let n = Right 3 :: Either String Int
+>>> n
+Right 3
+>>> :type s
+s :: Either String Int
+>>> :type n
+n :: Either String Int
+

The fmap from our Functor instance will ignore Left values, but +will apply the supplied function to values contained in a Right:

>>> let s = Left "foo" :: Either String Int
+>>> let n = Right 3 :: Either String Int
+>>> fmap (*2) s
+Left "foo"
+>>> fmap (*2) n
+Right 6
+

The Monad instance for Either allows us to chain together multiple +actions which may fail, and fail overall if any of the individual +steps failed. First we'll write a function that can either parse an +Int from a Char, or fail.

>>> import Data.Char ( digitToInt, isDigit )
+>>> :{
+    let parseEither :: Char -> Either String Int
+        parseEither c
+          | isDigit c = Right (digitToInt c)
+          | otherwise = Left "parse error"
+>>> :}
+

The following should work, since both '1' and '2' can be +parsed as Ints.

>>> :{
+    let parseMultiple :: Either String Int
+        parseMultiple = do
+          x <- parseEither '1'
+          y <- parseEither '2'
+          return (x + y)
+>>> :}
+
>>> parseMultiple
+Right 3
+

But the following should fail overall, since the first operation where +we attempt to parse 'm' as an Int will fail:

>>> :{
+    let parseMultiple :: Either String Int
+        parseMultiple = do
+          x <- parseEither 'm'
+          y <- parseEither '2'
+          return (x + y)
+>>> :}
+
>>> parseMultiple
+Left "parse error"
+

Constructors

Left a 
Right b 

Instances

Monad (Either e) 

Methods

(>>=) :: Either e a -> (a -> Either e b) -> Either e b #

(>>) :: Either e a -> Either e b -> Either e b #

return :: a -> Either e a #

fail :: String -> Either e a #

Functor (Either a) 

Methods

fmap :: (a -> b) -> Either a a -> Either a b #

(<$) :: a -> Either a b -> Either a a #

Applicative (Either e) 

Methods

pure :: a -> Either e a #

(<*>) :: Either e (a -> b) -> Either e a -> Either e b #

(*>) :: Either e a -> Either e b -> Either e b #

(<*) :: Either e a -> Either e b -> Either e a #

Foldable (Either a) 

Methods

fold :: Monoid m => Either a m -> m #

foldMap :: Monoid m => (a -> m) -> Either a a -> m #

foldr :: (a -> b -> b) -> b -> Either a a -> b #

foldr' :: (a -> b -> b) -> b -> Either a a -> b #

foldl :: (b -> a -> b) -> b -> Either a a -> b #

foldl' :: (b -> a -> b) -> b -> Either a a -> b #

foldr1 :: (a -> a -> a) -> Either a a -> a #

foldl1 :: (a -> a -> a) -> Either a a -> a #

toList :: Either a a -> [a] #

null :: Either a a -> Bool #

length :: Either a a -> Int #

elem :: Eq a => a -> Either a a -> Bool #

maximum :: Ord a => Either a a -> a #

minimum :: Ord a => Either a a -> a #

sum :: Num a => Either a a -> a #

product :: Num a => Either a a -> a #

Traversable (Either a) 

Methods

traverse :: Applicative f => (a -> f b) -> Either a a -> f (Either a b) #

sequenceA :: Applicative f => Either a (f a) -> f (Either a a) #

mapM :: Monad m => (a -> m b) -> Either a a -> m (Either a b) #

sequence :: Monad m => Either a (m a) -> m (Either a a) #

Generic1 (Either a) 

Associated Types

type Rep1 (Either a :: * -> *) :: * -> * #

Methods

from1 :: Either a a -> Rep1 (Either a) a #

to1 :: Rep1 (Either a) a -> Either a a #

(~) * e SomeException => MonadThrow (Either e) 

Methods

throwM :: Exception e => e -> Either e a #

(~) * e SomeException => MonadCatch (Either e)

Since: 0.8.3

Methods

catch :: Exception e => Either e a -> (e -> Either e a) -> Either e a #

(~) * e SomeException => MonadMask (Either e)

Since: 0.8.3

Methods

mask :: ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b #

uninterruptibleMask :: ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b #

(Eq a, Eq b) => Eq (Either a b) 

Methods

(==) :: Either a b -> Either a b -> Bool #

(/=) :: Either a b -> Either a b -> Bool #

(Ord a, Ord b) => Ord (Either a b) 

Methods

compare :: Either a b -> Either a b -> Ordering #

(<) :: Either a b -> Either a b -> Bool #

(<=) :: Either a b -> Either a b -> Bool #

(>) :: Either a b -> Either a b -> Bool #

(>=) :: Either a b -> Either a b -> Bool #

max :: Either a b -> Either a b -> Either a b #

min :: Either a b -> Either a b -> Either a b #

(Read a, Read b) => Read (Either a b) 
(Show a, Show b) => Show (Either a b) 

Methods

showsPrec :: Int -> Either a b -> ShowS #

show :: Either a b -> String #

showList :: [Either a b] -> ShowS #

Generic (Either a b) 

Associated Types

type Rep (Either a b) :: * -> * #

Methods

from :: Either a b -> Rep (Either a b) x #

to :: Rep (Either a b) x -> Either a b #

Semigroup (Either a b) 

Methods

(<>) :: Either a b -> Either a b -> Either a b #

sconcat :: NonEmpty (Either a b) -> Either a b #

stimes :: Integral b => b -> Either a b -> Either a b #

(Lift a, Lift b) => Lift (Either a b) 

Methods

lift :: Either a b -> Q Exp #

(NFData a, NFData b) => NFData (Either a b) 

Methods

rnf :: Either a b -> () #

(Hashable a, Hashable b) => Hashable (Either a b) 

Methods

hashWithSalt :: Int -> Either a b -> Int #

hash :: Either a b -> Int #

type Rep1 (Either a) 
type Rep (Either a b) 
type (==) (Either k k1) a b 
type (==) (Either k k1) a b = EqEither k k1 a b

data ByteString :: * #

A space-efficient representation of a Word8 vector, supporting many + efficient operations.

A ByteString contains 8-bit bytes, or by using the operations from + Data.ByteString.Char8 it can be interpreted as containing 8-bit + characters.

Instances

Eq ByteString 
Data ByteString 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteString -> c ByteString #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteString #

toConstr :: ByteString -> Constr #

dataTypeOf :: ByteString -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ByteString) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteString) #

gmapT :: (forall b. Data b => b -> b) -> ByteString -> ByteString #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r #

gmapQ :: (forall d. Data d => d -> u) -> ByteString -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteString -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

Ord ByteString 
Read ByteString 
Show ByteString 
IsString ByteString 
Semigroup ByteString 
Monoid ByteString 
NFData ByteString 

Methods

rnf :: ByteString -> () #

Hashable ByteString 

data Text :: * #

A space efficient, packed, unboxed Unicode text type.

Instances

Hashable Text 

Methods

hashWithSalt :: Int -> Text -> Int #

hash :: Text -> Int #

type Item Text 
type Item Text = Char

data Map k a :: * -> * -> * #

A Map from keys k to values a.

Instances

Functor (Map k) 

Methods

fmap :: (a -> b) -> Map k a -> Map k b #

(<$) :: a -> Map k b -> Map k a #

Foldable (Map k) 

Methods

fold :: Monoid m => Map k m -> m #

foldMap :: Monoid m => (a -> m) -> Map k a -> m #

foldr :: (a -> b -> b) -> b -> Map k a -> b #

foldr' :: (a -> b -> b) -> b -> Map k a -> b #

foldl :: (b -> a -> b) -> b -> Map k a -> b #

foldl' :: (b -> a -> b) -> b -> Map k a -> b #

foldr1 :: (a -> a -> a) -> Map k a -> a #

foldl1 :: (a -> a -> a) -> Map k a -> a #

toList :: Map k a -> [a] #

null :: Map k a -> Bool #

length :: Map k a -> Int #

elem :: Eq a => a -> Map k a -> Bool #

maximum :: Ord a => Map k a -> a #

minimum :: Ord a => Map k a -> a #

sum :: Num a => Map k a -> a #

product :: Num a => Map k a -> a #

Traversable (Map k) 

Methods

traverse :: Applicative f => (a -> f b) -> Map k a -> f (Map k b) #

sequenceA :: Applicative f => Map k (f a) -> f (Map k a) #

mapM :: Monad m => (a -> m b) -> Map k a -> m (Map k b) #

sequence :: Monad m => Map k (m a) -> m (Map k a) #

Ord k => IsList (Map k v) 

Associated Types

type Item (Map k v) :: * #

Methods

fromList :: [Item (Map k v)] -> Map k v #

fromListN :: Int -> [Item (Map k v)] -> Map k v #

toList :: Map k v -> [Item (Map k v)] #

(Eq k, Eq a) => Eq (Map k a) 

Methods

(==) :: Map k a -> Map k a -> Bool #

(/=) :: Map k a -> Map k a -> Bool #

(Data k, Data a, Ord k) => Data (Map k a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Map k a -> c (Map k a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Map k a) #

toConstr :: Map k a -> Constr #

dataTypeOf :: Map k a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Map k a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Map k a)) #

gmapT :: (forall b. Data b => b -> b) -> Map k a -> Map k a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Map k a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Map k a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Map k a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Map k a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) #

(Ord k, Ord v) => Ord (Map k v) 

Methods

compare :: Map k v -> Map k v -> Ordering #

(<) :: Map k v -> Map k v -> Bool #

(<=) :: Map k v -> Map k v -> Bool #

(>) :: Map k v -> Map k v -> Bool #

(>=) :: Map k v -> Map k v -> Bool #

max :: Map k v -> Map k v -> Map k v #

min :: Map k v -> Map k v -> Map k v #

(Ord k, Read k, Read e) => Read (Map k e) 

Methods

readsPrec :: Int -> ReadS (Map k e) #

readList :: ReadS [Map k e] #

readPrec :: ReadPrec (Map k e) #

readListPrec :: ReadPrec [Map k e] #

(Show k, Show a) => Show (Map k a) 

Methods

showsPrec :: Int -> Map k a -> ShowS #

show :: Map k a -> String #

showList :: [Map k a] -> ShowS #

Ord k => Semigroup (Map k v) 

Methods

(<>) :: Map k v -> Map k v -> Map k v #

sconcat :: NonEmpty (Map k v) -> Map k v #

stimes :: Integral b => b -> Map k v -> Map k v #

Ord k => Monoid (Map k v) 

Methods

mempty :: Map k v #

mappend :: Map k v -> Map k v -> Map k v #

mconcat :: [Map k v] -> Map k v #

(NFData k, NFData a) => NFData (Map k a) 

Methods

rnf :: Map k a -> () #

type Item (Map k v) 
type Item (Map k v) = (k, v)

data HashMap k v :: * -> * -> * #

A map from keys to values. A map cannot contain duplicate keys; + each key can map to at most one value.

Instances

Functor (HashMap k) 

Methods

fmap :: (a -> b) -> HashMap k a -> HashMap k b #

(<$) :: a -> HashMap k b -> HashMap k a #

Foldable (HashMap k) 

Methods

fold :: Monoid m => HashMap k m -> m #

foldMap :: Monoid m => (a -> m) -> HashMap k a -> m #

foldr :: (a -> b -> b) -> b -> HashMap k a -> b #

foldr' :: (a -> b -> b) -> b -> HashMap k a -> b #

foldl :: (b -> a -> b) -> b -> HashMap k a -> b #

foldl' :: (b -> a -> b) -> b -> HashMap k a -> b #

foldr1 :: (a -> a -> a) -> HashMap k a -> a #

foldl1 :: (a -> a -> a) -> HashMap k a -> a #

toList :: HashMap k a -> [a] #

null :: HashMap k a -> Bool #

length :: HashMap k a -> Int #

elem :: Eq a => a -> HashMap k a -> Bool #

maximum :: Ord a => HashMap k a -> a #

minimum :: Ord a => HashMap k a -> a #

sum :: Num a => HashMap k a -> a #

product :: Num a => HashMap k a -> a #

Traversable (HashMap k) 

Methods

traverse :: Applicative f => (a -> f b) -> HashMap k a -> f (HashMap k b) #

sequenceA :: Applicative f => HashMap k (f a) -> f (HashMap k a) #

mapM :: Monad m => (a -> m b) -> HashMap k a -> m (HashMap k b) #

sequence :: Monad m => HashMap k (m a) -> m (HashMap k a) #

(Eq k, Hashable k) => IsList (HashMap k v) 

Associated Types

type Item (HashMap k v) :: * #

Methods

fromList :: [Item (HashMap k v)] -> HashMap k v #

fromListN :: Int -> [Item (HashMap k v)] -> HashMap k v #

toList :: HashMap k v -> [Item (HashMap k v)] #

(Eq k, Eq v) => Eq (HashMap k v) 

Methods

(==) :: HashMap k v -> HashMap k v -> Bool #

(/=) :: HashMap k v -> HashMap k v -> Bool #

(Data k, Data v, Eq k, Hashable k) => Data (HashMap k v) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HashMap k v -> c (HashMap k v) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HashMap k v) #

toConstr :: HashMap k v -> Constr #

dataTypeOf :: HashMap k v -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (HashMap k v)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HashMap k v)) #

gmapT :: (forall b. Data b => b -> b) -> HashMap k v -> HashMap k v #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HashMap k v -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HashMap k v -> r #

gmapQ :: (forall d. Data d => d -> u) -> HashMap k v -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HashMap k v -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HashMap k v -> m (HashMap k v) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HashMap k v -> m (HashMap k v) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HashMap k v -> m (HashMap k v) #

(Eq k, Hashable k, Read k, Read e) => Read (HashMap k e) 
(Show k, Show v) => Show (HashMap k v) 

Methods

showsPrec :: Int -> HashMap k v -> ShowS #

show :: HashMap k v -> String #

showList :: [HashMap k v] -> ShowS #

(Eq k, Hashable k) => Semigroup (HashMap k v) 

Methods

(<>) :: HashMap k v -> HashMap k v -> HashMap k v #

sconcat :: NonEmpty (HashMap k v) -> HashMap k v #

stimes :: Integral b => b -> HashMap k v -> HashMap k v #

(Eq k, Hashable k) => Monoid (HashMap k v) 

Methods

mempty :: HashMap k v #

mappend :: HashMap k v -> HashMap k v -> HashMap k v #

mconcat :: [HashMap k v] -> HashMap k v #

(NFData k, NFData v) => NFData (HashMap k v) 

Methods

rnf :: HashMap k v -> () #

(Hashable k, Hashable v) => Hashable (HashMap k v) 

Methods

hashWithSalt :: Int -> HashMap k v -> Int #

hash :: HashMap k v -> Int #

type Item (HashMap k v) 
type Item (HashMap k v) = (k, v)

data IntMap a :: * -> * #

A map of integers to values a.

Instances

Functor IntMap 

Methods

fmap :: (a -> b) -> IntMap a -> IntMap b #

(<$) :: a -> IntMap b -> IntMap a #

Foldable IntMap 

Methods

fold :: Monoid m => IntMap m -> m #

foldMap :: Monoid m => (a -> m) -> IntMap a -> m #

foldr :: (a -> b -> b) -> b -> IntMap a -> b #

foldr' :: (a -> b -> b) -> b -> IntMap a -> b #

foldl :: (b -> a -> b) -> b -> IntMap a -> b #

foldl' :: (b -> a -> b) -> b -> IntMap a -> b #

foldr1 :: (a -> a -> a) -> IntMap a -> a #

foldl1 :: (a -> a -> a) -> IntMap a -> a #

toList :: IntMap a -> [a] #

null :: IntMap a -> Bool #

length :: IntMap a -> Int #

elem :: Eq a => a -> IntMap a -> Bool #

maximum :: Ord a => IntMap a -> a #

minimum :: Ord a => IntMap a -> a #

sum :: Num a => IntMap a -> a #

product :: Num a => IntMap a -> a #

Traversable IntMap 

Methods

traverse :: Applicative f => (a -> f b) -> IntMap a -> f (IntMap b) #

sequenceA :: Applicative f => IntMap (f a) -> f (IntMap a) #

mapM :: Monad m => (a -> m b) -> IntMap a -> m (IntMap b) #

sequence :: Monad m => IntMap (m a) -> m (IntMap a) #

IsList (IntMap a) 

Associated Types

type Item (IntMap a) :: * #

Methods

fromList :: [Item (IntMap a)] -> IntMap a #

fromListN :: Int -> [Item (IntMap a)] -> IntMap a #

toList :: IntMap a -> [Item (IntMap a)] #

Eq a => Eq (IntMap a) 

Methods

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

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

Data a => Data (IntMap a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IntMap a -> c (IntMap a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IntMap a) #

toConstr :: IntMap a -> Constr #

dataTypeOf :: IntMap a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (IntMap a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IntMap a)) #

gmapT :: (forall b. Data b => b -> b) -> IntMap a -> IntMap a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IntMap a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IntMap a -> r #

gmapQ :: (forall d. Data d => d -> u) -> IntMap a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IntMap a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IntMap a -> m (IntMap a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IntMap a -> m (IntMap a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IntMap a -> m (IntMap a) #

Ord a => Ord (IntMap a) 

Methods

compare :: IntMap a -> IntMap a -> Ordering #

(<) :: IntMap a -> IntMap a -> Bool #

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

(>) :: IntMap a -> IntMap a -> Bool #

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

max :: IntMap a -> IntMap a -> IntMap a #

min :: IntMap a -> IntMap a -> IntMap a #

Read e => Read (IntMap e) 
Show a => Show (IntMap a) 

Methods

showsPrec :: Int -> IntMap a -> ShowS #

show :: IntMap a -> String #

showList :: [IntMap a] -> ShowS #

Semigroup (IntMap a) 

Methods

(<>) :: IntMap a -> IntMap a -> IntMap a #

sconcat :: NonEmpty (IntMap a) -> IntMap a #

stimes :: Integral b => b -> IntMap a -> IntMap a #

Monoid (IntMap a) 

Methods

mempty :: IntMap a #

mappend :: IntMap a -> IntMap a -> IntMap a #

mconcat :: [IntMap a] -> IntMap a #

NFData a => NFData (IntMap a) 

Methods

rnf :: IntMap a -> () #

type Item (IntMap a) 
type Item (IntMap a) = (Key, a)

data Set a :: * -> * #

A set of values a.

Instances

Foldable Set 

Methods

fold :: Monoid m => Set m -> m #

foldMap :: Monoid m => (a -> m) -> Set a -> m #

foldr :: (a -> b -> b) -> b -> Set a -> b #

foldr' :: (a -> b -> b) -> b -> Set a -> b #

foldl :: (b -> a -> b) -> b -> Set a -> b #

foldl' :: (b -> a -> b) -> b -> Set a -> b #

foldr1 :: (a -> a -> a) -> Set a -> a #

foldl1 :: (a -> a -> a) -> Set a -> a #

toList :: Set a -> [a] #

null :: Set a -> Bool #

length :: Set a -> Int #

elem :: Eq a => a -> Set a -> Bool #

maximum :: Ord a => Set a -> a #

minimum :: Ord a => Set a -> a #

sum :: Num a => Set a -> a #

product :: Num a => Set a -> a #

Ord a => IsList (Set a) 

Associated Types

type Item (Set a) :: * #

Methods

fromList :: [Item (Set a)] -> Set a #

fromListN :: Int -> [Item (Set a)] -> Set a #

toList :: Set a -> [Item (Set a)] #

Eq a => Eq (Set a) 

Methods

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

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

(Data a, Ord a) => Data (Set a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Set a -> c (Set a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Set a) #

toConstr :: Set a -> Constr #

dataTypeOf :: Set a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Set a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Set a)) #

gmapT :: (forall b. Data b => b -> b) -> Set a -> Set a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Set a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Set a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) #

Ord a => Ord (Set a) 

Methods

compare :: Set a -> Set a -> Ordering #

(<) :: Set a -> Set a -> Bool #

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

(>) :: Set a -> Set a -> Bool #

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

max :: Set a -> Set a -> Set a #

min :: Set a -> Set a -> Set a #

(Read a, Ord a) => Read (Set a) 
Show a => Show (Set a) 

Methods

showsPrec :: Int -> Set a -> ShowS #

show :: Set a -> String #

showList :: [Set a] -> ShowS #

Ord a => Semigroup (Set a) 

Methods

(<>) :: Set a -> Set a -> Set a #

sconcat :: NonEmpty (Set a) -> Set a #

stimes :: Integral b => b -> Set a -> Set a #

Ord a => Monoid (Set a) 

Methods

mempty :: Set a #

mappend :: Set a -> Set a -> Set a #

mconcat :: [Set a] -> Set a #

NFData a => NFData (Set a) 

Methods

rnf :: Set a -> () #

type Item (Set a) 
type Item (Set a) = a

data HashSet a :: * -> * #

A set of values. A set cannot contain duplicate values.

Instances

Foldable HashSet 

Methods

fold :: Monoid m => HashSet m -> m #

foldMap :: Monoid m => (a -> m) -> HashSet a -> m #

foldr :: (a -> b -> b) -> b -> HashSet a -> b #

foldr' :: (a -> b -> b) -> b -> HashSet a -> b #

foldl :: (b -> a -> b) -> b -> HashSet a -> b #

foldl' :: (b -> a -> b) -> b -> HashSet a -> b #

foldr1 :: (a -> a -> a) -> HashSet a -> a #

foldl1 :: (a -> a -> a) -> HashSet a -> a #

toList :: HashSet a -> [a] #

null :: HashSet a -> Bool #

length :: HashSet a -> Int #

elem :: Eq a => a -> HashSet a -> Bool #

maximum :: Ord a => HashSet a -> a #

minimum :: Ord a => HashSet a -> a #

sum :: Num a => HashSet a -> a #

product :: Num a => HashSet a -> a #

(Eq a, Hashable a) => IsList (HashSet a) 

Associated Types

type Item (HashSet a) :: * #

Methods

fromList :: [Item (HashSet a)] -> HashSet a #

fromListN :: Int -> [Item (HashSet a)] -> HashSet a #

toList :: HashSet a -> [Item (HashSet a)] #

(Hashable a, Eq a) => Eq (HashSet a) 

Methods

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

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

(Data a, Eq a, Hashable a) => Data (HashSet a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HashSet a -> c (HashSet a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HashSet a) #

toConstr :: HashSet a -> Constr #

dataTypeOf :: HashSet a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (HashSet a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HashSet a)) #

gmapT :: (forall b. Data b => b -> b) -> HashSet a -> HashSet a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HashSet a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HashSet a -> r #

gmapQ :: (forall d. Data d => d -> u) -> HashSet a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HashSet a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HashSet a -> m (HashSet a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HashSet a -> m (HashSet a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HashSet a -> m (HashSet a) #

(Eq a, Hashable a, Read a) => Read (HashSet a) 
Show a => Show (HashSet a) 

Methods

showsPrec :: Int -> HashSet a -> ShowS #

show :: HashSet a -> String #

showList :: [HashSet a] -> ShowS #

(Hashable a, Eq a) => Semigroup (HashSet a) 

Methods

(<>) :: HashSet a -> HashSet a -> HashSet a #

sconcat :: NonEmpty (HashSet a) -> HashSet a #

stimes :: Integral b => b -> HashSet a -> HashSet a #

(Hashable a, Eq a) => Monoid (HashSet a) 

Methods

mempty :: HashSet a #

mappend :: HashSet a -> HashSet a -> HashSet a #

mconcat :: [HashSet a] -> HashSet a #

NFData a => NFData (HashSet a) 

Methods

rnf :: HashSet a -> () #

Hashable a => Hashable (HashSet a) 

Methods

hashWithSalt :: Int -> HashSet a -> Int #

hash :: HashSet a -> Int #

type Item (HashSet a) 
type Item (HashSet a) = a

data IntSet :: * #

A set of integers.

Instances

IsList IntSet 

Associated Types

type Item IntSet :: * #

Eq IntSet 

Methods

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

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

Data IntSet 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IntSet -> c IntSet #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IntSet #

toConstr :: IntSet -> Constr #

dataTypeOf :: IntSet -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c IntSet) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IntSet) #

gmapT :: (forall b. Data b => b -> b) -> IntSet -> IntSet #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IntSet -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IntSet -> r #

gmapQ :: (forall d. Data d => d -> u) -> IntSet -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IntSet -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IntSet -> m IntSet #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IntSet -> m IntSet #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IntSet -> m IntSet #

Ord IntSet 
Read IntSet 
Show IntSet 
Semigroup IntSet 
Monoid IntSet 
NFData IntSet 

Methods

rnf :: IntSet -> () #

type Item IntSet 
type Item IntSet = Key

data Seq a :: * -> * #

General-purpose finite sequences.

Instances

Monad Seq 

Methods

(>>=) :: Seq a -> (a -> Seq b) -> Seq b #

(>>) :: Seq a -> Seq b -> Seq b #

return :: a -> Seq a #

fail :: String -> Seq a #

Functor Seq 

Methods

fmap :: (a -> b) -> Seq a -> Seq b #

(<$) :: a -> Seq b -> Seq a #

Applicative Seq 

Methods

pure :: a -> Seq a #

(<*>) :: Seq (a -> b) -> Seq a -> Seq b #

(*>) :: Seq a -> Seq b -> Seq b #

(<*) :: Seq a -> Seq b -> Seq a #

Foldable Seq 

Methods

fold :: Monoid m => Seq m -> m #

foldMap :: Monoid m => (a -> m) -> Seq a -> m #

foldr :: (a -> b -> b) -> b -> Seq a -> b #

foldr' :: (a -> b -> b) -> b -> Seq a -> b #

foldl :: (b -> a -> b) -> b -> Seq a -> b #

foldl' :: (b -> a -> b) -> b -> Seq a -> b #

foldr1 :: (a -> a -> a) -> Seq a -> a #

foldl1 :: (a -> a -> a) -> Seq a -> a #

toList :: Seq a -> [a] #

null :: Seq a -> Bool #

length :: Seq a -> Int #

elem :: Eq a => a -> Seq a -> Bool #

maximum :: Ord a => Seq a -> a #

minimum :: Ord a => Seq a -> a #

sum :: Num a => Seq a -> a #

product :: Num a => Seq a -> a #

Traversable Seq 

Methods

traverse :: Applicative f => (a -> f b) -> Seq a -> f (Seq b) #

sequenceA :: Applicative f => Seq (f a) -> f (Seq a) #

mapM :: Monad m => (a -> m b) -> Seq a -> m (Seq b) #

sequence :: Monad m => Seq (m a) -> m (Seq a) #

Alternative Seq 

Methods

empty :: Seq a #

(<|>) :: Seq a -> Seq a -> Seq a #

some :: Seq a -> Seq [a] #

many :: Seq a -> Seq [a] #

MonadPlus Seq 

Methods

mzero :: Seq a #

mplus :: Seq a -> Seq a -> Seq a #

IsList (Seq a) 

Associated Types

type Item (Seq a) :: * #

Methods

fromList :: [Item (Seq a)] -> Seq a #

fromListN :: Int -> [Item (Seq a)] -> Seq a #

toList :: Seq a -> [Item (Seq a)] #

Eq a => Eq (Seq a) 

Methods

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

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

Data a => Data (Seq a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Seq a -> c (Seq a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Seq a) #

toConstr :: Seq a -> Constr #

dataTypeOf :: Seq a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Seq a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Seq a)) #

gmapT :: (forall b. Data b => b -> b) -> Seq a -> Seq a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Seq a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Seq a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) #

Ord a => Ord (Seq a) 

Methods

compare :: Seq a -> Seq a -> Ordering #

(<) :: Seq a -> Seq a -> Bool #

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

(>) :: Seq a -> Seq a -> Bool #

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

max :: Seq a -> Seq a -> Seq a #

min :: Seq a -> Seq a -> Seq a #

Read a => Read (Seq a) 
Show a => Show (Seq a) 

Methods

showsPrec :: Int -> Seq a -> ShowS #

show :: Seq a -> String #

showList :: [Seq a] -> ShowS #

IsString (Seq Char) 

Methods

fromString :: String -> Seq Char #

Semigroup (Seq a) 

Methods

(<>) :: Seq a -> Seq a -> Seq a #

sconcat :: NonEmpty (Seq a) -> Seq a #

stimes :: Integral b => b -> Seq a -> Seq a #

Monoid (Seq a) 

Methods

mempty :: Seq a #

mappend :: Seq a -> Seq a -> Seq a #

mconcat :: [Seq a] -> Seq a #

NFData a => NFData (Seq a) 

Methods

rnf :: Seq a -> () #

type Item (Seq a) 
type Item (Seq a) = a

newtype Identity a :: * -> * #

Identity functor and monad. (a non-strict monad)

Since: 4.8.0.0

Constructors

Identity 

Fields

Instances

Monad Identity 

Methods

(>>=) :: Identity a -> (a -> Identity b) -> Identity b #

(>>) :: Identity a -> Identity b -> Identity b #

return :: a -> Identity a #

fail :: String -> Identity a #

Functor Identity 

Methods

fmap :: (a -> b) -> Identity a -> Identity b #

(<$) :: a -> Identity b -> Identity a #

MonadFix Identity 

Methods

mfix :: (a -> Identity a) -> Identity a #

Applicative Identity 

Methods

pure :: a -> Identity a #

(<*>) :: Identity (a -> b) -> Identity a -> Identity b #

(*>) :: Identity a -> Identity b -> Identity b #

(<*) :: Identity a -> Identity b -> Identity a #

Foldable Identity 

Methods

fold :: Monoid m => Identity m -> m #

foldMap :: Monoid m => (a -> m) -> Identity a -> m #

foldr :: (a -> b -> b) -> b -> Identity a -> b #

foldr' :: (a -> b -> b) -> b -> Identity a -> b #

foldl :: (b -> a -> b) -> b -> Identity a -> b #

foldl' :: (b -> a -> b) -> b -> Identity a -> b #

foldr1 :: (a -> a -> a) -> Identity a -> a #

foldl1 :: (a -> a -> a) -> Identity a -> a #

toList :: Identity a -> [a] #

null :: Identity a -> Bool #

length :: Identity a -> Int #

elem :: Eq a => a -> Identity a -> Bool #

maximum :: Ord a => Identity a -> a #

minimum :: Ord a => Identity a -> a #

sum :: Num a => Identity a -> a #

product :: Num a => Identity a -> a #

Traversable Identity 

Methods

traverse :: Applicative f => (a -> f b) -> Identity a -> f (Identity b) #

sequenceA :: Applicative f => Identity (f a) -> f (Identity a) #

mapM :: Monad m => (a -> m b) -> Identity a -> m (Identity b) #

sequence :: Monad m => Identity (m a) -> m (Identity a) #

Generic1 Identity 

Associated Types

type Rep1 (Identity :: * -> *) :: * -> * #

Methods

from1 :: Identity a -> Rep1 Identity a #

to1 :: Rep1 Identity a -> Identity a #

MonadZip Identity 

Methods

mzip :: Identity a -> Identity b -> Identity (a, b) #

mzipWith :: (a -> b -> c) -> Identity a -> Identity b -> Identity c #

munzip :: Identity (a, b) -> (Identity a, Identity b) #

Bounded a => Bounded (Identity a) 
Enum a => Enum (Identity a) 
Eq a => Eq (Identity a) 

Methods

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

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

Floating a => Floating (Identity a) 
Fractional a => Fractional (Identity a) 
Integral a => Integral (Identity a) 
Data a => Data (Identity a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Identity a -> c (Identity a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Identity a) #

toConstr :: Identity a -> Constr #

dataTypeOf :: Identity a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Identity a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Identity a)) #

gmapT :: (forall b. Data b => b -> b) -> Identity a -> Identity a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Identity a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Identity a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Identity a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Identity a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Identity a -> m (Identity a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Identity a -> m (Identity a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Identity a -> m (Identity a) #

Num a => Num (Identity a) 
Ord a => Ord (Identity a) 

Methods

compare :: Identity a -> Identity a -> Ordering #

(<) :: Identity a -> Identity a -> Bool #

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

(>) :: Identity a -> Identity a -> Bool #

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

max :: Identity a -> Identity a -> Identity a #

min :: Identity a -> Identity a -> Identity a #

Read a => Read (Identity a)

This instance would be equivalent to the derived instances of the + Identity newtype if the runIdentity field were removed

Real a => Real (Identity a) 

Methods

toRational :: Identity a -> Rational #

RealFloat a => RealFloat (Identity a) 
RealFrac a => RealFrac (Identity a) 

Methods

properFraction :: Integral b => Identity a -> (b, Identity a) #

truncate :: Integral b => Identity a -> b #

round :: Integral b => Identity a -> b #

ceiling :: Integral b => Identity a -> b #

floor :: Integral b => Identity a -> b #

Show a => Show (Identity a)

This instance would be equivalent to the derived instances of the + Identity newtype if the runIdentity field were removed

Methods

showsPrec :: Int -> Identity a -> ShowS #

show :: Identity a -> String #

showList :: [Identity a] -> ShowS #

Ix a => Ix (Identity a) 
IsString a => IsString (Identity a) 

Methods

fromString :: String -> Identity a #

Generic (Identity a) 

Associated Types

type Rep (Identity a) :: * -> * #

Methods

from :: Identity a -> Rep (Identity a) x #

to :: Rep (Identity a) x -> Identity a #

Semigroup a => Semigroup (Identity a) 

Methods

(<>) :: Identity a -> Identity a -> Identity a #

sconcat :: NonEmpty (Identity a) -> Identity a #

stimes :: Integral b => b -> Identity a -> Identity a #

Monoid a => Monoid (Identity a) 

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

mconcat :: [Identity a] -> Identity a #

Storable a => Storable (Identity a) 

Methods

sizeOf :: Identity a -> Int #

alignment :: Identity a -> Int #

peekElemOff :: Ptr (Identity a) -> Int -> IO (Identity a) #

pokeElemOff :: Ptr (Identity a) -> Int -> Identity a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Identity a) #

pokeByteOff :: Ptr b -> Int -> Identity a -> IO () #

peek :: Ptr (Identity a) -> IO (Identity a) #

poke :: Ptr (Identity a) -> Identity a -> IO () #

Bits a => Bits (Identity a) 
FiniteBits a => FiniteBits (Identity a) 
NFData a => NFData (Identity a)

Since: 1.4.0.0

Methods

rnf :: Identity a -> () #

type Rep1 Identity 
type Rep1 Identity = D1 (MetaData "Identity" "Data.Functor.Identity" "base" True) (C1 (MetaCons "Identity" PrefixI True) (S1 (MetaSel (Just Symbol "runIdentity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep (Identity a) 
type Rep (Identity a) = D1 (MetaData "Identity" "Data.Functor.Identity" "base" True) (C1 (MetaCons "Identity" PrefixI True) (S1 (MetaSel (Just Symbol "runIdentity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

data SomeException :: * where #

The SomeException type is the root of the exception type hierarchy. +When an exception of type e is thrown, behind the scenes it is +encapsulated in a SomeException.

Constructors

SomeException :: SomeException 

type String = [Char] #

A String is a list of characters. String constants in Haskell are values + of type String.

type FilePath = String #

File and directory names are values of type String, whose precise + meaning is operating system dependent. Files can be opened, yielding a + handle which can then be used to operate on the contents of that file.

Numbers

data Word :: * #

A Word is an unsigned integral type, with the same size as Int.

Instances

Bounded Word 
Enum Word 

Methods

succ :: Word -> Word #

pred :: Word -> Word #

toEnum :: Int -> Word #

fromEnum :: Word -> Int #

enumFrom :: Word -> [Word] #

enumFromThen :: Word -> Word -> [Word] #

enumFromTo :: Word -> Word -> [Word] #

enumFromThenTo :: Word -> Word -> Word -> [Word] #

Eq Word 

Methods

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

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

Integral Word 

Methods

quot :: Word -> Word -> Word #

rem :: Word -> Word -> Word #

div :: Word -> Word -> Word #

mod :: Word -> Word -> Word #

quotRem :: Word -> Word -> (Word, Word) #

divMod :: Word -> Word -> (Word, Word) #

toInteger :: Word -> Integer #

Num Word 

Methods

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

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

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

negate :: Word -> Word #

abs :: Word -> Word #

signum :: Word -> Word #

fromInteger :: Integer -> Word #

Ord Word 

Methods

compare :: Word -> Word -> Ordering #

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

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

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

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

max :: Word -> Word -> Word #

min :: Word -> Word -> Word #

Read Word 
Real Word 

Methods

toRational :: Word -> Rational #

Show Word 

Methods

showsPrec :: Int -> Word -> ShowS #

show :: Word -> String #

showList :: [Word] -> ShowS #

Lift Word 

Methods

lift :: Word -> Q Exp #

NFData Word 

Methods

rnf :: Word -> () #

Hashable Word 

Methods

hashWithSalt :: Int -> Word -> Int #

hash :: Word -> Int #

Functor (URec Word) 

Methods

fmap :: (a -> b) -> URec Word a -> URec Word b #

(<$) :: a -> URec Word b -> URec Word a #

Foldable (URec Word) 

Methods

fold :: Monoid m => URec Word m -> m #

foldMap :: Monoid m => (a -> m) -> URec Word a -> m #

foldr :: (a -> b -> b) -> b -> URec Word a -> b #

foldr' :: (a -> b -> b) -> b -> URec Word a -> b #

foldl :: (b -> a -> b) -> b -> URec Word a -> b #

foldl' :: (b -> a -> b) -> b -> URec Word a -> b #

foldr1 :: (a -> a -> a) -> URec Word a -> a #

foldl1 :: (a -> a -> a) -> URec Word a -> a #

toList :: URec Word a -> [a] #

null :: URec Word a -> Bool #

length :: URec Word a -> Int #

elem :: Eq a => a -> URec Word a -> Bool #

maximum :: Ord a => URec Word a -> a #

minimum :: Ord a => URec Word a -> a #

sum :: Num a => URec Word a -> a #

product :: Num a => URec Word a -> a #

Traversable (URec Word) 

Methods

traverse :: Applicative f => (a -> f b) -> URec Word a -> f (URec Word b) #

sequenceA :: Applicative f => URec Word (f a) -> f (URec Word a) #

mapM :: Monad m => (a -> m b) -> URec Word a -> m (URec Word b) #

sequence :: Monad m => URec Word (m a) -> m (URec Word a) #

Generic1 (URec Word) 

Associated Types

type Rep1 (URec Word :: * -> *) :: * -> * #

Methods

from1 :: URec Word a -> Rep1 (URec Word) a #

to1 :: Rep1 (URec Word) a -> URec Word a #

Eq (URec Word p) 

Methods

(==) :: URec Word p -> URec Word p -> Bool #

(/=) :: URec Word p -> URec Word p -> Bool #

Ord (URec Word p) 

Methods

compare :: URec Word p -> URec Word p -> Ordering #

(<) :: URec Word p -> URec Word p -> Bool #

(<=) :: URec Word p -> URec Word p -> Bool #

(>) :: URec Word p -> URec Word p -> Bool #

(>=) :: URec Word p -> URec Word p -> Bool #

max :: URec Word p -> URec Word p -> URec Word p #

min :: URec Word p -> URec Word p -> URec Word p #

Show (URec Word p) 

Methods

showsPrec :: Int -> URec Word p -> ShowS #

show :: URec Word p -> String #

showList :: [URec Word p] -> ShowS #

Generic (URec Word p) 

Associated Types

type Rep (URec Word p) :: * -> * #

Methods

from :: URec Word p -> Rep (URec Word p) x #

to :: Rep (URec Word p) x -> URec Word p #

data URec Word

Used for marking occurrences of Word#

data URec Word = UWord {}
type Rep1 (URec Word) 
type Rep1 (URec Word) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UWord" PrefixI True) (S1 (MetaSel (Just Symbol "uWord#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UWord))
type Rep (URec Word p) 
type Rep (URec Word p) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UWord" PrefixI True) (S1 (MetaSel (Just Symbol "uWord#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UWord))

data Word8 :: * #

8-bit unsigned integer type

Instances

Bounded Word8 
Enum Word8 
Eq Word8 

Methods

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

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

Integral Word8 
Num Word8 
Ord Word8 

Methods

compare :: Word8 -> Word8 -> Ordering #

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

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

(>) :: Word8 -> Word8 -> Bool #

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

max :: Word8 -> Word8 -> Word8 #

min :: Word8 -> Word8 -> Word8 #

Read Word8 
Real Word8 

Methods

toRational :: Word8 -> Rational #

Show Word8 

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Ix Word8 
Lift Word8 

Methods

lift :: Word8 -> Q Exp #

Bits Word8 
FiniteBits Word8 
NFData Word8 

Methods

rnf :: Word8 -> () #

Hashable Word8 

Methods

hashWithSalt :: Int -> Word8 -> Int #

hash :: Word8 -> Int #

data Word16 :: * #

16-bit unsigned integer type

Instances

Bounded Word16 
Enum Word16 
Eq Word16 

Methods

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

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

Integral Word16 
Num Word16 
Ord Word16 
Read Word16 
Real Word16 
Show Word16 
Ix Word16 
Lift Word16 

Methods

lift :: Word16 -> Q Exp #

Bits Word16 
FiniteBits Word16 
NFData Word16 

Methods

rnf :: Word16 -> () #

Hashable Word16 

Methods

hashWithSalt :: Int -> Word16 -> Int #

hash :: Word16 -> Int #

data Word32 :: * #

32-bit unsigned integer type

Instances

Bounded Word32 
Enum Word32 
Eq Word32 

Methods

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

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

Integral Word32 
Num Word32 
Ord Word32 
Read Word32 
Real Word32 
Show Word32 
Ix Word32 
Lift Word32 

Methods

lift :: Word32 -> Q Exp #

Bits Word32 
FiniteBits Word32 
NFData Word32 

Methods

rnf :: Word32 -> () #

Hashable Word32 

Methods

hashWithSalt :: Int -> Word32 -> Int #

hash :: Word32 -> Int #

data Word64 :: * #

64-bit unsigned integer type

Instances

Bounded Word64 
Enum Word64 
Eq Word64 

Methods

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

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

Integral Word64 
Num Word64 
Ord Word64 
Read Word64 
Real Word64 
Show Word64 
Ix Word64 
Lift Word64 

Methods

lift :: Word64 -> Q Exp #

Bits Word64 
FiniteBits Word64 
NFData Word64 

Methods

rnf :: Word64 -> () #

Hashable Word64 

Methods

hashWithSalt :: Int -> Word64 -> Int #

hash :: Word64 -> Int #

data Int :: * #

A fixed-precision integer type with at least the range [-2^29 .. 2^29-1]. + The exact range for a given implementation can be determined by using + minBound and maxBound from the Bounded class.

Instances

Bounded Int 

Methods

minBound :: Int #

maxBound :: Int #

Enum Int 

Methods

succ :: Int -> Int #

pred :: Int -> Int #

toEnum :: Int -> Int #

fromEnum :: Int -> Int #

enumFrom :: Int -> [Int] #

enumFromThen :: Int -> Int -> [Int] #

enumFromTo :: Int -> Int -> [Int] #

enumFromThenTo :: Int -> Int -> Int -> [Int] #

Eq Int 

Methods

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

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

Integral Int 

Methods

quot :: Int -> Int -> Int #

rem :: Int -> Int -> Int #

div :: Int -> Int -> Int #

mod :: Int -> Int -> Int #

quotRem :: Int -> Int -> (Int, Int) #

divMod :: Int -> Int -> (Int, Int) #

toInteger :: Int -> Integer #

Num Int 

Methods

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

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

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

negate :: Int -> Int #

abs :: Int -> Int #

signum :: Int -> Int #

fromInteger :: Integer -> Int #

Ord Int 

Methods

compare :: Int -> Int -> Ordering #

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

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

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

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

max :: Int -> Int -> Int #

min :: Int -> Int -> Int #

Read Int 
Real Int 

Methods

toRational :: Int -> Rational #

Show Int 

Methods

showsPrec :: Int -> Int -> ShowS #

show :: Int -> String #

showList :: [Int] -> ShowS #

Lift Int 

Methods

lift :: Int -> Q Exp #

NFData Int 

Methods

rnf :: Int -> () #

Hashable Int 

Methods

hashWithSalt :: Int -> Int -> Int #

hash :: Int -> Int #

Functor (URec Int) 

Methods

fmap :: (a -> b) -> URec Int a -> URec Int b #

(<$) :: a -> URec Int b -> URec Int a #

Foldable (URec Int) 

Methods

fold :: Monoid m => URec Int m -> m #

foldMap :: Monoid m => (a -> m) -> URec Int a -> m #

foldr :: (a -> b -> b) -> b -> URec Int a -> b #

foldr' :: (a -> b -> b) -> b -> URec Int a -> b #

foldl :: (b -> a -> b) -> b -> URec Int a -> b #

foldl' :: (b -> a -> b) -> b -> URec Int a -> b #

foldr1 :: (a -> a -> a) -> URec Int a -> a #

foldl1 :: (a -> a -> a) -> URec Int a -> a #

toList :: URec Int a -> [a] #

null :: URec Int a -> Bool #

length :: URec Int a -> Int #

elem :: Eq a => a -> URec Int a -> Bool #

maximum :: Ord a => URec Int a -> a #

minimum :: Ord a => URec Int a -> a #

sum :: Num a => URec Int a -> a #

product :: Num a => URec Int a -> a #

Traversable (URec Int) 

Methods

traverse :: Applicative f => (a -> f b) -> URec Int a -> f (URec Int b) #

sequenceA :: Applicative f => URec Int (f a) -> f (URec Int a) #

mapM :: Monad m => (a -> m b) -> URec Int a -> m (URec Int b) #

sequence :: Monad m => URec Int (m a) -> m (URec Int a) #

Generic1 (URec Int) 

Associated Types

type Rep1 (URec Int :: * -> *) :: * -> * #

Methods

from1 :: URec Int a -> Rep1 (URec Int) a #

to1 :: Rep1 (URec Int) a -> URec Int a #

Eq (URec Int p) 

Methods

(==) :: URec Int p -> URec Int p -> Bool #

(/=) :: URec Int p -> URec Int p -> Bool #

Ord (URec Int p) 

Methods

compare :: URec Int p -> URec Int p -> Ordering #

(<) :: URec Int p -> URec Int p -> Bool #

(<=) :: URec Int p -> URec Int p -> Bool #

(>) :: URec Int p -> URec Int p -> Bool #

(>=) :: URec Int p -> URec Int p -> Bool #

max :: URec Int p -> URec Int p -> URec Int p #

min :: URec Int p -> URec Int p -> URec Int p #

Show (URec Int p) 

Methods

showsPrec :: Int -> URec Int p -> ShowS #

show :: URec Int p -> String #

showList :: [URec Int p] -> ShowS #

Generic (URec Int p) 

Associated Types

type Rep (URec Int p) :: * -> * #

Methods

from :: URec Int p -> Rep (URec Int p) x #

to :: Rep (URec Int p) x -> URec Int p #

data URec Int

Used for marking occurrences of Int#

data URec Int = UInt {}
type Rep1 (URec Int) 
type Rep1 (URec Int) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UInt" PrefixI True) (S1 (MetaSel (Just Symbol "uInt#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UInt))
type Rep (URec Int p) 
type Rep (URec Int p) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UInt" PrefixI True) (S1 (MetaSel (Just Symbol "uInt#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UInt))

data Int8 :: * #

8-bit signed integer type

Instances

Bounded Int8 
Enum Int8 

Methods

succ :: Int8 -> Int8 #

pred :: Int8 -> Int8 #

toEnum :: Int -> Int8 #

fromEnum :: Int8 -> Int #

enumFrom :: Int8 -> [Int8] #

enumFromThen :: Int8 -> Int8 -> [Int8] #

enumFromTo :: Int8 -> Int8 -> [Int8] #

enumFromThenTo :: Int8 -> Int8 -> Int8 -> [Int8] #

Eq Int8 

Methods

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

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

Integral Int8 

Methods

quot :: Int8 -> Int8 -> Int8 #

rem :: Int8 -> Int8 -> Int8 #

div :: Int8 -> Int8 -> Int8 #

mod :: Int8 -> Int8 -> Int8 #

quotRem :: Int8 -> Int8 -> (Int8, Int8) #

divMod :: Int8 -> Int8 -> (Int8, Int8) #

toInteger :: Int8 -> Integer #

Num Int8 

Methods

(+) :: Int8 -> Int8 -> Int8 #

(-) :: Int8 -> Int8 -> Int8 #

(*) :: Int8 -> Int8 -> Int8 #

negate :: Int8 -> Int8 #

abs :: Int8 -> Int8 #

signum :: Int8 -> Int8 #

fromInteger :: Integer -> Int8 #

Ord Int8 

Methods

compare :: Int8 -> Int8 -> Ordering #

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

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

(>) :: Int8 -> Int8 -> Bool #

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

max :: Int8 -> Int8 -> Int8 #

min :: Int8 -> Int8 -> Int8 #

Read Int8 
Real Int8 

Methods

toRational :: Int8 -> Rational #

Show Int8 

Methods

showsPrec :: Int -> Int8 -> ShowS #

show :: Int8 -> String #

showList :: [Int8] -> ShowS #

Ix Int8 

Methods

range :: (Int8, Int8) -> [Int8] #

index :: (Int8, Int8) -> Int8 -> Int #

unsafeIndex :: (Int8, Int8) -> Int8 -> Int

inRange :: (Int8, Int8) -> Int8 -> Bool #

rangeSize :: (Int8, Int8) -> Int #

unsafeRangeSize :: (Int8, Int8) -> Int

Lift Int8 

Methods

lift :: Int8 -> Q Exp #

Bits Int8 
FiniteBits Int8 
NFData Int8 

Methods

rnf :: Int8 -> () #

Hashable Int8 

Methods

hashWithSalt :: Int -> Int8 -> Int #

hash :: Int8 -> Int #

data Int16 :: * #

16-bit signed integer type

Instances

Bounded Int16 
Enum Int16 
Eq Int16 

Methods

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

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

Integral Int16 
Num Int16 
Ord Int16 

Methods

compare :: Int16 -> Int16 -> Ordering #

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

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

(>) :: Int16 -> Int16 -> Bool #

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

max :: Int16 -> Int16 -> Int16 #

min :: Int16 -> Int16 -> Int16 #

Read Int16 
Real Int16 

Methods

toRational :: Int16 -> Rational #

Show Int16 

Methods

showsPrec :: Int -> Int16 -> ShowS #

show :: Int16 -> String #

showList :: [Int16] -> ShowS #

Ix Int16 
Lift Int16 

Methods

lift :: Int16 -> Q Exp #

Bits Int16 
FiniteBits Int16 
NFData Int16 

Methods

rnf :: Int16 -> () #

Hashable Int16 

Methods

hashWithSalt :: Int -> Int16 -> Int #

hash :: Int16 -> Int #

data Int32 :: * #

32-bit signed integer type

Instances

Bounded Int32 
Enum Int32 
Eq Int32 

Methods

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

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

Integral Int32 
Num Int32 
Ord Int32 

Methods

compare :: Int32 -> Int32 -> Ordering #

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

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

(>) :: Int32 -> Int32 -> Bool #

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

max :: Int32 -> Int32 -> Int32 #

min :: Int32 -> Int32 -> Int32 #

Read Int32 
Real Int32 

Methods

toRational :: Int32 -> Rational #

Show Int32 

Methods

showsPrec :: Int -> Int32 -> ShowS #

show :: Int32 -> String #

showList :: [Int32] -> ShowS #

Ix Int32 
Lift Int32 

Methods

lift :: Int32 -> Q Exp #

Bits Int32 
FiniteBits Int32 
NFData Int32 

Methods

rnf :: Int32 -> () #

Hashable Int32 

Methods

hashWithSalt :: Int -> Int32 -> Int #

hash :: Int32 -> Int #

data Int64 :: * #

64-bit signed integer type

Instances

Bounded Int64 
Enum Int64 
Eq Int64 

Methods

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

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

Integral Int64 
Num Int64 
Ord Int64 

Methods

compare :: Int64 -> Int64 -> Ordering #

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

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

(>) :: Int64 -> Int64 -> Bool #

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

max :: Int64 -> Int64 -> Int64 #

min :: Int64 -> Int64 -> Int64 #

Read Int64 
Real Int64 

Methods

toRational :: Int64 -> Rational #

Show Int64 

Methods

showsPrec :: Int -> Int64 -> ShowS #

show :: Int64 -> String #

showList :: [Int64] -> ShowS #

Ix Int64 
Lift Int64 

Methods

lift :: Int64 -> Q Exp #

Bits Int64 
FiniteBits Int64 
NFData Int64 

Methods

rnf :: Int64 -> () #

Hashable Int64 

Methods

hashWithSalt :: Int -> Int64 -> Int #

hash :: Int64 -> Int #

data Integer :: * #

Invariant: Jn# and Jp# are used iff value doesn't fit in S#

Useful properties resulting from the invariants:

Instances

Enum Integer 
Eq Integer 

Methods

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

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

Integral Integer 
Num Integer 
Ord Integer 
Read Integer 
Real Integer 
Show Integer 
Lift Integer 

Methods

lift :: Integer -> Q Exp #

NFData Integer 

Methods

rnf :: Integer -> () #

Hashable Integer 

Methods

hashWithSalt :: Int -> Integer -> Int #

hash :: Integer -> Int #

type Rational = Ratio Integer #

Arbitrary-precision rational numbers, represented as a ratio of + two Integer values. A rational number may be constructed using + the % operator.

data Float :: * #

Single-precision floating point numbers. + It is desirable that this type be at least equal in range and precision + to the IEEE single-precision type.

Instances

Eq Float 

Methods

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

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

Floating Float 
Ord Float 

Methods

compare :: Float -> Float -> Ordering #

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

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

(>) :: Float -> Float -> Bool #

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

max :: Float -> Float -> Float #

min :: Float -> Float -> Float #

Read Float 
RealFloat Float 
Lift Float 

Methods

lift :: Float -> Q Exp #

NFData Float 

Methods

rnf :: Float -> () #

Hashable Float 

Methods

hashWithSalt :: Int -> Float -> Int #

hash :: Float -> Int #

Functor (URec Float) 

Methods

fmap :: (a -> b) -> URec Float a -> URec Float b #

(<$) :: a -> URec Float b -> URec Float a #

Foldable (URec Float) 

Methods

fold :: Monoid m => URec Float m -> m #

foldMap :: Monoid m => (a -> m) -> URec Float a -> m #

foldr :: (a -> b -> b) -> b -> URec Float a -> b #

foldr' :: (a -> b -> b) -> b -> URec Float a -> b #

foldl :: (b -> a -> b) -> b -> URec Float a -> b #

foldl' :: (b -> a -> b) -> b -> URec Float a -> b #

foldr1 :: (a -> a -> a) -> URec Float a -> a #

foldl1 :: (a -> a -> a) -> URec Float a -> a #

toList :: URec Float a -> [a] #

null :: URec Float a -> Bool #

length :: URec Float a -> Int #

elem :: Eq a => a -> URec Float a -> Bool #

maximum :: Ord a => URec Float a -> a #

minimum :: Ord a => URec Float a -> a #

sum :: Num a => URec Float a -> a #

product :: Num a => URec Float a -> a #

Traversable (URec Float) 

Methods

traverse :: Applicative f => (a -> f b) -> URec Float a -> f (URec Float b) #

sequenceA :: Applicative f => URec Float (f a) -> f (URec Float a) #

mapM :: Monad m => (a -> m b) -> URec Float a -> m (URec Float b) #

sequence :: Monad m => URec Float (m a) -> m (URec Float a) #

Generic1 (URec Float) 

Associated Types

type Rep1 (URec Float :: * -> *) :: * -> * #

Methods

from1 :: URec Float a -> Rep1 (URec Float) a #

to1 :: Rep1 (URec Float) a -> URec Float a #

Eq (URec Float p) 

Methods

(==) :: URec Float p -> URec Float p -> Bool #

(/=) :: URec Float p -> URec Float p -> Bool #

Ord (URec Float p) 

Methods

compare :: URec Float p -> URec Float p -> Ordering #

(<) :: URec Float p -> URec Float p -> Bool #

(<=) :: URec Float p -> URec Float p -> Bool #

(>) :: URec Float p -> URec Float p -> Bool #

(>=) :: URec Float p -> URec Float p -> Bool #

max :: URec Float p -> URec Float p -> URec Float p #

min :: URec Float p -> URec Float p -> URec Float p #

Show (URec Float p) 

Methods

showsPrec :: Int -> URec Float p -> ShowS #

show :: URec Float p -> String #

showList :: [URec Float p] -> ShowS #

Generic (URec Float p) 

Associated Types

type Rep (URec Float p) :: * -> * #

Methods

from :: URec Float p -> Rep (URec Float p) x #

to :: Rep (URec Float p) x -> URec Float p #

data URec Float

Used for marking occurrences of Float#

type Rep1 (URec Float) 
type Rep1 (URec Float) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UFloat" PrefixI True) (S1 (MetaSel (Just Symbol "uFloat#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UFloat))
type Rep (URec Float p) 
type Rep (URec Float p) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UFloat" PrefixI True) (S1 (MetaSel (Just Symbol "uFloat#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UFloat))

data Double :: * #

Double-precision floating point numbers. + It is desirable that this type be at least equal in range and precision + to the IEEE double-precision type.

Instances

Eq Double 

Methods

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

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

Floating Double 
Ord Double 
Read Double 
RealFloat Double 
Lift Double 

Methods

lift :: Double -> Q Exp #

NFData Double 

Methods

rnf :: Double -> () #

Hashable Double 

Methods

hashWithSalt :: Int -> Double -> Int #

hash :: Double -> Int #

Functor (URec Double) 

Methods

fmap :: (a -> b) -> URec Double a -> URec Double b #

(<$) :: a -> URec Double b -> URec Double a #

Foldable (URec Double) 

Methods

fold :: Monoid m => URec Double m -> m #

foldMap :: Monoid m => (a -> m) -> URec Double a -> m #

foldr :: (a -> b -> b) -> b -> URec Double a -> b #

foldr' :: (a -> b -> b) -> b -> URec Double a -> b #

foldl :: (b -> a -> b) -> b -> URec Double a -> b #

foldl' :: (b -> a -> b) -> b -> URec Double a -> b #

foldr1 :: (a -> a -> a) -> URec Double a -> a #

foldl1 :: (a -> a -> a) -> URec Double a -> a #

toList :: URec Double a -> [a] #

null :: URec Double a -> Bool #

length :: URec Double a -> Int #

elem :: Eq a => a -> URec Double a -> Bool #

maximum :: Ord a => URec Double a -> a #

minimum :: Ord a => URec Double a -> a #

sum :: Num a => URec Double a -> a #

product :: Num a => URec Double a -> a #

Traversable (URec Double) 

Methods

traverse :: Applicative f => (a -> f b) -> URec Double a -> f (URec Double b) #

sequenceA :: Applicative f => URec Double (f a) -> f (URec Double a) #

mapM :: Monad m => (a -> m b) -> URec Double a -> m (URec Double b) #

sequence :: Monad m => URec Double (m a) -> m (URec Double a) #

Generic1 (URec Double) 

Associated Types

type Rep1 (URec Double :: * -> *) :: * -> * #

Methods

from1 :: URec Double a -> Rep1 (URec Double) a #

to1 :: Rep1 (URec Double) a -> URec Double a #

Eq (URec Double p) 

Methods

(==) :: URec Double p -> URec Double p -> Bool #

(/=) :: URec Double p -> URec Double p -> Bool #

Ord (URec Double p) 

Methods

compare :: URec Double p -> URec Double p -> Ordering #

(<) :: URec Double p -> URec Double p -> Bool #

(<=) :: URec Double p -> URec Double p -> Bool #

(>) :: URec Double p -> URec Double p -> Bool #

(>=) :: URec Double p -> URec Double p -> Bool #

max :: URec Double p -> URec Double p -> URec Double p #

min :: URec Double p -> URec Double p -> URec Double p #

Show (URec Double p) 

Methods

showsPrec :: Int -> URec Double p -> ShowS #

show :: URec Double p -> String #

showList :: [URec Double p] -> ShowS #

Generic (URec Double p) 

Associated Types

type Rep (URec Double p) :: * -> * #

Methods

from :: URec Double p -> Rep (URec Double p) x #

to :: Rep (URec Double p) x -> URec Double p #

data URec Double

Used for marking occurrences of Double#

type Rep1 (URec Double) 
type Rep1 (URec Double) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UDouble" PrefixI True) (S1 (MetaSel (Just Symbol "uDouble#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UDouble))
type Rep (URec Double p) 
type Rep (URec Double p) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UDouble" PrefixI True) (S1 (MetaSel (Just Symbol "uDouble#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UDouble))

data Proxy k t :: forall k. k -> * #

A concrete, poly-kinded proxy type

Constructors

Proxy 

Instances

Monad (Proxy *) 

Methods

(>>=) :: Proxy * a -> (a -> Proxy * b) -> Proxy * b #

(>>) :: Proxy * a -> Proxy * b -> Proxy * b #

return :: a -> Proxy * a #

fail :: String -> Proxy * a #

Functor (Proxy *) 

Methods

fmap :: (a -> b) -> Proxy * a -> Proxy * b #

(<$) :: a -> Proxy * b -> Proxy * a #

Applicative (Proxy *) 

Methods

pure :: a -> Proxy * a #

(<*>) :: Proxy * (a -> b) -> Proxy * a -> Proxy * b #

(*>) :: Proxy * a -> Proxy * b -> Proxy * b #

(<*) :: Proxy * a -> Proxy * b -> Proxy * a #

Foldable (Proxy *) 

Methods

fold :: Monoid m => Proxy * m -> m #

foldMap :: Monoid m => (a -> m) -> Proxy * a -> m #

foldr :: (a -> b -> b) -> b -> Proxy * a -> b #

foldr' :: (a -> b -> b) -> b -> Proxy * a -> b #

foldl :: (b -> a -> b) -> b -> Proxy * a -> b #

foldl' :: (b -> a -> b) -> b -> Proxy * a -> b #

foldr1 :: (a -> a -> a) -> Proxy * a -> a #

foldl1 :: (a -> a -> a) -> Proxy * a -> a #

toList :: Proxy * a -> [a] #

null :: Proxy * a -> Bool #

length :: Proxy * a -> Int #

elem :: Eq a => a -> Proxy * a -> Bool #

maximum :: Ord a => Proxy * a -> a #

minimum :: Ord a => Proxy * a -> a #

sum :: Num a => Proxy * a -> a #

product :: Num a => Proxy * a -> a #

Traversable (Proxy *) 

Methods

traverse :: Applicative f => (a -> f b) -> Proxy * a -> f (Proxy * b) #

sequenceA :: Applicative f => Proxy * (f a) -> f (Proxy * a) #

mapM :: Monad m => (a -> m b) -> Proxy * a -> m (Proxy * b) #

sequence :: Monad m => Proxy * (m a) -> m (Proxy * a) #

Generic1 (Proxy *) 

Associated Types

type Rep1 (Proxy * :: * -> *) :: * -> * #

Methods

from1 :: Proxy * a -> Rep1 (Proxy *) a #

to1 :: Rep1 (Proxy *) a -> Proxy * a #

Alternative (Proxy *) 

Methods

empty :: Proxy * a #

(<|>) :: Proxy * a -> Proxy * a -> Proxy * a #

some :: Proxy * a -> Proxy * [a] #

many :: Proxy * a -> Proxy * [a] #

MonadPlus (Proxy *) 

Methods

mzero :: Proxy * a #

mplus :: Proxy * a -> Proxy * a -> Proxy * a #

Bounded (Proxy k s) 

Methods

minBound :: Proxy k s #

maxBound :: Proxy k s #

Enum (Proxy k s) 

Methods

succ :: Proxy k s -> Proxy k s #

pred :: Proxy k s -> Proxy k s #

toEnum :: Int -> Proxy k s #

fromEnum :: Proxy k s -> Int #

enumFrom :: Proxy k s -> [Proxy k s] #

enumFromThen :: Proxy k s -> Proxy k s -> [Proxy k s] #

enumFromTo :: Proxy k s -> Proxy k s -> [Proxy k s] #

enumFromThenTo :: Proxy k s -> Proxy k s -> Proxy k s -> [Proxy k s] #

Eq (Proxy k s) 

Methods

(==) :: Proxy k s -> Proxy k s -> Bool #

(/=) :: Proxy k s -> Proxy k s -> Bool #

Ord (Proxy k s) 

Methods

compare :: Proxy k s -> Proxy k s -> Ordering #

(<) :: Proxy k s -> Proxy k s -> Bool #

(<=) :: Proxy k s -> Proxy k s -> Bool #

(>) :: Proxy k s -> Proxy k s -> Bool #

(>=) :: Proxy k s -> Proxy k s -> Bool #

max :: Proxy k s -> Proxy k s -> Proxy k s #

min :: Proxy k s -> Proxy k s -> Proxy k s #

Read (Proxy k s) 
Show (Proxy k s) 

Methods

showsPrec :: Int -> Proxy k s -> ShowS #

show :: Proxy k s -> String #

showList :: [Proxy k s] -> ShowS #

Ix (Proxy k s) 

Methods

range :: (Proxy k s, Proxy k s) -> [Proxy k s] #

index :: (Proxy k s, Proxy k s) -> Proxy k s -> Int #

unsafeIndex :: (Proxy k s, Proxy k s) -> Proxy k s -> Int

inRange :: (Proxy k s, Proxy k s) -> Proxy k s -> Bool #

rangeSize :: (Proxy k s, Proxy k s) -> Int #

unsafeRangeSize :: (Proxy k s, Proxy k s) -> Int

Generic (Proxy k t) 

Associated Types

type Rep (Proxy k t) :: * -> * #

Methods

from :: Proxy k t -> Rep (Proxy k t) x #

to :: Rep (Proxy k t) x -> Proxy k t #

Semigroup (Proxy k s) 

Methods

(<>) :: Proxy k s -> Proxy k s -> Proxy k s #

sconcat :: NonEmpty (Proxy k s) -> Proxy k s #

stimes :: Integral b => b -> Proxy k s -> Proxy k s #

Monoid (Proxy k s) 

Methods

mempty :: Proxy k s #

mappend :: Proxy k s -> Proxy k s -> Proxy k s #

mconcat :: [Proxy k s] -> Proxy k s #

NFData (Proxy k a)

Since: 1.4.0.0

Methods

rnf :: Proxy k a -> () #

type Rep1 (Proxy *) 
type Rep1 (Proxy *) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) U1)
type Rep (Proxy k t) 
type Rep (Proxy k t) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) U1)

Type classes

class Eq a => Ord a where #

The Ord class is used for totally ordered datatypes.

Instances of Ord can be derived for any user-defined + datatype whose constituent types are in Ord. The declared order + of the constructors in the data declaration determines the ordering + in derived Ord instances. The Ordering datatype allows a single + comparison to determine the precise ordering of two objects.

Minimal complete definition: either compare or <=. + Using compare can be more efficient for complex types.

Minimal complete definition

compare | (<=)

Instances

Ord Bool 

Methods

compare :: Bool -> Bool -> Ordering #

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

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

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

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

max :: Bool -> Bool -> Bool #

min :: Bool -> Bool -> Bool #

Ord Char 

Methods

compare :: Char -> Char -> Ordering #

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

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

(>) :: Char -> Char -> Bool #

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

max :: Char -> Char -> Char #

min :: Char -> Char -> Char #

Ord Double 
Ord Float 

Methods

compare :: Float -> Float -> Ordering #

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

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

(>) :: Float -> Float -> Bool #

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

max :: Float -> Float -> Float #

min :: Float -> Float -> Float #

Ord Int 

Methods

compare :: Int -> Int -> Ordering #

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

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

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

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

max :: Int -> Int -> Int #

min :: Int -> Int -> Int #

Ord Int8 

Methods

compare :: Int8 -> Int8 -> Ordering #

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

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

(>) :: Int8 -> Int8 -> Bool #

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

max :: Int8 -> Int8 -> Int8 #

min :: Int8 -> Int8 -> Int8 #

Ord Int16 

Methods

compare :: Int16 -> Int16 -> Ordering #

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

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

(>) :: Int16 -> Int16 -> Bool #

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

max :: Int16 -> Int16 -> Int16 #

min :: Int16 -> Int16 -> Int16 #

Ord Int32 

Methods

compare :: Int32 -> Int32 -> Ordering #

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

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

(>) :: Int32 -> Int32 -> Bool #

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

max :: Int32 -> Int32 -> Int32 #

min :: Int32 -> Int32 -> Int32 #

Ord Int64 

Methods

compare :: Int64 -> Int64 -> Ordering #

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

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

(>) :: Int64 -> Int64 -> Bool #

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

max :: Int64 -> Int64 -> Int64 #

min :: Int64 -> Int64 -> Int64 #

Ord Integer 
Ord Ordering 
Ord Word 

Methods

compare :: Word -> Word -> Ordering #

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

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

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

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

max :: Word -> Word -> Word #

min :: Word -> Word -> Word #

Ord Word8 

Methods

compare :: Word8 -> Word8 -> Ordering #

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

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

(>) :: Word8 -> Word8 -> Bool #

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

max :: Word8 -> Word8 -> Word8 #

min :: Word8 -> Word8 -> Word8 #

Ord Word16 
Ord Word32 
Ord Word64 
Ord TypeRep 
Ord Exp 

Methods

compare :: Exp -> Exp -> Ordering #

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

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

(>) :: Exp -> Exp -> Bool #

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

max :: Exp -> Exp -> Exp #

min :: Exp -> Exp -> Exp #

Ord Match 

Methods

compare :: Match -> Match -> Ordering #

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

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

(>) :: Match -> Match -> Bool #

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

max :: Match -> Match -> Match #

min :: Match -> Match -> Match #

Ord Clause 
Ord Pat 

Methods

compare :: Pat -> Pat -> Ordering #

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

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

(>) :: Pat -> Pat -> Bool #

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

max :: Pat -> Pat -> Pat #

min :: Pat -> Pat -> Pat #

Ord Type 

Methods

compare :: Type -> Type -> Ordering #

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

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

(>) :: Type -> Type -> Bool #

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

max :: Type -> Type -> Type #

min :: Type -> Type -> Type #

Ord Dec 

Methods

compare :: Dec -> Dec -> Ordering #

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

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

(>) :: Dec -> Dec -> Bool #

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

max :: Dec -> Dec -> Dec #

min :: Dec -> Dec -> Dec #

Ord Name 

Methods

compare :: Name -> Name -> Ordering #

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

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

(>) :: Name -> Name -> Bool #

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

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Ord FunDep 
Ord TyVarBndr 
Ord InjectivityAnn 
Ord Overlap 
Ord () 

Methods

compare :: () -> () -> Ordering #

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

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

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

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

max :: () -> () -> () #

min :: () -> () -> () #

Ord TyCon 

Methods

compare :: TyCon -> TyCon -> Ordering #

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

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

(>) :: TyCon -> TyCon -> Bool #

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

max :: TyCon -> TyCon -> TyCon #

min :: TyCon -> TyCon -> TyCon #

Ord BigNat 
Ord Void 

Methods

compare :: Void -> Void -> Ordering #

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

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

(>) :: Void -> Void -> Bool #

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

max :: Void -> Void -> Void #

min :: Void -> Void -> Void #

Ord Version 
Ord ThreadId 
Ord BlockReason 
Ord ThreadStatus 
Ord AsyncException 
Ord ArrayException 
Ord ExitCode 
Ord BufferMode 
Ord Newline 
Ord NewlineMode 
Ord All 

Methods

compare :: All -> All -> Ordering #

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

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

(>) :: All -> All -> Bool #

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

max :: All -> All -> All #

min :: All -> All -> All #

Ord Any 

Methods

compare :: Any -> Any -> Ordering #

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

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

(>) :: Any -> Any -> Bool #

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

max :: Any -> Any -> Any #

min :: Any -> Any -> Any #

Ord Fixity 
Ord Associativity 
Ord SourceUnpackedness 
Ord SourceStrictness 
Ord DecidedStrictness 
Ord ErrorCall 
Ord ArithException 
Ord SomeNat 
Ord SomeSymbol 
Ord IOMode 
Ord ByteString 
Ord IntSet 
Ord ModName 
Ord PkgName 
Ord Module 
Ord OccName 
Ord NameFlavour 
Ord NameSpace 
Ord Loc 

Methods

compare :: Loc -> Loc -> Ordering #

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

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

(>) :: Loc -> Loc -> Bool #

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

max :: Loc -> Loc -> Loc #

min :: Loc -> Loc -> Loc #

Ord Info 

Methods

compare :: Info -> Info -> Ordering #

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

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

(>) :: Info -> Info -> Bool #

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

max :: Info -> Info -> Info #

min :: Info -> Info -> Info #

Ord ModuleInfo 
Ord Fixity 
Ord FixityDirection 
Ord Lit 

Methods

compare :: Lit -> Lit -> Ordering #

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

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

(>) :: Lit -> Lit -> Bool #

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

max :: Lit -> Lit -> Lit #

min :: Lit -> Lit -> Lit #

Ord Body 

Methods

compare :: Body -> Body -> Ordering #

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

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

(>) :: Body -> Body -> Bool #

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

max :: Body -> Body -> Body #

min :: Body -> Body -> Body #

Ord Guard 

Methods

compare :: Guard -> Guard -> Ordering #

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

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

(>) :: Guard -> Guard -> Bool #

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

max :: Guard -> Guard -> Guard #

min :: Guard -> Guard -> Guard #

Ord Stmt 

Methods

compare :: Stmt -> Stmt -> Ordering #

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

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

(>) :: Stmt -> Stmt -> Bool #

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

max :: Stmt -> Stmt -> Stmt #

min :: Stmt -> Stmt -> Stmt #

Ord Range 

Methods

compare :: Range -> Range -> Ordering #

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

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

(>) :: Range -> Range -> Bool #

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

max :: Range -> Range -> Range #

min :: Range -> Range -> Range #

Ord TypeFamilyHead 
Ord TySynEqn 
Ord FamFlavour 
Ord Foreign 
Ord Callconv 
Ord Safety 
Ord Pragma 
Ord Inline 
Ord RuleMatch 
Ord Phases 
Ord RuleBndr 
Ord AnnTarget 
Ord SourceUnpackedness 
Ord SourceStrictness 
Ord DecidedStrictness 
Ord Con 

Methods

compare :: Con -> Con -> Ordering #

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

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

(>) :: Con -> Con -> Bool #

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

max :: Con -> Con -> Con #

min :: Con -> Con -> Con #

Ord Bang 

Methods

compare :: Bang -> Bang -> Ordering #

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

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

(>) :: Bang -> Bang -> Bool #

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

max :: Bang -> Bang -> Bang #

min :: Bang -> Bang -> Bang #

Ord FamilyResultSig 
Ord TyLit 

Methods

compare :: TyLit -> TyLit -> Ordering #

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

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

(>) :: TyLit -> TyLit -> Bool #

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

max :: TyLit -> TyLit -> TyLit #

min :: TyLit -> TyLit -> TyLit #

Ord Role 

Methods

compare :: Role -> Role -> Ordering #

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

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

(>) :: Role -> Role -> Bool #

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

max :: Role -> Role -> Role #

min :: Role -> Role -> Role #

Ord AnnLookup 
Ord a => Ord [a] 

Methods

compare :: [a] -> [a] -> Ordering #

(<) :: [a] -> [a] -> Bool #

(<=) :: [a] -> [a] -> Bool #

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

(>=) :: [a] -> [a] -> Bool #

max :: [a] -> [a] -> [a] #

min :: [a] -> [a] -> [a] #

Ord a => Ord (Maybe a) 

Methods

compare :: Maybe a -> Maybe a -> Ordering #

(<) :: Maybe a -> Maybe a -> Bool #

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

(>) :: Maybe a -> Maybe a -> Bool #

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

max :: Maybe a -> Maybe a -> Maybe a #

min :: Maybe a -> Maybe a -> Maybe a #

Integral a => Ord (Ratio a) 

Methods

compare :: Ratio a -> Ratio a -> Ordering #

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

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

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

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

max :: Ratio a -> Ratio a -> Ratio a #

min :: Ratio a -> Ratio a -> Ratio a #

Ord (Ptr a) 

Methods

compare :: Ptr a -> Ptr a -> Ordering #

(<) :: Ptr a -> Ptr a -> Bool #

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

(>) :: Ptr a -> Ptr a -> Bool #

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

max :: Ptr a -> Ptr a -> Ptr a #

min :: Ptr a -> Ptr a -> Ptr a #

Ord (FunPtr a) 

Methods

compare :: FunPtr a -> FunPtr a -> Ordering #

(<) :: FunPtr a -> FunPtr a -> Bool #

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

(>) :: FunPtr a -> FunPtr a -> Bool #

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

max :: FunPtr a -> FunPtr a -> FunPtr a #

min :: FunPtr a -> FunPtr a -> FunPtr a #

Ord (V1 p) 

Methods

compare :: V1 p -> V1 p -> Ordering #

(<) :: V1 p -> V1 p -> Bool #

(<=) :: V1 p -> V1 p -> Bool #

(>) :: V1 p -> V1 p -> Bool #

(>=) :: V1 p -> V1 p -> Bool #

max :: V1 p -> V1 p -> V1 p #

min :: V1 p -> V1 p -> V1 p #

Ord (U1 p) 

Methods

compare :: U1 p -> U1 p -> Ordering #

(<) :: U1 p -> U1 p -> Bool #

(<=) :: U1 p -> U1 p -> Bool #

(>) :: U1 p -> U1 p -> Bool #

(>=) :: U1 p -> U1 p -> Bool #

max :: U1 p -> U1 p -> U1 p #

min :: U1 p -> U1 p -> U1 p #

Ord p => Ord (Par1 p) 

Methods

compare :: Par1 p -> Par1 p -> Ordering #

(<) :: Par1 p -> Par1 p -> Bool #

(<=) :: Par1 p -> Par1 p -> Bool #

(>) :: Par1 p -> Par1 p -> Bool #

(>=) :: Par1 p -> Par1 p -> Bool #

max :: Par1 p -> Par1 p -> Par1 p #

min :: Par1 p -> Par1 p -> Par1 p #

Ord (ForeignPtr a) 
Ord a => Ord (Identity a) 

Methods

compare :: Identity a -> Identity a -> Ordering #

(<) :: Identity a -> Identity a -> Bool #

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

(>) :: Identity a -> Identity a -> Bool #

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

max :: Identity a -> Identity a -> Identity a #

min :: Identity a -> Identity a -> Identity a #

Ord a => Ord (Min a) 

Methods

compare :: Min a -> Min a -> Ordering #

(<) :: Min a -> Min a -> Bool #

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

(>) :: Min a -> Min a -> Bool #

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

max :: Min a -> Min a -> Min a #

min :: Min a -> Min a -> Min a #

Ord a => Ord (Max a) 

Methods

compare :: Max a -> Max a -> Ordering #

(<) :: Max a -> Max a -> Bool #

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

(>) :: Max a -> Max a -> Bool #

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

max :: Max a -> Max a -> Max a #

min :: Max a -> Max a -> Max a #

Ord a => Ord (First a) 

Methods

compare :: First a -> First a -> Ordering #

(<) :: First a -> First a -> Bool #

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

(>) :: First a -> First a -> Bool #

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

max :: First a -> First a -> First a #

min :: First a -> First a -> First a #

Ord a => Ord (Last a) 

Methods

compare :: Last a -> Last a -> Ordering #

(<) :: Last a -> Last a -> Bool #

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

(>) :: Last a -> Last a -> Bool #

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

max :: Last a -> Last a -> Last a #

min :: Last a -> Last a -> Last a #

Ord m => Ord (WrappedMonoid m) 
Ord a => Ord (Option a) 

Methods

compare :: Option a -> Option a -> Ordering #

(<) :: Option a -> Option a -> Bool #

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

(>) :: Option a -> Option a -> Bool #

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

max :: Option a -> Option a -> Option a #

min :: Option a -> Option a -> Option a #

Ord a => Ord (NonEmpty a) 

Methods

compare :: NonEmpty a -> NonEmpty a -> Ordering #

(<) :: NonEmpty a -> NonEmpty a -> Bool #

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

(>) :: NonEmpty a -> NonEmpty a -> Bool #

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

max :: NonEmpty a -> NonEmpty a -> NonEmpty a #

min :: NonEmpty a -> NonEmpty a -> NonEmpty a #

Ord a => Ord (ZipList a) 

Methods

compare :: ZipList a -> ZipList a -> Ordering #

(<) :: ZipList a -> ZipList a -> Bool #

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

(>) :: ZipList a -> ZipList a -> Bool #

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

max :: ZipList a -> ZipList a -> ZipList a #

min :: ZipList a -> ZipList a -> ZipList a #

Ord a => Ord (Dual a) 

Methods

compare :: Dual a -> Dual a -> Ordering #

(<) :: Dual a -> Dual a -> Bool #

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

(>) :: Dual a -> Dual a -> Bool #

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

max :: Dual a -> Dual a -> Dual a #

min :: Dual a -> Dual a -> Dual a #

Ord a => Ord (Sum a) 

Methods

compare :: Sum a -> Sum a -> Ordering #

(<) :: Sum a -> Sum a -> Bool #

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

(>) :: Sum a -> Sum a -> Bool #

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

max :: Sum a -> Sum a -> Sum a #

min :: Sum a -> Sum a -> Sum a #

Ord a => Ord (Product a) 

Methods

compare :: Product a -> Product a -> Ordering #

(<) :: Product a -> Product a -> Bool #

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

(>) :: Product a -> Product a -> Bool #

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

max :: Product a -> Product a -> Product a #

min :: Product a -> Product a -> Product a #

Ord a => Ord (First a) 

Methods

compare :: First a -> First a -> Ordering #

(<) :: First a -> First a -> Bool #

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

(>) :: First a -> First a -> Bool #

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

max :: First a -> First a -> First a #

min :: First a -> First a -> First a #

Ord a => Ord (Last a) 

Methods

compare :: Last a -> Last a -> Ordering #

(<) :: Last a -> Last a -> Bool #

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

(>) :: Last a -> Last a -> Bool #

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

max :: Last a -> Last a -> Last a #

min :: Last a -> Last a -> Last a #

Ord a => Ord (Down a) 

Methods

compare :: Down a -> Down a -> Ordering #

(<) :: Down a -> Down a -> Bool #

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

(>) :: Down a -> Down a -> Bool #

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

max :: Down a -> Down a -> Down a #

min :: Down a -> Down a -> Down a #

Ord a => Ord (Seq a) 

Methods

compare :: Seq a -> Seq a -> Ordering #

(<) :: Seq a -> Seq a -> Bool #

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

(>) :: Seq a -> Seq a -> Bool #

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

max :: Seq a -> Seq a -> Seq a #

min :: Seq a -> Seq a -> Seq a #

Ord a => Ord (ViewL a) 

Methods

compare :: ViewL a -> ViewL a -> Ordering #

(<) :: ViewL a -> ViewL a -> Bool #

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

(>) :: ViewL a -> ViewL a -> Bool #

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

max :: ViewL a -> ViewL a -> ViewL a #

min :: ViewL a -> ViewL a -> ViewL a #

Ord a => Ord (ViewR a) 

Methods

compare :: ViewR a -> ViewR a -> Ordering #

(<) :: ViewR a -> ViewR a -> Bool #

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

(>) :: ViewR a -> ViewR a -> Bool #

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

max :: ViewR a -> ViewR a -> ViewR a #

min :: ViewR a -> ViewR a -> ViewR a #

Ord a => Ord (IntMap a) 

Methods

compare :: IntMap a -> IntMap a -> Ordering #

(<) :: IntMap a -> IntMap a -> Bool #

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

(>) :: IntMap a -> IntMap a -> Bool #

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

max :: IntMap a -> IntMap a -> IntMap a #

min :: IntMap a -> IntMap a -> IntMap a #

Ord a => Ord (Set a) 

Methods

compare :: Set a -> Set a -> Ordering #

(<) :: Set a -> Set a -> Bool #

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

(>) :: Set a -> Set a -> Bool #

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

max :: Set a -> Set a -> Set a #

min :: Set a -> Set a -> Set a #

(Ord a, Ord b) => Ord (Either a b) 

Methods

compare :: Either a b -> Either a b -> Ordering #

(<) :: Either a b -> Either a b -> Bool #

(<=) :: Either a b -> Either a b -> Bool #

(>) :: Either a b -> Either a b -> Bool #

(>=) :: Either a b -> Either a b -> Bool #

max :: Either a b -> Either a b -> Either a b #

min :: Either a b -> Either a b -> Either a b #

Ord (f p) => Ord (Rec1 f p) 

Methods

compare :: Rec1 f p -> Rec1 f p -> Ordering #

(<) :: Rec1 f p -> Rec1 f p -> Bool #

(<=) :: Rec1 f p -> Rec1 f p -> Bool #

(>) :: Rec1 f p -> Rec1 f p -> Bool #

(>=) :: Rec1 f p -> Rec1 f p -> Bool #

max :: Rec1 f p -> Rec1 f p -> Rec1 f p #

min :: Rec1 f p -> Rec1 f p -> Rec1 f p #

Ord (URec Char p) 

Methods

compare :: URec Char p -> URec Char p -> Ordering #

(<) :: URec Char p -> URec Char p -> Bool #

(<=) :: URec Char p -> URec Char p -> Bool #

(>) :: URec Char p -> URec Char p -> Bool #

(>=) :: URec Char p -> URec Char p -> Bool #

max :: URec Char p -> URec Char p -> URec Char p #

min :: URec Char p -> URec Char p -> URec Char p #

Ord (URec Double p) 

Methods

compare :: URec Double p -> URec Double p -> Ordering #

(<) :: URec Double p -> URec Double p -> Bool #

(<=) :: URec Double p -> URec Double p -> Bool #

(>) :: URec Double p -> URec Double p -> Bool #

(>=) :: URec Double p -> URec Double p -> Bool #

max :: URec Double p -> URec Double p -> URec Double p #

min :: URec Double p -> URec Double p -> URec Double p #

Ord (URec Float p) 

Methods

compare :: URec Float p -> URec Float p -> Ordering #

(<) :: URec Float p -> URec Float p -> Bool #

(<=) :: URec Float p -> URec Float p -> Bool #

(>) :: URec Float p -> URec Float p -> Bool #

(>=) :: URec Float p -> URec Float p -> Bool #

max :: URec Float p -> URec Float p -> URec Float p #

min :: URec Float p -> URec Float p -> URec Float p #

Ord (URec Int p) 

Methods

compare :: URec Int p -> URec Int p -> Ordering #

(<) :: URec Int p -> URec Int p -> Bool #

(<=) :: URec Int p -> URec Int p -> Bool #

(>) :: URec Int p -> URec Int p -> Bool #

(>=) :: URec Int p -> URec Int p -> Bool #

max :: URec Int p -> URec Int p -> URec Int p #

min :: URec Int p -> URec Int p -> URec Int p #

Ord (URec Word p) 

Methods

compare :: URec Word p -> URec Word p -> Ordering #

(<) :: URec Word p -> URec Word p -> Bool #

(<=) :: URec Word p -> URec Word p -> Bool #

(>) :: URec Word p -> URec Word p -> Bool #

(>=) :: URec Word p -> URec Word p -> Bool #

max :: URec Word p -> URec Word p -> URec Word p #

min :: URec Word p -> URec Word p -> URec Word p #

Ord (URec (Ptr ()) p) 

Methods

compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering #

(<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(<=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(>) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(>=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p #

min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p #

(Ord a, Ord b) => Ord (a, b) 

Methods

compare :: (a, b) -> (a, b) -> Ordering #

(<) :: (a, b) -> (a, b) -> Bool #

(<=) :: (a, b) -> (a, b) -> Bool #

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

(>=) :: (a, b) -> (a, b) -> Bool #

max :: (a, b) -> (a, b) -> (a, b) #

min :: (a, b) -> (a, b) -> (a, b) #

Ord a => Ord (Arg a b) 

Methods

compare :: Arg a b -> Arg a b -> Ordering #

(<) :: Arg a b -> Arg a b -> Bool #

(<=) :: Arg a b -> Arg a b -> Bool #

(>) :: Arg a b -> Arg a b -> Bool #

(>=) :: Arg a b -> Arg a b -> Bool #

max :: Arg a b -> Arg a b -> Arg a b #

min :: Arg a b -> Arg a b -> Arg a b #

Ord (Proxy k s) 

Methods

compare :: Proxy k s -> Proxy k s -> Ordering #

(<) :: Proxy k s -> Proxy k s -> Bool #

(<=) :: Proxy k s -> Proxy k s -> Bool #

(>) :: Proxy k s -> Proxy k s -> Bool #

(>=) :: Proxy k s -> Proxy k s -> Bool #

max :: Proxy k s -> Proxy k s -> Proxy k s #

min :: Proxy k s -> Proxy k s -> Proxy k s #

(Ord k, Ord v) => Ord (Map k v) 

Methods

compare :: Map k v -> Map k v -> Ordering #

(<) :: Map k v -> Map k v -> Bool #

(<=) :: Map k v -> Map k v -> Bool #

(>) :: Map k v -> Map k v -> Bool #

(>=) :: Map k v -> Map k v -> Bool #

max :: Map k v -> Map k v -> Map k v #

min :: Map k v -> Map k v -> Map k v #

Ord c => Ord (K1 i c p) 

Methods

compare :: K1 i c p -> K1 i c p -> Ordering #

(<) :: K1 i c p -> K1 i c p -> Bool #

(<=) :: K1 i c p -> K1 i c p -> Bool #

(>) :: K1 i c p -> K1 i c p -> Bool #

(>=) :: K1 i c p -> K1 i c p -> Bool #

max :: K1 i c p -> K1 i c p -> K1 i c p #

min :: K1 i c p -> K1 i c p -> K1 i c p #

(Ord (f p), Ord (g p)) => Ord ((:+:) f g p) 

Methods

compare :: (f :+: g) p -> (f :+: g) p -> Ordering #

(<) :: (f :+: g) p -> (f :+: g) p -> Bool #

(<=) :: (f :+: g) p -> (f :+: g) p -> Bool #

(>) :: (f :+: g) p -> (f :+: g) p -> Bool #

(>=) :: (f :+: g) p -> (f :+: g) p -> Bool #

max :: (f :+: g) p -> (f :+: g) p -> (f :+: g) p #

min :: (f :+: g) p -> (f :+: g) p -> (f :+: g) p #

(Ord (f p), Ord (g p)) => Ord ((:*:) f g p) 

Methods

compare :: (f :*: g) p -> (f :*: g) p -> Ordering #

(<) :: (f :*: g) p -> (f :*: g) p -> Bool #

(<=) :: (f :*: g) p -> (f :*: g) p -> Bool #

(>) :: (f :*: g) p -> (f :*: g) p -> Bool #

(>=) :: (f :*: g) p -> (f :*: g) p -> Bool #

max :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p #

min :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p #

Ord (f (g p)) => Ord ((:.:) f g p) 

Methods

compare :: (f :.: g) p -> (f :.: g) p -> Ordering #

(<) :: (f :.: g) p -> (f :.: g) p -> Bool #

(<=) :: (f :.: g) p -> (f :.: g) p -> Bool #

(>) :: (f :.: g) p -> (f :.: g) p -> Bool #

(>=) :: (f :.: g) p -> (f :.: g) p -> Bool #

max :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p #

min :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p #

(Ord a, Ord b, Ord c) => Ord (a, b, c) 

Methods

compare :: (a, b, c) -> (a, b, c) -> Ordering #

(<) :: (a, b, c) -> (a, b, c) -> Bool #

(<=) :: (a, b, c) -> (a, b, c) -> Bool #

(>) :: (a, b, c) -> (a, b, c) -> Bool #

(>=) :: (a, b, c) -> (a, b, c) -> Bool #

max :: (a, b, c) -> (a, b, c) -> (a, b, c) #

min :: (a, b, c) -> (a, b, c) -> (a, b, c) #

Ord a => Ord (Const k a b) 

Methods

compare :: Const k a b -> Const k a b -> Ordering #

(<) :: Const k a b -> Const k a b -> Bool #

(<=) :: Const k a b -> Const k a b -> Bool #

(>) :: Const k a b -> Const k a b -> Bool #

(>=) :: Const k a b -> Const k a b -> Bool #

max :: Const k a b -> Const k a b -> Const k a b #

min :: Const k a b -> Const k a b -> Const k a b #

Ord (f a) => Ord (Alt k f a) 

Methods

compare :: Alt k f a -> Alt k f a -> Ordering #

(<) :: Alt k f a -> Alt k f a -> Bool #

(<=) :: Alt k f a -> Alt k f a -> Bool #

(>) :: Alt k f a -> Alt k f a -> Bool #

(>=) :: Alt k f a -> Alt k f a -> Bool #

max :: Alt k f a -> Alt k f a -> Alt k f a #

min :: Alt k f a -> Alt k f a -> Alt k f a #

Ord ((:~:) k a b) 

Methods

compare :: (k :~: a) b -> (k :~: a) b -> Ordering #

(<) :: (k :~: a) b -> (k :~: a) b -> Bool #

(<=) :: (k :~: a) b -> (k :~: a) b -> Bool #

(>) :: (k :~: a) b -> (k :~: a) b -> Bool #

(>=) :: (k :~: a) b -> (k :~: a) b -> Bool #

max :: (k :~: a) b -> (k :~: a) b -> (k :~: a) b #

min :: (k :~: a) b -> (k :~: a) b -> (k :~: a) b #

(Ord e, Ord1 m, Ord a) => Ord (ErrorT e m a) 

Methods

compare :: ErrorT e m a -> ErrorT e m a -> Ordering #

(<) :: ErrorT e m a -> ErrorT e m a -> Bool #

(<=) :: ErrorT e m a -> ErrorT e m a -> Bool #

(>) :: ErrorT e m a -> ErrorT e m a -> Bool #

(>=) :: ErrorT e m a -> ErrorT e m a -> Bool #

max :: ErrorT e m a -> ErrorT e m a -> ErrorT e m a #

min :: ErrorT e m a -> ErrorT e m a -> ErrorT e m a #

Ord (f p) => Ord (M1 i c f p) 

Methods

compare :: M1 i c f p -> M1 i c f p -> Ordering #

(<) :: M1 i c f p -> M1 i c f p -> Bool #

(<=) :: M1 i c f p -> M1 i c f p -> Bool #

(>) :: M1 i c f p -> M1 i c f p -> Bool #

(>=) :: M1 i c f p -> M1 i c f p -> Bool #

max :: M1 i c f p -> M1 i c f p -> M1 i c f p #

min :: M1 i c f p -> M1 i c f p -> M1 i c f p #

(Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) 

Methods

compare :: (a, b, c, d) -> (a, b, c, d) -> Ordering #

(<) :: (a, b, c, d) -> (a, b, c, d) -> Bool #

(<=) :: (a, b, c, d) -> (a, b, c, d) -> Bool #

(>) :: (a, b, c, d) -> (a, b, c, d) -> Bool #

(>=) :: (a, b, c, d) -> (a, b, c, d) -> Bool #

max :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

min :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

(Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) 

Methods

compare :: (a, b, c, d, e) -> (a, b, c, d, e) -> Ordering #

(<) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool #

(<=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool #

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

(>=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool #

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

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

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f) => Ord (a, b, c, d, e, f) 

Methods

compare :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Ordering #

(<) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool #

(<=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool #

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

(>=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool #

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

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

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g) => Ord (a, b, c, d, e, f, g) 

Methods

compare :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Ordering #

(<) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool #

(<=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool #

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

(>=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool #

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

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

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h) => Ord (a, b, c, d, e, f, g, h) 

Methods

compare :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Ordering #

(<) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool #

(<=) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool #

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

(>=) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool #

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

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

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) => Ord (a, b, c, d, e, f, g, h, i) 

Methods

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

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

(<=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool #

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

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

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

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

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j) => Ord (a, b, c, d, e, f, g, h, i, j) 

Methods

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

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

(<=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool #

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

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

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

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

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

Methods

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

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

(<=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool #

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

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

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

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

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

Methods

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

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

(<=) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool #

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

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

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

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

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

Methods

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

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

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

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

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

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

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

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

Methods

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

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

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

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

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

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

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

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

Methods

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

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

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

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

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

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

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

class Eq a where #

The Eq class defines equality (==) and inequality (/=). + All the basic datatypes exported by the Prelude are instances of Eq, + and Eq may be derived for any datatype whose constituents are also + instances of Eq.

Minimal complete definition: either == or /=.

Minimal complete definition

(==) | (/=)

Instances

Eq Bool 

Methods

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

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

Eq Char 

Methods

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

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

Eq Double 

Methods

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

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

Eq Float 

Methods

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

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

Eq Int 

Methods

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

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

Eq Int8 

Methods

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

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

Eq Int16 

Methods

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

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

Eq Int32 

Methods

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

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

Eq Int64 

Methods

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

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

Eq Integer 

Methods

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

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

Eq Ordering 
Eq Word 

Methods

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

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

Eq Word8 

Methods

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

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

Eq Word16 

Methods

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

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

Eq Word32 

Methods

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

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

Eq Word64 

Methods

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

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

Eq TypeRep 

Methods

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

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

Eq Exp 

Methods

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

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

Eq Match 

Methods

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

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

Eq Clause 

Methods

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

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

Eq Pat 

Methods

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

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

Eq Type 

Methods

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

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

Eq Dec 

Methods

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

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

Eq Name 

Methods

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

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

Eq FunDep 

Methods

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

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

Eq TyVarBndr 
Eq InjectivityAnn 
Eq Overlap 

Methods

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

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

Eq () 

Methods

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

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

Eq TyCon 

Methods

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

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

Eq Handle 

Methods

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

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

Eq BigNat 

Methods

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

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

Eq SpecConstrAnnotation 
Eq Void 

Methods

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

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

Eq Version 

Methods

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

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

Eq HandlePosn 
Eq ThreadId 
Eq BlockReason 
Eq ThreadStatus 
Eq AsyncException 
Eq ArrayException 
Eq ExitCode 
Eq IOErrorType 
Eq BufferMode 
Eq Newline 

Methods

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

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

Eq NewlineMode 
Eq All 

Methods

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

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

Eq Any 

Methods

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

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

Eq Fixity 

Methods

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

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

Eq Associativity 
Eq SourceUnpackedness 
Eq SourceStrictness 
Eq DecidedStrictness 
Eq MaskingState 
Eq IOException 
Eq ErrorCall 
Eq ArithException 
Eq SomeNat 

Methods

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

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

Eq SomeSymbol 
Eq IOMode 

Methods

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

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

Eq SrcLoc 

Methods

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

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

Eq ByteString 
Eq IntSet 

Methods

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

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

Eq Extension 
Eq ModName 

Methods

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

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

Eq PkgName 

Methods

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

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

Eq Module 

Methods

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

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

Eq OccName 

Methods

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

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

Eq NameFlavour 
Eq NameSpace 
Eq Loc 

Methods

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

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

Eq Info 

Methods

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

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

Eq ModuleInfo 
Eq Fixity 

Methods

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

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

Eq FixityDirection 
Eq Lit 

Methods

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

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

Eq Body 

Methods

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

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

Eq Guard 

Methods

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

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

Eq Stmt 

Methods

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

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

Eq Range 

Methods

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

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

Eq TypeFamilyHead 
Eq TySynEqn 
Eq FamFlavour 
Eq Foreign 

Methods

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

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

Eq Callconv 
Eq Safety 

Methods

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

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

Eq Pragma 

Methods

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

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

Eq Inline 

Methods

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

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

Eq RuleMatch 
Eq Phases 

Methods

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

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

Eq RuleBndr 
Eq AnnTarget 
Eq SourceUnpackedness 
Eq SourceStrictness 
Eq DecidedStrictness 
Eq Con 

Methods

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

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

Eq Bang 

Methods

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

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

Eq FamilyResultSig 
Eq TyLit 

Methods

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

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

Eq Role 

Methods

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

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

Eq AnnLookup 
Eq CodePoint 

Methods

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

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

Eq DecoderState 

Methods

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

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

Eq UnicodeException 
Eq a => Eq [a] 

Methods

(==) :: [a] -> [a] -> Bool #

(/=) :: [a] -> [a] -> Bool #

Eq a => Eq (Maybe a) 

Methods

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

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

Eq a => Eq (Ratio a) 

Methods

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

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

Eq (Ptr a) 

Methods

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

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

Eq (FunPtr a) 

Methods

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

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

Eq (V1 p) 

Methods

(==) :: V1 p -> V1 p -> Bool #

(/=) :: V1 p -> V1 p -> Bool #

Eq (U1 p) 

Methods

(==) :: U1 p -> U1 p -> Bool #

(/=) :: U1 p -> U1 p -> Bool #

Eq p => Eq (Par1 p) 

Methods

(==) :: Par1 p -> Par1 p -> Bool #

(/=) :: Par1 p -> Par1 p -> Bool #

Eq (ForeignPtr a) 

Methods

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

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

Eq a => Eq (Identity a) 

Methods

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

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

Eq a => Eq (Min a) 

Methods

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

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

Eq a => Eq (Max a) 

Methods

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

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

Eq a => Eq (First a) 

Methods

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

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

Eq a => Eq (Last a) 

Methods

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

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

Eq m => Eq (WrappedMonoid m) 
Eq a => Eq (Option a) 

Methods

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

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

Eq a => Eq (NonEmpty a) 

Methods

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

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

Eq a => Eq (Complex a) 

Methods

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

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

Eq (Chan a) 

Methods

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

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

Eq a => Eq (ZipList a) 

Methods

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

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

Eq (TVar a) 

Methods

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

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

Eq a => Eq (Dual a) 

Methods

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

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

Eq a => Eq (Sum a) 

Methods

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

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

Eq a => Eq (Product a) 

Methods

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

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

Eq a => Eq (First a) 

Methods

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

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

Eq a => Eq (Last a) 

Methods

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

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

Eq (IORef a) 

Methods

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

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

Eq a => Eq (Down a) 

Methods

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

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

Eq (MVar a) 

Methods

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

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

Eq a => Eq (Seq a) 

Methods

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

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

Eq a => Eq (ViewL a) 

Methods

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

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

Eq a => Eq (ViewR a) 

Methods

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

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

Eq a => Eq (IntMap a) 

Methods

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

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

Eq a => Eq (Set a) 

Methods

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

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

(Hashable a, Eq a) => Eq (HashSet a) 

Methods

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

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

(Eq a, Eq b) => Eq (Either a b) 

Methods

(==) :: Either a b -> Either a b -> Bool #

(/=) :: Either a b -> Either a b -> Bool #

Eq (f p) => Eq (Rec1 f p) 

Methods

(==) :: Rec1 f p -> Rec1 f p -> Bool #

(/=) :: Rec1 f p -> Rec1 f p -> Bool #

Eq (URec Char p) 

Methods

(==) :: URec Char p -> URec Char p -> Bool #

(/=) :: URec Char p -> URec Char p -> Bool #

Eq (URec Double p) 

Methods

(==) :: URec Double p -> URec Double p -> Bool #

(/=) :: URec Double p -> URec Double p -> Bool #

Eq (URec Float p) 

Methods

(==) :: URec Float p -> URec Float p -> Bool #

(/=) :: URec Float p -> URec Float p -> Bool #

Eq (URec Int p) 

Methods

(==) :: URec Int p -> URec Int p -> Bool #

(/=) :: URec Int p -> URec Int p -> Bool #

Eq (URec Word p) 

Methods

(==) :: URec Word p -> URec Word p -> Bool #

(/=) :: URec Word p -> URec Word p -> Bool #

Eq (URec (Ptr ()) p) 

Methods

(==) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(/=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(Eq a, Eq b) => Eq (a, b) 

Methods

(==) :: (a, b) -> (a, b) -> Bool #

(/=) :: (a, b) -> (a, b) -> Bool #

Eq a => Eq (Arg a b) 

Methods

(==) :: Arg a b -> Arg a b -> Bool #

(/=) :: Arg a b -> Arg a b -> Bool #

Eq (Proxy k s) 

Methods

(==) :: Proxy k s -> Proxy k s -> Bool #

(/=) :: Proxy k s -> Proxy k s -> Bool #

Eq (STRef s a) 

Methods

(==) :: STRef s a -> STRef s a -> Bool #

(/=) :: STRef s a -> STRef s a -> Bool #

(Eq k, Eq a) => Eq (Map k a) 

Methods

(==) :: Map k a -> Map k a -> Bool #

(/=) :: Map k a -> Map k a -> Bool #

(Eq k, Eq v) => Eq (Leaf k v) 

Methods

(==) :: Leaf k v -> Leaf k v -> Bool #

(/=) :: Leaf k v -> Leaf k v -> Bool #

(Eq k, Eq v) => Eq (HashMap k v) 

Methods

(==) :: HashMap k v -> HashMap k v -> Bool #

(/=) :: HashMap k v -> HashMap k v -> Bool #

Eq c => Eq (K1 i c p) 

Methods

(==) :: K1 i c p -> K1 i c p -> Bool #

(/=) :: K1 i c p -> K1 i c p -> Bool #

(Eq (f p), Eq (g p)) => Eq ((:+:) f g p) 

Methods

(==) :: (f :+: g) p -> (f :+: g) p -> Bool #

(/=) :: (f :+: g) p -> (f :+: g) p -> Bool #

(Eq (f p), Eq (g p)) => Eq ((:*:) f g p) 

Methods

(==) :: (f :*: g) p -> (f :*: g) p -> Bool #

(/=) :: (f :*: g) p -> (f :*: g) p -> Bool #

Eq (f (g p)) => Eq ((:.:) f g p) 

Methods

(==) :: (f :.: g) p -> (f :.: g) p -> Bool #

(/=) :: (f :.: g) p -> (f :.: g) p -> Bool #

(Eq a, Eq b, Eq c) => Eq (a, b, c) 

Methods

(==) :: (a, b, c) -> (a, b, c) -> Bool #

(/=) :: (a, b, c) -> (a, b, c) -> Bool #

Eq a => Eq (Const k a b) 

Methods

(==) :: Const k a b -> Const k a b -> Bool #

(/=) :: Const k a b -> Const k a b -> Bool #

Eq (f a) => Eq (Alt k f a) 

Methods

(==) :: Alt k f a -> Alt k f a -> Bool #

(/=) :: Alt k f a -> Alt k f a -> Bool #

Eq ((:~:) k a b) 

Methods

(==) :: (k :~: a) b -> (k :~: a) b -> Bool #

(/=) :: (k :~: a) b -> (k :~: a) b -> Bool #

(Eq e, Eq1 m, Eq a) => Eq (ErrorT e m a) 

Methods

(==) :: ErrorT e m a -> ErrorT e m a -> Bool #

(/=) :: ErrorT e m a -> ErrorT e m a -> Bool #

Eq (f p) => Eq (M1 i c f p) 

Methods

(==) :: M1 i c f p -> M1 i c f p -> Bool #

(/=) :: M1 i c f p -> M1 i c f p -> Bool #

(Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) 

Methods

(==) :: (a, b, c, d) -> (a, b, c, d) -> Bool #

(/=) :: (a, b, c, d) -> (a, b, c, d) -> Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e) 

Methods

(==) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool #

(/=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (a, b, c, d, e, f) 

Methods

(==) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool #

(/=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (a, b, c, d, e, f, g) 

Methods

(==) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool #

(/=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h) => Eq (a, b, c, d, e, f, g, h) 

Methods

(==) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool #

(/=) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) => Eq (a, b, c, d, e, f, g, h, i) 

Methods

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

(/=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j) => Eq (a, b, c, d, e, f, g, h, i, j) 

Methods

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

(/=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool #

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

Methods

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

(/=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool #

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

Methods

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

(/=) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool #

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

class Bounded a where #

The Bounded class is used to name the upper and lower limits of a + type. Ord is not a superclass of Bounded since types that are not + totally ordered may also have upper and lower bounds.

The Bounded class may be derived for any enumeration type; + minBound is the first constructor listed in the data declaration + and maxBound is the last. + Bounded may also be derived for single-constructor datatypes whose + constituent types are in Bounded.

Instances

Bounded Bool 
Bounded Char 
Bounded Int 

Methods

minBound :: Int #

maxBound :: Int #

Bounded Int8 
Bounded Int16 
Bounded Int32 
Bounded Int64 
Bounded Ordering 
Bounded Word 
Bounded Word8 
Bounded Word16 
Bounded Word32 
Bounded Word64 
Bounded () 

Methods

minBound :: () #

maxBound :: () #

Bounded All 

Methods

minBound :: All #

maxBound :: All #

Bounded Any 

Methods

minBound :: Any #

maxBound :: Any #

Bounded Associativity 
Bounded SourceUnpackedness 
Bounded SourceStrictness 
Bounded DecidedStrictness 
Bounded a => Bounded (Identity a) 
Bounded a => Bounded (Min a) 

Methods

minBound :: Min a #

maxBound :: Min a #

Bounded a => Bounded (Max a) 

Methods

minBound :: Max a #

maxBound :: Max a #

Bounded a => Bounded (First a) 

Methods

minBound :: First a #

maxBound :: First a #

Bounded a => Bounded (Last a) 

Methods

minBound :: Last a #

maxBound :: Last a #

Bounded a => Bounded (WrappedMonoid a) 
Bounded a => Bounded (Dual a) 

Methods

minBound :: Dual a #

maxBound :: Dual a #

Bounded a => Bounded (Sum a) 

Methods

minBound :: Sum a #

maxBound :: Sum a #

Bounded a => Bounded (Product a) 
(Bounded a, Bounded b) => Bounded (a, b) 

Methods

minBound :: (a, b) #

maxBound :: (a, b) #

Bounded (Proxy k s) 

Methods

minBound :: Proxy k s #

maxBound :: Proxy k s #

(Bounded a, Bounded b, Bounded c) => Bounded (a, b, c) 

Methods

minBound :: (a, b, c) #

maxBound :: (a, b, c) #

Bounded a => Bounded (Const k a b) 

Methods

minBound :: Const k a b #

maxBound :: Const k a b #

(~) k a b => Bounded ((:~:) k a b) 

Methods

minBound :: (k :~: a) b #

maxBound :: (k :~: a) b #

(Bounded a, Bounded b, Bounded c, Bounded d) => Bounded (a, b, c, d) 

Methods

minBound :: (a, b, c, d) #

maxBound :: (a, b, c, d) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e) => Bounded (a, b, c, d, e) 

Methods

minBound :: (a, b, c, d, e) #

maxBound :: (a, b, c, d, e) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f) => Bounded (a, b, c, d, e, f) 

Methods

minBound :: (a, b, c, d, e, f) #

maxBound :: (a, b, c, d, e, f) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g) => Bounded (a, b, c, d, e, f, g) 

Methods

minBound :: (a, b, c, d, e, f, g) #

maxBound :: (a, b, c, d, e, f, g) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h) => Bounded (a, b, c, d, e, f, g, h) 

Methods

minBound :: (a, b, c, d, e, f, g, h) #

maxBound :: (a, b, c, d, e, f, g, h) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i) => Bounded (a, b, c, d, e, f, g, h, i) 

Methods

minBound :: (a, b, c, d, e, f, g, h, i) #

maxBound :: (a, b, c, d, e, f, g, h, i) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j) => Bounded (a, b, c, d, e, f, g, h, i, j) 

Methods

minBound :: (a, b, c, d, e, f, g, h, i, j) #

maxBound :: (a, b, c, d, e, f, g, h, i, j) #

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

Methods

minBound :: (a, b, c, d, e, f, g, h, i, j, k) #

maxBound :: (a, b, c, d, e, f, g, h, i, j, k) #

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

Methods

minBound :: (a, b, c, d, e, f, g, h, i, j, k, l) #

maxBound :: (a, b, c, d, e, f, g, h, i, j, k, l) #

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

Methods

minBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m) #

maxBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m) #

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

Methods

minBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) #

maxBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) #

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

Methods

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

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

class Show a where #

Conversion of values to readable Strings.

Derived instances of Show have the following properties, which + are compatible with derived instances of Read:

  • The result of show is a syntactically correct Haskell + expression containing only constants, given the fixity + declarations in force at the point where the type is declared. + It contains only the constructor names defined in the data type, + parentheses, and spaces. When labelled constructor fields are + used, braces, commas, field names, and equal signs are also used.
  • If the constructor is defined to be an infix operator, then + showsPrec will produce infix applications of the constructor.
  • the representation will be enclosed in parentheses if the + precedence of the top-level constructor in x is less than d + (associativity is ignored). Thus, if d is 0 then the result + is never surrounded in parentheses; if d is 11 it is always + surrounded in parentheses, unless it is an atomic expression.
  • If the constructor is defined using record syntax, then show + will produce the record-syntax form, with the fields given in the + same order as the original declaration.

For example, given the declarations

infixr 5 :^:
+data Tree a =  Leaf a  |  Tree a :^: Tree a

the derived instance of Show is equivalent to

instance (Show a) => Show (Tree a) where
+
+       showsPrec d (Leaf m) = showParen (d > app_prec) $
+            showString "Leaf " . showsPrec (app_prec+1) m
+         where app_prec = 10
+
+       showsPrec d (u :^: v) = showParen (d > up_prec) $
+            showsPrec (up_prec+1) u .
+            showString " :^: "      .
+            showsPrec (up_prec+1) v
+         where up_prec = 5

Note that right-associativity of :^: is ignored. For example,

  • show (Leaf 1 :^: Leaf 2 :^: Leaf 3) produces the string + "Leaf 1 :^: (Leaf 2 :^: Leaf 3)".

Minimal complete definition

showsPrec | show

Instances

Show Bool 

Methods

showsPrec :: Int -> Bool -> ShowS #

show :: Bool -> String #

showList :: [Bool] -> ShowS #

Show Char 

Methods

showsPrec :: Int -> Char -> ShowS #

show :: Char -> String #

showList :: [Char] -> ShowS #

Show Int 

Methods

showsPrec :: Int -> Int -> ShowS #

show :: Int -> String #

showList :: [Int] -> ShowS #

Show Int8 

Methods

showsPrec :: Int -> Int8 -> ShowS #

show :: Int8 -> String #

showList :: [Int8] -> ShowS #

Show Int16 

Methods

showsPrec :: Int -> Int16 -> ShowS #

show :: Int16 -> String #

showList :: [Int16] -> ShowS #

Show Int32 

Methods

showsPrec :: Int -> Int32 -> ShowS #

show :: Int32 -> String #

showList :: [Int32] -> ShowS #

Show Int64 

Methods

showsPrec :: Int -> Int64 -> ShowS #

show :: Int64 -> String #

showList :: [Int64] -> ShowS #

Show Integer 
Show Ordering 
Show Word 

Methods

showsPrec :: Int -> Word -> ShowS #

show :: Word -> String #

showList :: [Word] -> ShowS #

Show Word8 

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Show Word16 
Show Word32 
Show Word64 
Show CallStack 
Show TypeRep 
Show Exp 

Methods

showsPrec :: Int -> Exp -> ShowS #

show :: Exp -> String #

showList :: [Exp] -> ShowS #

Show Match 

Methods

showsPrec :: Int -> Match -> ShowS #

show :: Match -> String #

showList :: [Match] -> ShowS #

Show Clause 
Show Pat 

Methods

showsPrec :: Int -> Pat -> ShowS #

show :: Pat -> String #

showList :: [Pat] -> ShowS #

Show Type 

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Show Dec 

Methods

showsPrec :: Int -> Dec -> ShowS #

show :: Dec -> String #

showList :: [Dec] -> ShowS #

Show Name 

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Show FunDep 
Show TyVarBndr 
Show InjectivityAnn 
Show Overlap 
Show () 

Methods

showsPrec :: Int -> () -> ShowS #

show :: () -> String #

showList :: [()] -> ShowS #

Show TyCon 

Methods

showsPrec :: Int -> TyCon -> ShowS #

show :: TyCon -> String #

showList :: [TyCon] -> ShowS #

Show Module 
Show TrName 
Show Handle 
Show HandleType 

Methods

showsPrec :: Int -> HandleType -> ShowS #

show :: HandleType -> String #

showList :: [HandleType] -> ShowS #

Show Void 

Methods

showsPrec :: Int -> Void -> ShowS #

show :: Void -> String #

showList :: [Void] -> ShowS #

Show Version 
Show HandlePosn 
Show ThreadId 
Show BlockReason 
Show ThreadStatus 
Show BlockedIndefinitelyOnMVar 
Show BlockedIndefinitelyOnSTM 
Show Deadlock 
Show AllocationLimitExceeded 
Show AssertionFailed 
Show SomeAsyncException 
Show AsyncException 
Show ArrayException 
Show ExitCode 
Show IOErrorType 
Show BufferMode 
Show Newline 
Show NewlineMode 
Show All 

Methods

showsPrec :: Int -> All -> ShowS #

show :: All -> String #

showList :: [All] -> ShowS #

Show Any 

Methods

showsPrec :: Int -> Any -> ShowS #

show :: Any -> String #

showList :: [Any] -> ShowS #

Show Fixity 
Show Associativity 
Show SourceUnpackedness 
Show SourceStrictness 
Show DecidedStrictness 
Show MaskingState 
Show IOException 
Show ErrorCall 
Show ArithException 
Show SomeNat 
Show SomeSymbol 
Show IOMode 
Show SomeException 
Show SrcLoc 
Show ByteString 
Show IntSet 
Show Extension 
Show SyncExceptionWrapper 
Show AsyncExceptionWrapper 
Show ModName 
Show PkgName 
Show Module 
Show OccName 
Show NameFlavour 
Show NameSpace 
Show Loc 

Methods

showsPrec :: Int -> Loc -> ShowS #

show :: Loc -> String #

showList :: [Loc] -> ShowS #

Show Info 

Methods

showsPrec :: Int -> Info -> ShowS #

show :: Info -> String #

showList :: [Info] -> ShowS #

Show ModuleInfo 
Show Fixity 
Show FixityDirection 
Show Lit 

Methods

showsPrec :: Int -> Lit -> ShowS #

show :: Lit -> String #

showList :: [Lit] -> ShowS #

Show Body 

Methods

showsPrec :: Int -> Body -> ShowS #

show :: Body -> String #

showList :: [Body] -> ShowS #

Show Guard 

Methods

showsPrec :: Int -> Guard -> ShowS #

show :: Guard -> String #

showList :: [Guard] -> ShowS #

Show Stmt 

Methods

showsPrec :: Int -> Stmt -> ShowS #

show :: Stmt -> String #

showList :: [Stmt] -> ShowS #

Show Range 

Methods

showsPrec :: Int -> Range -> ShowS #

show :: Range -> String #

showList :: [Range] -> ShowS #

Show TypeFamilyHead 
Show TySynEqn 
Show FamFlavour 
Show Foreign 
Show Callconv 
Show Safety 
Show Pragma 
Show Inline 
Show RuleMatch 
Show Phases 
Show RuleBndr 
Show AnnTarget 
Show SourceUnpackedness 
Show SourceStrictness 
Show DecidedStrictness 
Show Con 

Methods

showsPrec :: Int -> Con -> ShowS #

show :: Con -> String #

showList :: [Con] -> ShowS #

Show Bang 

Methods

showsPrec :: Int -> Bang -> ShowS #

show :: Bang -> String #

showList :: [Bang] -> ShowS #

Show FamilyResultSig 
Show TyLit 

Methods

showsPrec :: Int -> TyLit -> ShowS #

show :: TyLit -> String #

showList :: [TyLit] -> ShowS #

Show Role 

Methods

showsPrec :: Int -> Role -> ShowS #

show :: Role -> String #

showList :: [Role] -> ShowS #

Show AnnLookup 
Show CodePoint 

Methods

showsPrec :: Int -> CodePoint -> ShowS #

show :: CodePoint -> String #

showList :: [CodePoint] -> ShowS #

Show DecoderState 

Methods

showsPrec :: Int -> DecoderState -> ShowS #

show :: DecoderState -> String #

showList :: [DecoderState] -> ShowS #

Show Decoding 
Show UnicodeException 
Show a => Show [a] 

Methods

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

show :: [a] -> String #

showList :: [[a]] -> ShowS #

Show a => Show (Maybe a) 

Methods

showsPrec :: Int -> Maybe a -> ShowS #

show :: Maybe a -> String #

showList :: [Maybe a] -> ShowS #

Show a => Show (Ratio a) 

Methods

showsPrec :: Int -> Ratio a -> ShowS #

show :: Ratio a -> String #

showList :: [Ratio a] -> ShowS #

Show (Ptr a) 

Methods

showsPrec :: Int -> Ptr a -> ShowS #

show :: Ptr a -> String #

showList :: [Ptr a] -> ShowS #

Show (FunPtr a) 

Methods

showsPrec :: Int -> FunPtr a -> ShowS #

show :: FunPtr a -> String #

showList :: [FunPtr a] -> ShowS #

Show (V1 p) 

Methods

showsPrec :: Int -> V1 p -> ShowS #

show :: V1 p -> String #

showList :: [V1 p] -> ShowS #

Show (U1 p) 

Methods

showsPrec :: Int -> U1 p -> ShowS #

show :: U1 p -> String #

showList :: [U1 p] -> ShowS #

Show p => Show (Par1 p) 

Methods

showsPrec :: Int -> Par1 p -> ShowS #

show :: Par1 p -> String #

showList :: [Par1 p] -> ShowS #

Show (ForeignPtr a) 
Show a => Show (Identity a)

This instance would be equivalent to the derived instances of the + Identity newtype if the runIdentity field were removed

Methods

showsPrec :: Int -> Identity a -> ShowS #

show :: Identity a -> String #

showList :: [Identity a] -> ShowS #

Show a => Show (Min a) 

Methods

showsPrec :: Int -> Min a -> ShowS #

show :: Min a -> String #

showList :: [Min a] -> ShowS #

Show a => Show (Max a) 

Methods

showsPrec :: Int -> Max a -> ShowS #

show :: Max a -> String #

showList :: [Max a] -> ShowS #

Show a => Show (First a) 

Methods

showsPrec :: Int -> First a -> ShowS #

show :: First a -> String #

showList :: [First a] -> ShowS #

Show a => Show (Last a) 

Methods

showsPrec :: Int -> Last a -> ShowS #

show :: Last a -> String #

showList :: [Last a] -> ShowS #

Show m => Show (WrappedMonoid m) 
Show a => Show (Option a) 

Methods

showsPrec :: Int -> Option a -> ShowS #

show :: Option a -> String #

showList :: [Option a] -> ShowS #

Show a => Show (NonEmpty a) 

Methods

showsPrec :: Int -> NonEmpty a -> ShowS #

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Show a => Show (Complex a) 

Methods

showsPrec :: Int -> Complex a -> ShowS #

show :: Complex a -> String #

showList :: [Complex a] -> ShowS #

Show a => Show (ZipList a) 

Methods

showsPrec :: Int -> ZipList a -> ShowS #

show :: ZipList a -> String #

showList :: [ZipList a] -> ShowS #

Show a => Show (Dual a) 

Methods

showsPrec :: Int -> Dual a -> ShowS #

show :: Dual a -> String #

showList :: [Dual a] -> ShowS #

Show a => Show (Sum a) 

Methods

showsPrec :: Int -> Sum a -> ShowS #

show :: Sum a -> String #

showList :: [Sum a] -> ShowS #

Show a => Show (Product a) 

Methods

showsPrec :: Int -> Product a -> ShowS #

show :: Product a -> String #

showList :: [Product a] -> ShowS #

Show a => Show (First a) 

Methods

showsPrec :: Int -> First a -> ShowS #

show :: First a -> String #

showList :: [First a] -> ShowS #

Show a => Show (Last a) 

Methods

showsPrec :: Int -> Last a -> ShowS #

show :: Last a -> String #

showList :: [Last a] -> ShowS #

Show a => Show (Down a) 

Methods

showsPrec :: Int -> Down a -> ShowS #

show :: Down a -> String #

showList :: [Down a] -> ShowS #

Show a => Show (Seq a) 

Methods

showsPrec :: Int -> Seq a -> ShowS #

show :: Seq a -> String #

showList :: [Seq a] -> ShowS #

Show a => Show (ViewL a) 

Methods

showsPrec :: Int -> ViewL a -> ShowS #

show :: ViewL a -> String #

showList :: [ViewL a] -> ShowS #

Show a => Show (ViewR a) 

Methods

showsPrec :: Int -> ViewR a -> ShowS #

show :: ViewR a -> String #

showList :: [ViewR a] -> ShowS #

Show a => Show (IntMap a) 

Methods

showsPrec :: Int -> IntMap a -> ShowS #

show :: IntMap a -> String #

showList :: [IntMap a] -> ShowS #

Show a => Show (Set a) 

Methods

showsPrec :: Int -> Set a -> ShowS #

show :: Set a -> String #

showList :: [Set a] -> ShowS #

Show a => Show (Array a) 

Methods

showsPrec :: Int -> Array a -> ShowS #

show :: Array a -> String #

showList :: [Array a] -> ShowS #

Show a => Show (HashSet a) 

Methods

showsPrec :: Int -> HashSet a -> ShowS #

show :: HashSet a -> String #

showList :: [HashSet a] -> ShowS #

(Show a, Show b) => Show (Either a b) 

Methods

showsPrec :: Int -> Either a b -> ShowS #

show :: Either a b -> String #

showList :: [Either a b] -> ShowS #

Show (f p) => Show (Rec1 f p) 

Methods

showsPrec :: Int -> Rec1 f p -> ShowS #

show :: Rec1 f p -> String #

showList :: [Rec1 f p] -> ShowS #

Show (URec Char p) 

Methods

showsPrec :: Int -> URec Char p -> ShowS #

show :: URec Char p -> String #

showList :: [URec Char p] -> ShowS #

Show (URec Double p) 

Methods

showsPrec :: Int -> URec Double p -> ShowS #

show :: URec Double p -> String #

showList :: [URec Double p] -> ShowS #

Show (URec Float p) 

Methods

showsPrec :: Int -> URec Float p -> ShowS #

show :: URec Float p -> String #

showList :: [URec Float p] -> ShowS #

Show (URec Int p) 

Methods

showsPrec :: Int -> URec Int p -> ShowS #

show :: URec Int p -> String #

showList :: [URec Int p] -> ShowS #

Show (URec Word p) 

Methods

showsPrec :: Int -> URec Word p -> ShowS #

show :: URec Word p -> String #

showList :: [URec Word p] -> ShowS #

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

Methods

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

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

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

(Show a, Show b) => Show (Arg a b) 

Methods

showsPrec :: Int -> Arg a b -> ShowS #

show :: Arg a b -> String #

showList :: [Arg a b] -> ShowS #

Show (Proxy k s) 

Methods

showsPrec :: Int -> Proxy k s -> ShowS #

show :: Proxy k s -> String #

showList :: [Proxy k s] -> ShowS #

(Show k, Show a) => Show (Map k a) 

Methods

showsPrec :: Int -> Map k a -> ShowS #

show :: Map k a -> String #

showList :: [Map k a] -> ShowS #

(Show k, Show v) => Show (HashMap k v) 

Methods

showsPrec :: Int -> HashMap k v -> ShowS #

show :: HashMap k v -> String #

showList :: [HashMap k v] -> ShowS #

Show c => Show (K1 i c p) 

Methods

showsPrec :: Int -> K1 i c p -> ShowS #

show :: K1 i c p -> String #

showList :: [K1 i c p] -> ShowS #

(Show (f p), Show (g p)) => Show ((:+:) f g p) 

Methods

showsPrec :: Int -> (f :+: g) p -> ShowS #

show :: (f :+: g) p -> String #

showList :: [(f :+: g) p] -> ShowS #

(Show (f p), Show (g p)) => Show ((:*:) f g p) 

Methods

showsPrec :: Int -> (f :*: g) p -> ShowS #

show :: (f :*: g) p -> String #

showList :: [(f :*: g) p] -> ShowS #

Show (f (g p)) => Show ((:.:) f g p) 

Methods

showsPrec :: Int -> (f :.: g) p -> ShowS #

show :: (f :.: g) p -> String #

showList :: [(f :.: g) p] -> ShowS #

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

Methods

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

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

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

Show a => Show (Const k a b)

This instance would be equivalent to the derived instances of the + Const newtype if the runConst field were removed

Methods

showsPrec :: Int -> Const k a b -> ShowS #

show :: Const k a b -> String #

showList :: [Const k a b] -> ShowS #

Show (f a) => Show (Alt k f a) 

Methods

showsPrec :: Int -> Alt k f a -> ShowS #

show :: Alt k f a -> String #

showList :: [Alt k f a] -> ShowS #

Show ((:~:) k a b) 

Methods

showsPrec :: Int -> (k :~: a) b -> ShowS #

show :: (k :~: a) b -> String #

showList :: [(k :~: a) b] -> ShowS #

(Show e, Show1 m, Show a) => Show (ErrorT e m a) 

Methods

showsPrec :: Int -> ErrorT e m a -> ShowS #

show :: ErrorT e m a -> String #

showList :: [ErrorT e m a] -> ShowS #

Show (f p) => Show (M1 i c f p) 

Methods

showsPrec :: Int -> M1 i c f p -> ShowS #

show :: M1 i c f p -> String #

showList :: [M1 i c f p] -> ShowS #

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

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) 

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) 

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) 

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) 

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) 

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) 

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) 

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) 

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) 

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) 

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) 

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 #

class Read a where #

Parsing of Strings, producing values.

Derived instances of Read make the following assumptions, which + derived instances of Show obey:

  • If the constructor is defined to be an infix operator, then the + derived Read instance will parse only infix applications of + the constructor (not the prefix form).
  • Associativity is not used to reduce the occurrence of parentheses, + although precedence may be.
  • If the constructor is defined using record syntax, the derived Read + will parse only the record-syntax form, and furthermore, the fields + must be given in the same order as the original declaration.
  • The derived Read instance allows arbitrary Haskell whitespace + between tokens of the input string. Extra parentheses are also + allowed.

For example, given the declarations

infixr 5 :^:
+data Tree a =  Leaf a  |  Tree a :^: Tree a

the derived instance of Read in Haskell 2010 is equivalent to

instance (Read a) => Read (Tree a) where
+
+        readsPrec d r =  readParen (d > app_prec)
+                         (\r -> [(Leaf m,t) |
+                                 ("Leaf",s) <- lex r,
+                                 (m,t) <- readsPrec (app_prec+1) s]) r
+
+                      ++ readParen (d > up_prec)
+                         (\r -> [(u:^:v,w) |
+                                 (u,s) <- readsPrec (up_prec+1) r,
+                                 (":^:",t) <- lex s,
+                                 (v,w) <- readsPrec (up_prec+1) t]) r
+
+          where app_prec = 10
+                up_prec = 5

Note that right-associativity of :^: is unused.

The derived instance in GHC is equivalent to

instance (Read a) => Read (Tree a) where
+
+        readPrec = parens $ (prec app_prec $ do
+                                 Ident "Leaf" <- lexP
+                                 m <- step readPrec
+                                 return (Leaf m))
+
+                     +++ (prec up_prec $ do
+                                 u <- step readPrec
+                                 Symbol ":^:" <- lexP
+                                 v <- step readPrec
+                                 return (u :^: v))
+
+          where app_prec = 10
+                up_prec = 5
+
+        readListPrec = readListPrecDefault

Minimal complete definition

readsPrec | readPrec

Instances

Read Bool 
Read Char 
Read Double 
Read Float 
Read Int 
Read Int8 
Read Int16 
Read Int32 
Read Int64 
Read Integer 
Read Ordering 
Read Word 
Read Word8 
Read Word16 
Read Word32 
Read Word64 
Read () 

Methods

readsPrec :: Int -> ReadS () #

readList :: ReadS [()] #

readPrec :: ReadPrec () #

readListPrec :: ReadPrec [()] #

Read Void

Reading a Void value is always a parse error, considering + Void as a data type with no constructors.

Read Version 
Read ExitCode 
Read BufferMode 
Read Newline 
Read NewlineMode 
Read All 
Read Any 
Read Fixity 
Read Associativity 
Read SourceUnpackedness 
Read SourceStrictness 
Read DecidedStrictness 
Read SomeNat 
Read SomeSymbol 
Read IOMode 
Read Lexeme 
Read GeneralCategory 
Read ByteString 
Read IntSet 
Read a => Read [a] 

Methods

readsPrec :: Int -> ReadS [a] #

readList :: ReadS [[a]] #

readPrec :: ReadPrec [a] #

readListPrec :: ReadPrec [[a]] #

Read a => Read (Maybe a) 
(Integral a, Read a) => Read (Ratio a) 
Read (V1 p) 
Read (U1 p) 
Read p => Read (Par1 p) 
Read a => Read (Identity a)

This instance would be equivalent to the derived instances of the + Identity newtype if the runIdentity field were removed

Read a => Read (Min a) 
Read a => Read (Max a) 
Read a => Read (First a) 
Read a => Read (Last a) 
Read m => Read (WrappedMonoid m) 
Read a => Read (Option a) 
Read a => Read (NonEmpty a) 
Read a => Read (Complex a) 
Read a => Read (ZipList a) 
Read a => Read (Dual a) 
Read a => Read (Sum a) 
Read a => Read (Product a) 
Read a => Read (First a) 
Read a => Read (Last a) 
Read a => Read (Down a) 
Read a => Read (Seq a) 
Read a => Read (ViewL a) 
Read a => Read (ViewR a) 
Read e => Read (IntMap e) 
(Read a, Ord a) => Read (Set a) 
(Eq a, Hashable a, Read a) => Read (HashSet a) 
(Read a, Read b) => Read (Either a b) 
Read (f p) => Read (Rec1 f p) 

Methods

readsPrec :: Int -> ReadS (Rec1 f p) #

readList :: ReadS [Rec1 f p] #

readPrec :: ReadPrec (Rec1 f p) #

readListPrec :: ReadPrec [Rec1 f p] #

(Read a, Read b) => Read (a, b) 

Methods

readsPrec :: Int -> ReadS (a, b) #

readList :: ReadS [(a, b)] #

readPrec :: ReadPrec (a, b) #

readListPrec :: ReadPrec [(a, b)] #

(Ix a, Read a, Read b) => Read (Array a b) 
(Read a, Read b) => Read (Arg a b) 

Methods

readsPrec :: Int -> ReadS (Arg a b) #

readList :: ReadS [Arg a b] #

readPrec :: ReadPrec (Arg a b) #

readListPrec :: ReadPrec [Arg a b] #

Read (Proxy k s) 
(Ord k, Read k, Read e) => Read (Map k e) 

Methods

readsPrec :: Int -> ReadS (Map k e) #

readList :: ReadS [Map k e] #

readPrec :: ReadPrec (Map k e) #

readListPrec :: ReadPrec [Map k e] #

(Eq k, Hashable k, Read k, Read e) => Read (HashMap k e) 
Read c => Read (K1 i c p) 

Methods

readsPrec :: Int -> ReadS (K1 i c p) #

readList :: ReadS [K1 i c p] #

readPrec :: ReadPrec (K1 i c p) #

readListPrec :: ReadPrec [K1 i c p] #

(Read (f p), Read (g p)) => Read ((:+:) f g p) 

Methods

readsPrec :: Int -> ReadS ((f :+: g) p) #

readList :: ReadS [(f :+: g) p] #

readPrec :: ReadPrec ((f :+: g) p) #

readListPrec :: ReadPrec [(f :+: g) p] #

(Read (f p), Read (g p)) => Read ((:*:) f g p) 

Methods

readsPrec :: Int -> ReadS ((f :*: g) p) #

readList :: ReadS [(f :*: g) p] #

readPrec :: ReadPrec ((f :*: g) p) #

readListPrec :: ReadPrec [(f :*: g) p] #

Read (f (g p)) => Read ((:.:) f g p) 

Methods

readsPrec :: Int -> ReadS ((f :.: g) p) #

readList :: ReadS [(f :.: g) p] #

readPrec :: ReadPrec ((f :.: g) p) #

readListPrec :: ReadPrec [(f :.: g) p] #

(Read a, Read b, Read c) => Read (a, b, c) 

Methods

readsPrec :: Int -> ReadS (a, b, c) #

readList :: ReadS [(a, b, c)] #

readPrec :: ReadPrec (a, b, c) #

readListPrec :: ReadPrec [(a, b, c)] #

Read a => Read (Const k a b)

This instance would be equivalent to the derived instances of the + Const newtype if the runConst field were removed

Methods

readsPrec :: Int -> ReadS (Const k a b) #

readList :: ReadS [Const k a b] #

readPrec :: ReadPrec (Const k a b) #

readListPrec :: ReadPrec [Const k a b] #

Read (f a) => Read (Alt k f a) 

Methods

readsPrec :: Int -> ReadS (Alt k f a) #

readList :: ReadS [Alt k f a] #

readPrec :: ReadPrec (Alt k f a) #

readListPrec :: ReadPrec [Alt k f a] #

(~) k a b => Read ((:~:) k a b) 

Methods

readsPrec :: Int -> ReadS ((k :~: a) b) #

readList :: ReadS [(k :~: a) b] #

readPrec :: ReadPrec ((k :~: a) b) #

readListPrec :: ReadPrec [(k :~: a) b] #

(Read e, Read1 m, Read a) => Read (ErrorT e m a) 

Methods

readsPrec :: Int -> ReadS (ErrorT e m a) #

readList :: ReadS [ErrorT e m a] #

readPrec :: ReadPrec (ErrorT e m a) #

readListPrec :: ReadPrec [ErrorT e m a] #

Read (f p) => Read (M1 i c f p) 

Methods

readsPrec :: Int -> ReadS (M1 i c f p) #

readList :: ReadS [M1 i c f p] #

readPrec :: ReadPrec (M1 i c f p) #

readListPrec :: ReadPrec [M1 i c f p] #

(Read a, Read b, Read c, Read d) => Read (a, b, c, d) 

Methods

readsPrec :: Int -> ReadS (a, b, c, d) #

readList :: ReadS [(a, b, c, d)] #

readPrec :: ReadPrec (a, b, c, d) #

readListPrec :: ReadPrec [(a, b, c, d)] #

(Read a, Read b, Read c, Read d, Read e) => Read (a, b, c, d, e) 

Methods

readsPrec :: Int -> ReadS (a, b, c, d, e) #

readList :: ReadS [(a, b, c, d, e)] #

readPrec :: ReadPrec (a, b, c, d, e) #

readListPrec :: ReadPrec [(a, b, c, d, e)] #

(Read a, Read b, Read c, Read d, Read e, Read f) => Read (a, b, c, d, e, f) 

Methods

readsPrec :: Int -> ReadS (a, b, c, d, e, f) #

readList :: ReadS [(a, b, c, d, e, f)] #

readPrec :: ReadPrec (a, b, c, d, e, f) #

readListPrec :: ReadPrec [(a, b, c, d, e, f)] #

(Read a, Read b, Read c, Read d, Read e, Read f, Read g) => Read (a, b, c, d, e, f, g) 

Methods

readsPrec :: Int -> ReadS (a, b, c, d, e, f, g) #

readList :: ReadS [(a, b, c, d, e, f, g)] #

readPrec :: ReadPrec (a, b, c, d, e, f, g) #

readListPrec :: ReadPrec [(a, b, c, d, e, f, g)] #

(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h) => Read (a, b, c, d, e, f, g, h) 

Methods

readsPrec :: Int -> ReadS (a, b, c, d, e, f, g, h) #

readList :: ReadS [(a, b, c, d, e, f, g, h)] #

readPrec :: ReadPrec (a, b, c, d, e, f, g, h) #

readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h)] #

(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i) => Read (a, b, c, d, e, f, g, h, i) 

Methods

readsPrec :: Int -> ReadS (a, b, c, d, e, f, g, h, i) #

readList :: ReadS [(a, b, c, d, e, f, g, h, i)] #

readPrec :: ReadPrec (a, b, c, d, e, f, g, h, i) #

readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h, i)] #

(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j) => Read (a, b, c, d, e, f, g, h, i, j) 

Methods

readsPrec :: Int -> ReadS (a, b, c, d, e, f, g, h, i, j) #

readList :: ReadS [(a, b, c, d, e, f, g, h, i, j)] #

readPrec :: ReadPrec (a, b, c, d, e, f, g, h, i, j) #

readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h, i, j)] #

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

Methods

readsPrec :: Int -> ReadS (a, b, c, d, e, f, g, h, i, j, k) #

readList :: ReadS [(a, b, c, d, e, f, g, h, i, j, k)] #

readPrec :: ReadPrec (a, b, c, d, e, f, g, h, i, j, k) #

readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h, i, j, k)] #

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

Methods

readsPrec :: Int -> ReadS (a, b, c, d, e, f, g, h, i, j, k, l) #

readList :: ReadS [(a, b, c, d, e, f, g, h, i, j, k, l)] #

readPrec :: ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l) #

readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h, i, j, k, l)] #

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

Methods

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

readList :: ReadS [(a, b, c, d, e, f, g, h, i, j, k, l, m)] #

readPrec :: ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l, m) #

readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h, i, j, k, l, m)] #

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

Methods

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

readList :: ReadS [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] #

readPrec :: ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l, m, n) #

readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] #

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

Methods

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

readList :: ReadS [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] #

readPrec :: ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) #

readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] #

class Functor f where #

The Functor class is used for types that can be mapped over. +Instances of Functor should satisfy the following laws:

fmap id  ==  id
+fmap (f . g)  ==  fmap f . fmap g

The instances of Functor for lists, Maybe and IO +satisfy these laws.

Minimal complete definition

fmap

Instances

Functor [] 

Methods

fmap :: (a -> b) -> [a] -> [b] #

(<$) :: a -> [b] -> [a] #

Functor Maybe 

Methods

fmap :: (a -> b) -> Maybe a -> Maybe b #

(<$) :: a -> Maybe b -> Maybe a #

Functor IO 

Methods

fmap :: (a -> b) -> IO a -> IO b #

(<$) :: a -> IO b -> IO a #

Functor V1 

Methods

fmap :: (a -> b) -> V1 a -> V1 b #

(<$) :: a -> V1 b -> V1 a #

Functor U1 

Methods

fmap :: (a -> b) -> U1 a -> U1 b #

(<$) :: a -> U1 b -> U1 a #

Functor Par1 

Methods

fmap :: (a -> b) -> Par1 a -> Par1 b #

(<$) :: a -> Par1 b -> Par1 a #

Functor Q 

Methods

fmap :: (a -> b) -> Q a -> Q b #

(<$) :: a -> Q b -> Q a #

Functor Id 

Methods

fmap :: (a -> b) -> Id a -> Id b #

(<$) :: a -> Id b -> Id a #

Functor P 

Methods

fmap :: (a -> b) -> P a -> P b #

(<$) :: a -> P b -> P a #

Functor Identity 

Methods

fmap :: (a -> b) -> Identity a -> Identity b #

(<$) :: a -> Identity b -> Identity a #

Functor Min 

Methods

fmap :: (a -> b) -> Min a -> Min b #

(<$) :: a -> Min b -> Min a #

Functor Max 

Methods

fmap :: (a -> b) -> Max a -> Max b #

(<$) :: a -> Max b -> Max a #

Functor First 

Methods

fmap :: (a -> b) -> First a -> First b #

(<$) :: a -> First b -> First a #

Functor Last 

Methods

fmap :: (a -> b) -> Last a -> Last b #

(<$) :: a -> Last b -> Last a #

Functor Option 

Methods

fmap :: (a -> b) -> Option a -> Option b #

(<$) :: a -> Option b -> Option a #

Functor NonEmpty 

Methods

fmap :: (a -> b) -> NonEmpty a -> NonEmpty b #

(<$) :: a -> NonEmpty b -> NonEmpty a #

Functor Complex 

Methods

fmap :: (a -> b) -> Complex a -> Complex b #

(<$) :: a -> Complex b -> Complex a #

Functor ZipList 

Methods

fmap :: (a -> b) -> ZipList a -> ZipList b #

(<$) :: a -> ZipList b -> ZipList a #

Functor STM 

Methods

fmap :: (a -> b) -> STM a -> STM b #

(<$) :: a -> STM b -> STM a #

Functor Dual 

Methods

fmap :: (a -> b) -> Dual a -> Dual b #

(<$) :: a -> Dual b -> Dual a #

Functor Sum 

Methods

fmap :: (a -> b) -> Sum a -> Sum b #

(<$) :: a -> Sum b -> Sum a #

Functor Product 

Methods

fmap :: (a -> b) -> Product a -> Product b #

(<$) :: a -> Product b -> Product a #

Functor First 

Methods

fmap :: (a -> b) -> First a -> First b #

(<$) :: a -> First b -> First a #

Functor Last 

Methods

fmap :: (a -> b) -> Last a -> Last b #

(<$) :: a -> Last b -> Last a #

Functor ReadPrec 

Methods

fmap :: (a -> b) -> ReadPrec a -> ReadPrec b #

(<$) :: a -> ReadPrec b -> ReadPrec a #

Functor ReadP 

Methods

fmap :: (a -> b) -> ReadP a -> ReadP b #

(<$) :: a -> ReadP b -> ReadP a #

Functor Digit 

Methods

fmap :: (a -> b) -> Digit a -> Digit b #

(<$) :: a -> Digit b -> Digit a #

Functor Node 

Methods

fmap :: (a -> b) -> Node a -> Node b #

(<$) :: a -> Node b -> Node a #

Functor Elem 

Methods

fmap :: (a -> b) -> Elem a -> Elem b #

(<$) :: a -> Elem b -> Elem a #

Functor FingerTree 

Methods

fmap :: (a -> b) -> FingerTree a -> FingerTree b #

(<$) :: a -> FingerTree b -> FingerTree a #

Functor Seq 

Methods

fmap :: (a -> b) -> Seq a -> Seq b #

(<$) :: a -> Seq b -> Seq a #

Functor ViewL 

Methods

fmap :: (a -> b) -> ViewL a -> ViewL b #

(<$) :: a -> ViewL b -> ViewL a #

Functor ViewR 

Methods

fmap :: (a -> b) -> ViewR a -> ViewR b #

(<$) :: a -> ViewR b -> ViewR a #

Functor IntMap 

Methods

fmap :: (a -> b) -> IntMap a -> IntMap b #

(<$) :: a -> IntMap b -> IntMap a #

Functor ((->) r) 

Methods

fmap :: (a -> b) -> (r -> a) -> r -> b #

(<$) :: a -> (r -> b) -> r -> a #

Functor (Either a) 

Methods

fmap :: (a -> b) -> Either a a -> Either a b #

(<$) :: a -> Either a b -> Either a a #

Functor f => Functor (Rec1 f) 

Methods

fmap :: (a -> b) -> Rec1 f a -> Rec1 f b #

(<$) :: a -> Rec1 f b -> Rec1 f a #

Functor (URec Char) 

Methods

fmap :: (a -> b) -> URec Char a -> URec Char b #

(<$) :: a -> URec Char b -> URec Char a #

Functor (URec Double) 

Methods

fmap :: (a -> b) -> URec Double a -> URec Double b #

(<$) :: a -> URec Double b -> URec Double a #

Functor (URec Float) 

Methods

fmap :: (a -> b) -> URec Float a -> URec Float b #

(<$) :: a -> URec Float b -> URec Float a #

Functor (URec Int) 

Methods

fmap :: (a -> b) -> URec Int a -> URec Int b #

(<$) :: a -> URec Int b -> URec Int a #

Functor (URec Word) 

Methods

fmap :: (a -> b) -> URec Word a -> URec Word b #

(<$) :: a -> URec Word b -> URec Word a #

Functor (URec (Ptr ())) 

Methods

fmap :: (a -> b) -> URec (Ptr ()) a -> URec (Ptr ()) b #

(<$) :: a -> URec (Ptr ()) b -> URec (Ptr ()) a #

Functor ((,) a) 

Methods

fmap :: (a -> b) -> (a, a) -> (a, b) #

(<$) :: a -> (a, b) -> (a, a) #

Functor (StateL s) 

Methods

fmap :: (a -> b) -> StateL s a -> StateL s b #

(<$) :: a -> StateL s b -> StateL s a #

Functor (StateR s) 

Methods

fmap :: (a -> b) -> StateR s a -> StateR s b #

(<$) :: a -> StateR s b -> StateR s a #

Functor (Arg a) 

Methods

fmap :: (a -> b) -> Arg a a -> Arg a b #

(<$) :: a -> Arg a b -> Arg a a #

Monad m => Functor (WrappedMonad m) 

Methods

fmap :: (a -> b) -> WrappedMonad m a -> WrappedMonad m b #

(<$) :: a -> WrappedMonad m b -> WrappedMonad m a #

Arrow a => Functor (ArrowMonad a) 

Methods

fmap :: (a -> b) -> ArrowMonad a a -> ArrowMonad a b #

(<$) :: a -> ArrowMonad a b -> ArrowMonad a a #

Functor (Proxy *) 

Methods

fmap :: (a -> b) -> Proxy * a -> Proxy * b #

(<$) :: a -> Proxy * b -> Proxy * a #

Functor (State s) 

Methods

fmap :: (a -> b) -> State s a -> State s b #

(<$) :: a -> State s b -> State s a #

Functor (Map k) 

Methods

fmap :: (a -> b) -> Map k a -> Map k b #

(<$) :: a -> Map k b -> Map k a #

Monad m => Functor (Handler m) 

Methods

fmap :: (a -> b) -> Handler m a -> Handler m b #

(<$) :: a -> Handler m b -> Handler m a #

Functor (HashMap k) 

Methods

fmap :: (a -> b) -> HashMap k a -> HashMap k b #

(<$) :: a -> HashMap k b -> HashMap k a #

Functor (K1 i c) 

Methods

fmap :: (a -> b) -> K1 i c a -> K1 i c b #

(<$) :: a -> K1 i c b -> K1 i c a #

(Functor f, Functor g) => Functor ((:+:) f g) 

Methods

fmap :: (a -> b) -> (f :+: g) a -> (f :+: g) b #

(<$) :: a -> (f :+: g) b -> (f :+: g) a #

(Functor f, Functor g) => Functor ((:*:) f g) 

Methods

fmap :: (a -> b) -> (f :*: g) a -> (f :*: g) b #

(<$) :: a -> (f :*: g) b -> (f :*: g) a #

(Functor f, Functor g) => Functor ((:.:) f g) 

Methods

fmap :: (a -> b) -> (f :.: g) a -> (f :.: g) b #

(<$) :: a -> (f :.: g) b -> (f :.: g) a #

Arrow a => Functor (WrappedArrow a b) 

Methods

fmap :: (a -> b) -> WrappedArrow a b a -> WrappedArrow a b b #

(<$) :: a -> WrappedArrow a b b -> WrappedArrow a b a #

Functor (Const * m) 

Methods

fmap :: (a -> b) -> Const * m a -> Const * m b #

(<$) :: a -> Const * m b -> Const * m a #

Functor f => Functor (Alt * f) 

Methods

fmap :: (a -> b) -> Alt * f a -> Alt * f b #

(<$) :: a -> Alt * f b -> Alt * f a #

Functor m => Functor (ErrorT e m) 

Methods

fmap :: (a -> b) -> ErrorT e m a -> ErrorT e m b #

(<$) :: a -> ErrorT e m b -> ErrorT e m a #

Functor f => Functor (M1 i c f) 

Methods

fmap :: (a -> b) -> M1 i c f a -> M1 i c f b #

(<$) :: a -> M1 i c f b -> M1 i c f a #

class Functor f => Applicative f where #

A functor with application, providing operations to

  • embed pure expressions (pure), and
  • sequence computations and combine their results (<*>).

A minimal complete definition must include implementations of these + functions satisfying the following laws:

identity
pure id <*> v = v
composition
pure (.) <*> u <*> v <*> w = u <*> (v <*> w)
homomorphism
pure f <*> pure x = pure (f x)
interchange
u <*> pure y = pure ($ y) <*> u

The other methods have the following default definitions, which may + be overridden with equivalent specialized implementations:

As a consequence of these laws, the Functor instance for f will satisfy

If f is also a Monad, it should satisfy

(which implies that pure and <*> satisfy the applicative functor laws).

Minimal complete definition

pure, (<*>)

Instances

Applicative [] 

Methods

pure :: a -> [a] #

(<*>) :: [a -> b] -> [a] -> [b] #

(*>) :: [a] -> [b] -> [b] #

(<*) :: [a] -> [b] -> [a] #

Applicative Maybe 

Methods

pure :: a -> Maybe a #

(<*>) :: Maybe (a -> b) -> Maybe a -> Maybe b #

(*>) :: Maybe a -> Maybe b -> Maybe b #

(<*) :: Maybe a -> Maybe b -> Maybe a #

Applicative IO 

Methods

pure :: a -> IO a #

(<*>) :: IO (a -> b) -> IO a -> IO b #

(*>) :: IO a -> IO b -> IO b #

(<*) :: IO a -> IO b -> IO a #

Applicative U1 

Methods

pure :: a -> U1 a #

(<*>) :: U1 (a -> b) -> U1 a -> U1 b #

(*>) :: U1 a -> U1 b -> U1 b #

(<*) :: U1 a -> U1 b -> U1 a #

Applicative Par1 

Methods

pure :: a -> Par1 a #

(<*>) :: Par1 (a -> b) -> Par1 a -> Par1 b #

(*>) :: Par1 a -> Par1 b -> Par1 b #

(<*) :: Par1 a -> Par1 b -> Par1 a #

Applicative Q 

Methods

pure :: a -> Q a #

(<*>) :: Q (a -> b) -> Q a -> Q b #

(*>) :: Q a -> Q b -> Q b #

(<*) :: Q a -> Q b -> Q a #

Applicative Id 

Methods

pure :: a -> Id a #

(<*>) :: Id (a -> b) -> Id a -> Id b #

(*>) :: Id a -> Id b -> Id b #

(<*) :: Id a -> Id b -> Id a #

Applicative P 

Methods

pure :: a -> P a #

(<*>) :: P (a -> b) -> P a -> P b #

(*>) :: P a -> P b -> P b #

(<*) :: P a -> P b -> P a #

Applicative Identity 

Methods

pure :: a -> Identity a #

(<*>) :: Identity (a -> b) -> Identity a -> Identity b #

(*>) :: Identity a -> Identity b -> Identity b #

(<*) :: Identity a -> Identity b -> Identity a #

Applicative Min 

Methods

pure :: a -> Min a #

(<*>) :: Min (a -> b) -> Min a -> Min b #

(*>) :: Min a -> Min b -> Min b #

(<*) :: Min a -> Min b -> Min a #

Applicative Max 

Methods

pure :: a -> Max a #

(<*>) :: Max (a -> b) -> Max a -> Max b #

(*>) :: Max a -> Max b -> Max b #

(<*) :: Max a -> Max b -> Max a #

Applicative First 

Methods

pure :: a -> First a #

(<*>) :: First (a -> b) -> First a -> First b #

(*>) :: First a -> First b -> First b #

(<*) :: First a -> First b -> First a #

Applicative Last 

Methods

pure :: a -> Last a #

(<*>) :: Last (a -> b) -> Last a -> Last b #

(*>) :: Last a -> Last b -> Last b #

(<*) :: Last a -> Last b -> Last a #

Applicative Option 

Methods

pure :: a -> Option a #

(<*>) :: Option (a -> b) -> Option a -> Option b #

(*>) :: Option a -> Option b -> Option b #

(<*) :: Option a -> Option b -> Option a #

Applicative NonEmpty 

Methods

pure :: a -> NonEmpty a #

(<*>) :: NonEmpty (a -> b) -> NonEmpty a -> NonEmpty b #

(*>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

(<*) :: NonEmpty a -> NonEmpty b -> NonEmpty a #

Applicative Complex 

Methods

pure :: a -> Complex a #

(<*>) :: Complex (a -> b) -> Complex a -> Complex b #

(*>) :: Complex a -> Complex b -> Complex b #

(<*) :: Complex a -> Complex b -> Complex a #

Applicative ZipList 

Methods

pure :: a -> ZipList a #

(<*>) :: ZipList (a -> b) -> ZipList a -> ZipList b #

(*>) :: ZipList a -> ZipList b -> ZipList b #

(<*) :: ZipList a -> ZipList b -> ZipList a #

Applicative STM 

Methods

pure :: a -> STM a #

(<*>) :: STM (a -> b) -> STM a -> STM b #

(*>) :: STM a -> STM b -> STM b #

(<*) :: STM a -> STM b -> STM a #

Applicative Dual 

Methods

pure :: a -> Dual a #

(<*>) :: Dual (a -> b) -> Dual a -> Dual b #

(*>) :: Dual a -> Dual b -> Dual b #

(<*) :: Dual a -> Dual b -> Dual a #

Applicative Sum 

Methods

pure :: a -> Sum a #

(<*>) :: Sum (a -> b) -> Sum a -> Sum b #

(*>) :: Sum a -> Sum b -> Sum b #

(<*) :: Sum a -> Sum b -> Sum a #

Applicative Product 

Methods

pure :: a -> Product a #

(<*>) :: Product (a -> b) -> Product a -> Product b #

(*>) :: Product a -> Product b -> Product b #

(<*) :: Product a -> Product b -> Product a #

Applicative First 

Methods

pure :: a -> First a #

(<*>) :: First (a -> b) -> First a -> First b #

(*>) :: First a -> First b -> First b #

(<*) :: First a -> First b -> First a #

Applicative Last 

Methods

pure :: a -> Last a #

(<*>) :: Last (a -> b) -> Last a -> Last b #

(*>) :: Last a -> Last b -> Last b #

(<*) :: Last a -> Last b -> Last a #

Applicative ReadPrec 

Methods

pure :: a -> ReadPrec a #

(<*>) :: ReadPrec (a -> b) -> ReadPrec a -> ReadPrec b #

(*>) :: ReadPrec a -> ReadPrec b -> ReadPrec b #

(<*) :: ReadPrec a -> ReadPrec b -> ReadPrec a #

Applicative ReadP 

Methods

pure :: a -> ReadP a #

(<*>) :: ReadP (a -> b) -> ReadP a -> ReadP b #

(*>) :: ReadP a -> ReadP b -> ReadP b #

(<*) :: ReadP a -> ReadP b -> ReadP a #

Applicative Seq 

Methods

pure :: a -> Seq a #

(<*>) :: Seq (a -> b) -> Seq a -> Seq b #

(*>) :: Seq a -> Seq b -> Seq b #

(<*) :: Seq a -> Seq b -> Seq a #

Applicative ((->) a) 

Methods

pure :: a -> a -> a #

(<*>) :: (a -> a -> b) -> (a -> a) -> a -> b #

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

(<*) :: (a -> a) -> (a -> b) -> a -> a #

Applicative (Either e) 

Methods

pure :: a -> Either e a #

(<*>) :: Either e (a -> b) -> Either e a -> Either e b #

(*>) :: Either e a -> Either e b -> Either e b #

(<*) :: Either e a -> Either e b -> Either e a #

Applicative f => Applicative (Rec1 f) 

Methods

pure :: a -> Rec1 f a #

(<*>) :: Rec1 f (a -> b) -> Rec1 f a -> Rec1 f b #

(*>) :: Rec1 f a -> Rec1 f b -> Rec1 f b #

(<*) :: Rec1 f a -> Rec1 f b -> Rec1 f a #

Monoid a => Applicative ((,) a) 

Methods

pure :: a -> (a, a) #

(<*>) :: (a, a -> b) -> (a, a) -> (a, b) #

(*>) :: (a, a) -> (a, b) -> (a, b) #

(<*) :: (a, a) -> (a, b) -> (a, a) #

Applicative (StateL s) 

Methods

pure :: a -> StateL s a #

(<*>) :: StateL s (a -> b) -> StateL s a -> StateL s b #

(*>) :: StateL s a -> StateL s b -> StateL s b #

(<*) :: StateL s a -> StateL s b -> StateL s a #

Applicative (StateR s) 

Methods

pure :: a -> StateR s a #

(<*>) :: StateR s (a -> b) -> StateR s a -> StateR s b #

(*>) :: StateR s a -> StateR s b -> StateR s b #

(<*) :: StateR s a -> StateR s b -> StateR s a #

Monad m => Applicative (WrappedMonad m) 

Methods

pure :: a -> WrappedMonad m a #

(<*>) :: WrappedMonad m (a -> b) -> WrappedMonad m a -> WrappedMonad m b #

(*>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b #

(<*) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m a #

Arrow a => Applicative (ArrowMonad a) 

Methods

pure :: a -> ArrowMonad a a #

(<*>) :: ArrowMonad a (a -> b) -> ArrowMonad a a -> ArrowMonad a b #

(*>) :: ArrowMonad a a -> ArrowMonad a b -> ArrowMonad a b #

(<*) :: ArrowMonad a a -> ArrowMonad a b -> ArrowMonad a a #

Applicative (Proxy *) 

Methods

pure :: a -> Proxy * a #

(<*>) :: Proxy * (a -> b) -> Proxy * a -> Proxy * b #

(*>) :: Proxy * a -> Proxy * b -> Proxy * b #

(<*) :: Proxy * a -> Proxy * b -> Proxy * a #

Applicative (State s) 

Methods

pure :: a -> State s a #

(<*>) :: State s (a -> b) -> State s a -> State s b #

(*>) :: State s a -> State s b -> State s b #

(<*) :: State s a -> State s b -> State s a #

(Applicative f, Applicative g) => Applicative ((:*:) f g) 

Methods

pure :: a -> (f :*: g) a #

(<*>) :: (f :*: g) (a -> b) -> (f :*: g) a -> (f :*: g) b #

(*>) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) b #

(<*) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) a #

(Applicative f, Applicative g) => Applicative ((:.:) f g) 

Methods

pure :: a -> (f :.: g) a #

(<*>) :: (f :.: g) (a -> b) -> (f :.: g) a -> (f :.: g) b #

(*>) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) b #

(<*) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) a #

Arrow a => Applicative (WrappedArrow a b) 

Methods

pure :: a -> WrappedArrow a b a #

(<*>) :: WrappedArrow a b (a -> b) -> WrappedArrow a b a -> WrappedArrow a b b #

(*>) :: WrappedArrow a b a -> WrappedArrow a b b -> WrappedArrow a b b #

(<*) :: WrappedArrow a b a -> WrappedArrow a b b -> WrappedArrow a b a #

Monoid m => Applicative (Const * m) 

Methods

pure :: a -> Const * m a #

(<*>) :: Const * m (a -> b) -> Const * m a -> Const * m b #

(*>) :: Const * m a -> Const * m b -> Const * m b #

(<*) :: Const * m a -> Const * m b -> Const * m a #

Applicative f => Applicative (Alt * f) 

Methods

pure :: a -> Alt * f a #

(<*>) :: Alt * f (a -> b) -> Alt * f a -> Alt * f b #

(*>) :: Alt * f a -> Alt * f b -> Alt * f b #

(<*) :: Alt * f a -> Alt * f b -> Alt * f a #

(Functor m, Monad m) => Applicative (ErrorT e m) 

Methods

pure :: a -> ErrorT e m a #

(<*>) :: ErrorT e m (a -> b) -> ErrorT e m a -> ErrorT e m b #

(*>) :: ErrorT e m a -> ErrorT e m b -> ErrorT e m b #

(<*) :: ErrorT e m a -> ErrorT e m b -> ErrorT e m a #

Applicative f => Applicative (M1 i c f) 

Methods

pure :: a -> M1 i c f a #

(<*>) :: M1 i c f (a -> b) -> M1 i c f a -> M1 i c f b #

(*>) :: M1 i c f a -> M1 i c f b -> M1 i c f b #

(<*) :: M1 i c f a -> M1 i c f b -> M1 i c f a #

class Applicative f => Alternative f where #

A monoid on applicative functors.

If defined, some and many should be the least solutions + of the equations:

  • some v = (:) <$> v <*> many v
  • many v = some v <|> pure []

Minimal complete definition

empty, (<|>)

Instances

Alternative [] 

Methods

empty :: [a] #

(<|>) :: [a] -> [a] -> [a] #

some :: [a] -> [[a]] #

many :: [a] -> [[a]] #

Alternative Maybe 

Methods

empty :: Maybe a #

(<|>) :: Maybe a -> Maybe a -> Maybe a #

some :: Maybe a -> Maybe [a] #

many :: Maybe a -> Maybe [a] #

Alternative IO 

Methods

empty :: IO a #

(<|>) :: IO a -> IO a -> IO a #

some :: IO a -> IO [a] #

many :: IO a -> IO [a] #

Alternative U1 

Methods

empty :: U1 a #

(<|>) :: U1 a -> U1 a -> U1 a #

some :: U1 a -> U1 [a] #

many :: U1 a -> U1 [a] #

Alternative P 

Methods

empty :: P a #

(<|>) :: P a -> P a -> P a #

some :: P a -> P [a] #

many :: P a -> P [a] #

Alternative Option 

Methods

empty :: Option a #

(<|>) :: Option a -> Option a -> Option a #

some :: Option a -> Option [a] #

many :: Option a -> Option [a] #

Alternative STM 

Methods

empty :: STM a #

(<|>) :: STM a -> STM a -> STM a #

some :: STM a -> STM [a] #

many :: STM a -> STM [a] #

Alternative ReadPrec 

Methods

empty :: ReadPrec a #

(<|>) :: ReadPrec a -> ReadPrec a -> ReadPrec a #

some :: ReadPrec a -> ReadPrec [a] #

many :: ReadPrec a -> ReadPrec [a] #

Alternative ReadP 

Methods

empty :: ReadP a #

(<|>) :: ReadP a -> ReadP a -> ReadP a #

some :: ReadP a -> ReadP [a] #

many :: ReadP a -> ReadP [a] #

Alternative Seq 

Methods

empty :: Seq a #

(<|>) :: Seq a -> Seq a -> Seq a #

some :: Seq a -> Seq [a] #

many :: Seq a -> Seq [a] #

Alternative f => Alternative (Rec1 f) 

Methods

empty :: Rec1 f a #

(<|>) :: Rec1 f a -> Rec1 f a -> Rec1 f a #

some :: Rec1 f a -> Rec1 f [a] #

many :: Rec1 f a -> Rec1 f [a] #

MonadPlus m => Alternative (WrappedMonad m) 

Methods

empty :: WrappedMonad m a #

(<|>) :: WrappedMonad m a -> WrappedMonad m a -> WrappedMonad m a #

some :: WrappedMonad m a -> WrappedMonad m [a] #

many :: WrappedMonad m a -> WrappedMonad m [a] #

ArrowPlus a => Alternative (ArrowMonad a) 

Methods

empty :: ArrowMonad a a #

(<|>) :: ArrowMonad a a -> ArrowMonad a a -> ArrowMonad a a #

some :: ArrowMonad a a -> ArrowMonad a [a] #

many :: ArrowMonad a a -> ArrowMonad a [a] #

Alternative (Proxy *) 

Methods

empty :: Proxy * a #

(<|>) :: Proxy * a -> Proxy * a -> Proxy * a #

some :: Proxy * a -> Proxy * [a] #

many :: Proxy * a -> Proxy * [a] #

(Alternative f, Alternative g) => Alternative ((:*:) f g) 

Methods

empty :: (f :*: g) a #

(<|>) :: (f :*: g) a -> (f :*: g) a -> (f :*: g) a #

some :: (f :*: g) a -> (f :*: g) [a] #

many :: (f :*: g) a -> (f :*: g) [a] #

(Alternative f, Applicative g) => Alternative ((:.:) f g) 

Methods

empty :: (f :.: g) a #

(<|>) :: (f :.: g) a -> (f :.: g) a -> (f :.: g) a #

some :: (f :.: g) a -> (f :.: g) [a] #

many :: (f :.: g) a -> (f :.: g) [a] #

(ArrowZero a, ArrowPlus a) => Alternative (WrappedArrow a b) 

Methods

empty :: WrappedArrow a b a #

(<|>) :: WrappedArrow a b a -> WrappedArrow a b a -> WrappedArrow a b a #

some :: WrappedArrow a b a -> WrappedArrow a b [a] #

many :: WrappedArrow a b a -> WrappedArrow a b [a] #

Alternative f => Alternative (Alt * f) 

Methods

empty :: Alt * f a #

(<|>) :: Alt * f a -> Alt * f a -> Alt * f a #

some :: Alt * f a -> Alt * f [a] #

many :: Alt * f a -> Alt * f [a] #

(Functor m, Monad m, Error e) => Alternative (ErrorT e m) 

Methods

empty :: ErrorT e m a #

(<|>) :: ErrorT e m a -> ErrorT e m a -> ErrorT e m a #

some :: ErrorT e m a -> ErrorT e m [a] #

many :: ErrorT e m a -> ErrorT e m [a] #

Alternative f => Alternative (M1 i c f) 

Methods

empty :: M1 i c f a #

(<|>) :: M1 i c f a -> M1 i c f a -> M1 i c f a #

some :: M1 i c f a -> M1 i c f [a] #

many :: M1 i c f a -> M1 i c f [a] #

class Applicative m => Monad m where #

The Monad class defines the basic operations over a monad, +a concept from a branch of mathematics known as category theory. +From the perspective of a Haskell programmer, however, it is best to +think of a monad as an abstract datatype of actions. +Haskell's do expressions provide a convenient syntax for writing +monadic expressions.

Instances of Monad should satisfy the following laws:

Furthermore, the Monad and Applicative operations should relate as follows:

The above laws imply:

and that pure and (<*>) satisfy the applicative functor laws.

The instances of Monad for lists, Maybe and IO +defined in the Prelude satisfy these laws.

Minimal complete definition

(>>=)

Instances

Monad [] 

Methods

(>>=) :: [a] -> (a -> [b]) -> [b] #

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

return :: a -> [a] #

fail :: String -> [a] #

Monad Maybe 

Methods

(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b #

(>>) :: Maybe a -> Maybe b -> Maybe b #

return :: a -> Maybe a #

fail :: String -> Maybe a #

Monad IO 

Methods

(>>=) :: IO a -> (a -> IO b) -> IO b #

(>>) :: IO a -> IO b -> IO b #

return :: a -> IO a #

fail :: String -> IO a #

Monad U1 

Methods

(>>=) :: U1 a -> (a -> U1 b) -> U1 b #

(>>) :: U1 a -> U1 b -> U1 b #

return :: a -> U1 a #

fail :: String -> U1 a #

Monad Par1 

Methods

(>>=) :: Par1 a -> (a -> Par1 b) -> Par1 b #

(>>) :: Par1 a -> Par1 b -> Par1 b #

return :: a -> Par1 a #

fail :: String -> Par1 a #

Monad Q 

Methods

(>>=) :: Q a -> (a -> Q b) -> Q b #

(>>) :: Q a -> Q b -> Q b #

return :: a -> Q a #

fail :: String -> Q a #

Monad P 

Methods

(>>=) :: P a -> (a -> P b) -> P b #

(>>) :: P a -> P b -> P b #

return :: a -> P a #

fail :: String -> P a #

Monad Identity 

Methods

(>>=) :: Identity a -> (a -> Identity b) -> Identity b #

(>>) :: Identity a -> Identity b -> Identity b #

return :: a -> Identity a #

fail :: String -> Identity a #

Monad Min 

Methods

(>>=) :: Min a -> (a -> Min b) -> Min b #

(>>) :: Min a -> Min b -> Min b #

return :: a -> Min a #

fail :: String -> Min a #

Monad Max 

Methods

(>>=) :: Max a -> (a -> Max b) -> Max b #

(>>) :: Max a -> Max b -> Max b #

return :: a -> Max a #

fail :: String -> Max a #

Monad First 

Methods

(>>=) :: First a -> (a -> First b) -> First b #

(>>) :: First a -> First b -> First b #

return :: a -> First a #

fail :: String -> First a #

Monad Last 

Methods

(>>=) :: Last a -> (a -> Last b) -> Last b #

(>>) :: Last a -> Last b -> Last b #

return :: a -> Last a #

fail :: String -> Last a #

Monad Option 

Methods

(>>=) :: Option a -> (a -> Option b) -> Option b #

(>>) :: Option a -> Option b -> Option b #

return :: a -> Option a #

fail :: String -> Option a #

Monad NonEmpty 

Methods

(>>=) :: NonEmpty a -> (a -> NonEmpty b) -> NonEmpty b #

(>>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

return :: a -> NonEmpty a #

fail :: String -> NonEmpty a #

Monad Complex 

Methods

(>>=) :: Complex a -> (a -> Complex b) -> Complex b #

(>>) :: Complex a -> Complex b -> Complex b #

return :: a -> Complex a #

fail :: String -> Complex a #

Monad STM 

Methods

(>>=) :: STM a -> (a -> STM b) -> STM b #

(>>) :: STM a -> STM b -> STM b #

return :: a -> STM a #

fail :: String -> STM a #

Monad Dual 

Methods

(>>=) :: Dual a -> (a -> Dual b) -> Dual b #

(>>) :: Dual a -> Dual b -> Dual b #

return :: a -> Dual a #

fail :: String -> Dual a #

Monad Sum 

Methods

(>>=) :: Sum a -> (a -> Sum b) -> Sum b #

(>>) :: Sum a -> Sum b -> Sum b #

return :: a -> Sum a #

fail :: String -> Sum a #

Monad Product 

Methods

(>>=) :: Product a -> (a -> Product b) -> Product b #

(>>) :: Product a -> Product b -> Product b #

return :: a -> Product a #

fail :: String -> Product a #

Monad First 

Methods

(>>=) :: First a -> (a -> First b) -> First b #

(>>) :: First a -> First b -> First b #

return :: a -> First a #

fail :: String -> First a #

Monad Last 

Methods

(>>=) :: Last a -> (a -> Last b) -> Last b #

(>>) :: Last a -> Last b -> Last b #

return :: a -> Last a #

fail :: String -> Last a #

Monad ReadPrec 

Methods

(>>=) :: ReadPrec a -> (a -> ReadPrec b) -> ReadPrec b #

(>>) :: ReadPrec a -> ReadPrec b -> ReadPrec b #

return :: a -> ReadPrec a #

fail :: String -> ReadPrec a #

Monad ReadP 

Methods

(>>=) :: ReadP a -> (a -> ReadP b) -> ReadP b #

(>>) :: ReadP a -> ReadP b -> ReadP b #

return :: a -> ReadP a #

fail :: String -> ReadP a #

Monad Seq 

Methods

(>>=) :: Seq a -> (a -> Seq b) -> Seq b #

(>>) :: Seq a -> Seq b -> Seq b #

return :: a -> Seq a #

fail :: String -> Seq a #

Monad ((->) r) 

Methods

(>>=) :: (r -> a) -> (a -> r -> b) -> r -> b #

(>>) :: (r -> a) -> (r -> b) -> r -> b #

return :: a -> r -> a #

fail :: String -> r -> a #

Monad (Either e) 

Methods

(>>=) :: Either e a -> (a -> Either e b) -> Either e b #

(>>) :: Either e a -> Either e b -> Either e b #

return :: a -> Either e a #

fail :: String -> Either e a #

Monad f => Monad (Rec1 f) 

Methods

(>>=) :: Rec1 f a -> (a -> Rec1 f b) -> Rec1 f b #

(>>) :: Rec1 f a -> Rec1 f b -> Rec1 f b #

return :: a -> Rec1 f a #

fail :: String -> Rec1 f a #

Monoid a => Monad ((,) a) 

Methods

(>>=) :: (a, a) -> (a -> (a, b)) -> (a, b) #

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

return :: a -> (a, a) #

fail :: String -> (a, a) #

Monad m => Monad (WrappedMonad m) 

Methods

(>>=) :: WrappedMonad m a -> (a -> WrappedMonad m b) -> WrappedMonad m b #

(>>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b #

return :: a -> WrappedMonad m a #

fail :: String -> WrappedMonad m a #

ArrowApply a => Monad (ArrowMonad a) 

Methods

(>>=) :: ArrowMonad a a -> (a -> ArrowMonad a b) -> ArrowMonad a b #

(>>) :: ArrowMonad a a -> ArrowMonad a b -> ArrowMonad a b #

return :: a -> ArrowMonad a a #

fail :: String -> ArrowMonad a a #

Monad (Proxy *) 

Methods

(>>=) :: Proxy * a -> (a -> Proxy * b) -> Proxy * b #

(>>) :: Proxy * a -> Proxy * b -> Proxy * b #

return :: a -> Proxy * a #

fail :: String -> Proxy * a #

Monad (State s) 

Methods

(>>=) :: State s a -> (a -> State s b) -> State s b #

(>>) :: State s a -> State s b -> State s b #

return :: a -> State s a #

fail :: String -> State s a #

(Monad f, Monad g) => Monad ((:*:) f g) 

Methods

(>>=) :: (f :*: g) a -> (a -> (f :*: g) b) -> (f :*: g) b #

(>>) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) b #

return :: a -> (f :*: g) a #

fail :: String -> (f :*: g) a #

Monad f => Monad (Alt * f) 

Methods

(>>=) :: Alt * f a -> (a -> Alt * f b) -> Alt * f b #

(>>) :: Alt * f a -> Alt * f b -> Alt * f b #

return :: a -> Alt * f a #

fail :: String -> Alt * f a #

(Monad m, Error e) => Monad (ErrorT e m) 

Methods

(>>=) :: ErrorT e m a -> (a -> ErrorT e m b) -> ErrorT e m b #

(>>) :: ErrorT e m a -> ErrorT e m b -> ErrorT e m b #

return :: a -> ErrorT e m a #

fail :: String -> ErrorT e m a #

Monad f => Monad (M1 i c f) 

Methods

(>>=) :: M1 i c f a -> (a -> M1 i c f b) -> M1 i c f b #

(>>) :: M1 i c f a -> M1 i c f b -> M1 i c f b #

return :: a -> M1 i c f a #

fail :: String -> M1 i c f a #

class Monad m => MonadIO m where #

Monads in which IO computations may be embedded. + Any monad built by applying a sequence of monad transformers to the + IO monad will be an instance of this class.

Instances should satisfy the following laws, which state that liftIO + is a transformer of monads:

Instances

MonadIO IO 

Methods

liftIO :: IO a -> IO a #

(Error e, MonadIO m) => MonadIO (ErrorT e m) 

Methods

liftIO :: IO a -> ErrorT e m a #

class MonadTrans t where #

The class of monad transformers. Instances should satisfy the + following laws, which state that lift is a monad transformation:

Instances

MonadTrans (ErrorT e) 

Methods

lift :: Monad m => m a -> ErrorT e m a #

class Monad m => MonadReader r m | m -> r where #

See examples in Control.Monad.Reader. + Note, the partially applied function type (->) r is a simple reader monad. + See the instance declaration below.

Minimal complete definition

(ask | reader), local

Instances

MonadReader r m => MonadReader r (MaybeT m) 

Methods

ask :: MaybeT m r #

local :: (r -> r) -> MaybeT m a -> MaybeT m a #

reader :: (r -> a) -> MaybeT m a #

MonadReader r m => MonadReader r (ListT m) 

Methods

ask :: ListT m r #

local :: (r -> r) -> ListT m a -> ListT m a #

reader :: (r -> a) -> ListT m a #

MonadReader r ((->) r) 

Methods

ask :: r -> r #

local :: (r -> r) -> (r -> a) -> r -> a #

reader :: (r -> a) -> r -> a #

(Monoid w, MonadReader r m) => MonadReader r (WriterT w m) 

Methods

ask :: WriterT w m r #

local :: (r -> r) -> WriterT w m a -> WriterT w m a #

reader :: (r -> a) -> WriterT w m a #

(Monoid w, MonadReader r m) => MonadReader r (WriterT w m) 

Methods

ask :: WriterT w m r #

local :: (r -> r) -> WriterT w m a -> WriterT w m a #

reader :: (r -> a) -> WriterT w m a #

MonadReader r m => MonadReader r (StateT s m) 

Methods

ask :: StateT s m r #

local :: (r -> r) -> StateT s m a -> StateT s m a #

reader :: (r -> a) -> StateT s m a #

MonadReader r m => MonadReader r (StateT s m) 

Methods

ask :: StateT s m r #

local :: (r -> r) -> StateT s m a -> StateT s m a #

reader :: (r -> a) -> StateT s m a #

MonadReader r m => MonadReader r (IdentityT * m) 

Methods

ask :: IdentityT * m r #

local :: (r -> r) -> IdentityT * m a -> IdentityT * m a #

reader :: (r -> a) -> IdentityT * m a #

MonadReader r m => MonadReader r (ExceptT e m) 

Methods

ask :: ExceptT e m r #

local :: (r -> r) -> ExceptT e m a -> ExceptT e m a #

reader :: (r -> a) -> ExceptT e m a #

(Error e, MonadReader r m) => MonadReader r (ErrorT e m) 

Methods

ask :: ErrorT e m r #

local :: (r -> r) -> ErrorT e m a -> ErrorT e m a #

reader :: (r -> a) -> ErrorT e m a #

Monad m => MonadReader r (ReaderT * r m) 

Methods

ask :: ReaderT * r m r #

local :: (r -> r) -> ReaderT * r m a -> ReaderT * r m a #

reader :: (r -> a) -> ReaderT * r m a #

MonadReader r' m => MonadReader r' (ContT * r m) 

Methods

ask :: ContT * r m r' #

local :: (r' -> r') -> ContT * r m a -> ContT * r m a #

reader :: (r' -> a) -> ContT * r m a #

(Monad m, Monoid w) => MonadReader r (RWST r w s m) 

Methods

ask :: RWST r w s m r #

local :: (r -> r) -> RWST r w s m a -> RWST r w s m a #

reader :: (r -> a) -> RWST r w s m a #

(Monad m, Monoid w) => MonadReader r (RWST r w s m) 

Methods

ask :: RWST r w s m r #

local :: (r -> r) -> RWST r w s m a -> RWST r w s m a #

reader :: (r -> a) -> RWST r w s m a #

class Monad m => MonadThrow m #

A class for monads in which exceptions may be thrown.

Instances should obey the following law:

throwM e >> x = throwM e

In other words, throwing an exception short-circuits the rest of the monadic + computation.

Minimal complete definition

throwM

Instances

MonadThrow [] 

Methods

throwM :: Exception e => e -> [a] #

MonadThrow Maybe 

Methods

throwM :: Exception e => e -> Maybe a #

MonadThrow IO 

Methods

throwM :: Exception e => e -> IO a #

MonadThrow Q 

Methods

throwM :: Exception e => e -> Q a #

MonadThrow STM 

Methods

throwM :: Exception e => e -> STM a #

(~) * e SomeException => MonadThrow (Either e) 

Methods

throwM :: Exception e => e -> Either e a #

MonadThrow m => MonadThrow (ListT m) 

Methods

throwM :: Exception e => e -> ListT m a #

MonadThrow m => MonadThrow (MaybeT m)

Throws exceptions into the base monad.

Methods

throwM :: Exception e => e -> MaybeT m a #

MonadThrow m => MonadThrow (ExceptT e m)

Throws exceptions into the base monad.

Methods

throwM :: Exception e => e -> ExceptT e m a #

(Error e, MonadThrow m) => MonadThrow (ErrorT e m)

Throws exceptions into the base monad.

Methods

throwM :: Exception e => e -> ErrorT e m a #

MonadThrow m => MonadThrow (StateT s m) 

Methods

throwM :: Exception e => e -> StateT s m a #

MonadThrow m => MonadThrow (StateT s m) 

Methods

throwM :: Exception e => e -> StateT s m a #

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 

Methods

throwM :: Exception e => e -> WriterT w m a #

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 

Methods

throwM :: Exception e => e -> WriterT w m a #

MonadThrow m => MonadThrow (IdentityT * m) 

Methods

throwM :: Exception e => e -> IdentityT * m a #

MonadThrow m => MonadThrow (ContT * r m) 

Methods

throwM :: Exception e => e -> ContT * r m a #

MonadThrow m => MonadThrow (ReaderT * r m) 

Methods

throwM :: Exception e => e -> ReaderT * r m a #

(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 

Methods

throwM :: Exception e => e -> RWST r w s m a #

(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 

Methods

throwM :: Exception e => e -> RWST r w s m a #

class (Typeable * e, Show e) => Exception e where #

Any type that you wish to throw or catch as an exception must be an +instance of the Exception class. The simplest case is a new exception +type directly below the root:

data MyException = ThisException | ThatException
+    deriving (Show, Typeable)
+
+instance Exception MyException

The default method definitions in the Exception class do what we need +in this case. You can now throw and catch ThisException and +ThatException as exceptions:

*Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException))
+Caught ThisException
+

In more complicated examples, you may wish to define a whole hierarchy +of exceptions:

---------------------------------------------------------------------
+-- Make the root exception type for all the exceptions in a compiler
+
+data SomeCompilerException = forall e . Exception e => SomeCompilerException e
+    deriving Typeable
+
+instance Show SomeCompilerException where
+    show (SomeCompilerException e) = show e
+
+instance Exception SomeCompilerException
+
+compilerExceptionToException :: Exception e => e -> SomeException
+compilerExceptionToException = toException . SomeCompilerException
+
+compilerExceptionFromException :: Exception e => SomeException -> Maybe e
+compilerExceptionFromException x = do
+    SomeCompilerException a <- fromException x
+    cast a
+
+---------------------------------------------------------------------
+-- Make a subhierarchy for exceptions in the frontend of the compiler
+
+data SomeFrontendException = forall e . Exception e => SomeFrontendException e
+    deriving Typeable
+
+instance Show SomeFrontendException where
+    show (SomeFrontendException e) = show e
+
+instance Exception SomeFrontendException where
+    toException = compilerExceptionToException
+    fromException = compilerExceptionFromException
+
+frontendExceptionToException :: Exception e => e -> SomeException
+frontendExceptionToException = toException . SomeFrontendException
+
+frontendExceptionFromException :: Exception e => SomeException -> Maybe e
+frontendExceptionFromException x = do
+    SomeFrontendException a <- fromException x
+    cast a
+
+---------------------------------------------------------------------
+-- Make an exception type for a particular frontend compiler exception
+
+data MismatchedParentheses = MismatchedParentheses
+    deriving (Typeable, Show)
+
+instance Exception MismatchedParentheses where
+    toException   = frontendExceptionToException
+    fromException = frontendExceptionFromException

We can now catch a MismatchedParentheses exception as +MismatchedParentheses, SomeFrontendException or +SomeCompilerException, but not other types, e.g. IOException:

*Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses))
+Caught MismatchedParentheses
+*Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException))
+Caught MismatchedParentheses
+*Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException))
+Caught MismatchedParentheses
+*Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: IOException))
+*** Exception: MismatchedParentheses
+

Minimal complete definition

Nothing

Instances

Exception Void 
Exception BlockedIndefinitelyOnMVar 
Exception BlockedIndefinitelyOnSTM 
Exception Deadlock 
Exception AllocationLimitExceeded 
Exception AssertionFailed 
Exception SomeAsyncException 
Exception AsyncException 
Exception ArrayException 
Exception ExitCode 
Exception IOException 
Exception ErrorCall 
Exception ArithException 
Exception SomeException 
Exception SyncExceptionWrapper 
Exception AsyncExceptionWrapper 
Exception UnicodeException 

class MonadThrow m => MonadCatch m #

A class for monads which allow exceptions to be caught, in particular + exceptions which were thrown by throwM.

Instances should obey the following law:

catch (throwM e) f = f e

Note that the ability to catch an exception does not guarantee that we can + deal with all possible exit points from a computation. Some monads, such as + continuation-based stacks, allow for more than just a success/failure + strategy, and therefore catch cannot be used by those monads to properly + implement a function such as finally. For more information, see + MonadMask.

Minimal complete definition

catch

Instances

MonadCatch IO 

Methods

catch :: Exception e => IO a -> (e -> IO a) -> IO a #

MonadCatch STM 

Methods

catch :: Exception e => STM a -> (e -> STM a) -> STM a #

(~) * e SomeException => MonadCatch (Either e)

Since: 0.8.3

Methods

catch :: Exception e => Either e a -> (e -> Either e a) -> Either e a #

MonadCatch m => MonadCatch (ListT m) 

Methods

catch :: Exception e => ListT m a -> (e -> ListT m a) -> ListT m a #

MonadCatch m => MonadCatch (MaybeT m)

Catches exceptions from the base monad.

Methods

catch :: Exception e => MaybeT m a -> (e -> MaybeT m a) -> MaybeT m a #

MonadCatch m => MonadCatch (ExceptT e m)

Catches exceptions from the base monad.

Methods

catch :: Exception e => ExceptT e m a -> (e -> ExceptT e m a) -> ExceptT e m a #

(Error e, MonadCatch m) => MonadCatch (ErrorT e m)

Catches exceptions from the base monad.

Methods

catch :: Exception e => ErrorT e m a -> (e -> ErrorT e m a) -> ErrorT e m a #

MonadCatch m => MonadCatch (StateT s m) 

Methods

catch :: Exception e => StateT s m a -> (e -> StateT s m a) -> StateT s m a #

MonadCatch m => MonadCatch (StateT s m) 

Methods

catch :: Exception e => StateT s m a -> (e -> StateT s m a) -> StateT s m a #

(MonadCatch m, Monoid w) => MonadCatch (WriterT w m) 

Methods

catch :: Exception e => WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a #

(MonadCatch m, Monoid w) => MonadCatch (WriterT w m) 

Methods

catch :: Exception e => WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a #

MonadCatch m => MonadCatch (IdentityT * m) 

Methods

catch :: Exception e => IdentityT * m a -> (e -> IdentityT * m a) -> IdentityT * m a #

MonadCatch m => MonadCatch (ReaderT * r m) 

Methods

catch :: Exception e => ReaderT * r m a -> (e -> ReaderT * r m a) -> ReaderT * r m a #

(MonadCatch m, Monoid w) => MonadCatch (RWST r w s m) 

Methods

catch :: Exception e => RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a #

(MonadCatch m, Monoid w) => MonadCatch (RWST r w s m) 

Methods

catch :: Exception e => RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a #

class MonadCatch m => MonadMask m #

A class for monads which provide for the ability to account for all + possible exit points from a computation, and to mask asynchronous + exceptions. Continuation-based monads, and stacks such as ErrorT e IO + which provide for multiple failure modes, are invalid instances of this + class.

Note that this package does provide a MonadMask instance for CatchT. + This instance is only valid if the base monad provides no ability to + provide multiple exit. For example, IO or Either would be invalid base + monads, but Reader or State would be acceptable.

Instances should ensure that, in the following code:

f `finally` g

The action g is called regardless of what occurs within f, including + async exceptions.

Minimal complete definition

mask, uninterruptibleMask

Instances

MonadMask IO 

Methods

mask :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

uninterruptibleMask :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

(~) * e SomeException => MonadMask (Either e)

Since: 0.8.3

Methods

mask :: ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b #

uninterruptibleMask :: ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b #

MonadMask m => MonadMask (StateT s m) 

Methods

mask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

uninterruptibleMask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

MonadMask m => MonadMask (StateT s m) 

Methods

mask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

uninterruptibleMask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

(MonadMask m, Monoid w) => MonadMask (WriterT w m) 

Methods

mask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

uninterruptibleMask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

(MonadMask m, Monoid w) => MonadMask (WriterT w m) 

Methods

mask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

uninterruptibleMask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

MonadMask m => MonadMask (IdentityT * m) 

Methods

mask :: ((forall a. IdentityT * m a -> IdentityT * m a) -> IdentityT * m b) -> IdentityT * m b #

uninterruptibleMask :: ((forall a. IdentityT * m a -> IdentityT * m a) -> IdentityT * m b) -> IdentityT * m b #

MonadMask m => MonadMask (ReaderT * r m) 

Methods

mask :: ((forall a. ReaderT * r m a -> ReaderT * r m a) -> ReaderT * r m b) -> ReaderT * r m b #

uninterruptibleMask :: ((forall a. ReaderT * r m a -> ReaderT * r m a) -> ReaderT * r m b) -> ReaderT * r m b #

(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 

Methods

mask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

uninterruptibleMask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 

Methods

mask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

uninterruptibleMask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

class Foldable t where #

Data structures that can be folded.

For example, given a data type

data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)

a suitable instance would be

instance Foldable Tree where
+   foldMap f Empty = mempty
+   foldMap f (Leaf x) = f x
+   foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend` foldMap f r

This is suitable even for abstract types, as the monoid is assumed + to satisfy the monoid laws. Alternatively, one could define foldr:

instance Foldable Tree where
+   foldr f z Empty = z
+   foldr f z (Leaf x) = f x z
+   foldr f z (Node l k r) = foldr f (f k (foldr f z r)) l

Foldable instances are expected to satisfy the following laws:

foldr f z t = appEndo (foldMap (Endo . f) t ) z
foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z
fold = foldMap id

sum, product, maximum, and minimum should all be essentially + equivalent to foldMap forms, such as

sum = getSum . foldMap Sum

but may be less defined.

If the type is also a Functor instance, it should satisfy

foldMap f = fold . fmap f

which implies that

foldMap f . fmap g = foldMap (f . g)

Minimal complete definition

foldMap | foldr

Instances

Foldable [] 

Methods

fold :: Monoid m => [m] -> m #

foldMap :: Monoid m => (a -> m) -> [a] -> m #

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

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

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

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

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

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

toList :: [a] -> [a] #

null :: [a] -> Bool #

length :: [a] -> Int #

elem :: Eq a => a -> [a] -> Bool #

maximum :: Ord a => [a] -> a #

minimum :: Ord a => [a] -> a #

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

product :: Num a => [a] -> a #

Foldable Maybe 

Methods

fold :: Monoid m => Maybe m -> m #

foldMap :: Monoid m => (a -> m) -> Maybe a -> m #

foldr :: (a -> b -> b) -> b -> Maybe a -> b #

foldr' :: (a -> b -> b) -> b -> Maybe a -> b #

foldl :: (b -> a -> b) -> b -> Maybe a -> b #

foldl' :: (b -> a -> b) -> b -> Maybe a -> b #

foldr1 :: (a -> a -> a) -> Maybe a -> a #

foldl1 :: (a -> a -> a) -> Maybe a -> a #

toList :: Maybe a -> [a] #

null :: Maybe a -> Bool #

length :: Maybe a -> Int #

elem :: Eq a => a -> Maybe a -> Bool #

maximum :: Ord a => Maybe a -> a #

minimum :: Ord a => Maybe a -> a #

sum :: Num a => Maybe a -> a #

product :: Num a => Maybe a -> a #

Foldable V1 

Methods

fold :: Monoid m => V1 m -> m #

foldMap :: Monoid m => (a -> m) -> V1 a -> m #

foldr :: (a -> b -> b) -> b -> V1 a -> b #

foldr' :: (a -> b -> b) -> b -> V1 a -> b #

foldl :: (b -> a -> b) -> b -> V1 a -> b #

foldl' :: (b -> a -> b) -> b -> V1 a -> b #

foldr1 :: (a -> a -> a) -> V1 a -> a #

foldl1 :: (a -> a -> a) -> V1 a -> a #

toList :: V1 a -> [a] #

null :: V1 a -> Bool #

length :: V1 a -> Int #

elem :: Eq a => a -> V1 a -> Bool #

maximum :: Ord a => V1 a -> a #

minimum :: Ord a => V1 a -> a #

sum :: Num a => V1 a -> a #

product :: Num a => V1 a -> a #

Foldable U1 

Methods

fold :: Monoid m => U1 m -> m #

foldMap :: Monoid m => (a -> m) -> U1 a -> m #

foldr :: (a -> b -> b) -> b -> U1 a -> b #

foldr' :: (a -> b -> b) -> b -> U1 a -> b #

foldl :: (b -> a -> b) -> b -> U1 a -> b #

foldl' :: (b -> a -> b) -> b -> U1 a -> b #

foldr1 :: (a -> a -> a) -> U1 a -> a #

foldl1 :: (a -> a -> a) -> U1 a -> a #

toList :: U1 a -> [a] #

null :: U1 a -> Bool #

length :: U1 a -> Int #

elem :: Eq a => a -> U1 a -> Bool #

maximum :: Ord a => U1 a -> a #

minimum :: Ord a => U1 a -> a #

sum :: Num a => U1 a -> a #

product :: Num a => U1 a -> a #

Foldable Par1 

Methods

fold :: Monoid m => Par1 m -> m #

foldMap :: Monoid m => (a -> m) -> Par1 a -> m #

foldr :: (a -> b -> b) -> b -> Par1 a -> b #

foldr' :: (a -> b -> b) -> b -> Par1 a -> b #

foldl :: (b -> a -> b) -> b -> Par1 a -> b #

foldl' :: (b -> a -> b) -> b -> Par1 a -> b #

foldr1 :: (a -> a -> a) -> Par1 a -> a #

foldl1 :: (a -> a -> a) -> Par1 a -> a #

toList :: Par1 a -> [a] #

null :: Par1 a -> Bool #

length :: Par1 a -> Int #

elem :: Eq a => a -> Par1 a -> Bool #

maximum :: Ord a => Par1 a -> a #

minimum :: Ord a => Par1 a -> a #

sum :: Num a => Par1 a -> a #

product :: Num a => Par1 a -> a #

Foldable Identity 

Methods

fold :: Monoid m => Identity m -> m #

foldMap :: Monoid m => (a -> m) -> Identity a -> m #

foldr :: (a -> b -> b) -> b -> Identity a -> b #

foldr' :: (a -> b -> b) -> b -> Identity a -> b #

foldl :: (b -> a -> b) -> b -> Identity a -> b #

foldl' :: (b -> a -> b) -> b -> Identity a -> b #

foldr1 :: (a -> a -> a) -> Identity a -> a #

foldl1 :: (a -> a -> a) -> Identity a -> a #

toList :: Identity a -> [a] #

null :: Identity a -> Bool #

length :: Identity a -> Int #

elem :: Eq a => a -> Identity a -> Bool #

maximum :: Ord a => Identity a -> a #

minimum :: Ord a => Identity a -> a #

sum :: Num a => Identity a -> a #

product :: Num a => Identity a -> a #

Foldable Min 

Methods

fold :: Monoid m => Min m -> m #

foldMap :: Monoid m => (a -> m) -> Min a -> m #

foldr :: (a -> b -> b) -> b -> Min a -> b #

foldr' :: (a -> b -> b) -> b -> Min a -> b #

foldl :: (b -> a -> b) -> b -> Min a -> b #

foldl' :: (b -> a -> b) -> b -> Min a -> b #

foldr1 :: (a -> a -> a) -> Min a -> a #

foldl1 :: (a -> a -> a) -> Min a -> a #

toList :: Min a -> [a] #

null :: Min a -> Bool #

length :: Min a -> Int #

elem :: Eq a => a -> Min a -> Bool #

maximum :: Ord a => Min a -> a #

minimum :: Ord a => Min a -> a #

sum :: Num a => Min a -> a #

product :: Num a => Min a -> a #

Foldable Max 

Methods

fold :: Monoid m => Max m -> m #

foldMap :: Monoid m => (a -> m) -> Max a -> m #

foldr :: (a -> b -> b) -> b -> Max a -> b #

foldr' :: (a -> b -> b) -> b -> Max a -> b #

foldl :: (b -> a -> b) -> b -> Max a -> b #

foldl' :: (b -> a -> b) -> b -> Max a -> b #

foldr1 :: (a -> a -> a) -> Max a -> a #

foldl1 :: (a -> a -> a) -> Max a -> a #

toList :: Max a -> [a] #

null :: Max a -> Bool #

length :: Max a -> Int #

elem :: Eq a => a -> Max a -> Bool #

maximum :: Ord a => Max a -> a #

minimum :: Ord a => Max a -> a #

sum :: Num a => Max a -> a #

product :: Num a => Max a -> a #

Foldable First 

Methods

fold :: Monoid m => First m -> m #

foldMap :: Monoid m => (a -> m) -> First a -> m #

foldr :: (a -> b -> b) -> b -> First a -> b #

foldr' :: (a -> b -> b) -> b -> First a -> b #

foldl :: (b -> a -> b) -> b -> First a -> b #

foldl' :: (b -> a -> b) -> b -> First a -> b #

foldr1 :: (a -> a -> a) -> First a -> a #

foldl1 :: (a -> a -> a) -> First a -> a #

toList :: First a -> [a] #

null :: First a -> Bool #

length :: First a -> Int #

elem :: Eq a => a -> First a -> Bool #

maximum :: Ord a => First a -> a #

minimum :: Ord a => First a -> a #

sum :: Num a => First a -> a #

product :: Num a => First a -> a #

Foldable Last 

Methods

fold :: Monoid m => Last m -> m #

foldMap :: Monoid m => (a -> m) -> Last a -> m #

foldr :: (a -> b -> b) -> b -> Last a -> b #

foldr' :: (a -> b -> b) -> b -> Last a -> b #

foldl :: (b -> a -> b) -> b -> Last a -> b #

foldl' :: (b -> a -> b) -> b -> Last a -> b #

foldr1 :: (a -> a -> a) -> Last a -> a #

foldl1 :: (a -> a -> a) -> Last a -> a #

toList :: Last a -> [a] #

null :: Last a -> Bool #

length :: Last a -> Int #

elem :: Eq a => a -> Last a -> Bool #

maximum :: Ord a => Last a -> a #

minimum :: Ord a => Last a -> a #

sum :: Num a => Last a -> a #

product :: Num a => Last a -> a #

Foldable Option 

Methods

fold :: Monoid m => Option m -> m #

foldMap :: Monoid m => (a -> m) -> Option a -> m #

foldr :: (a -> b -> b) -> b -> Option a -> b #

foldr' :: (a -> b -> b) -> b -> Option a -> b #

foldl :: (b -> a -> b) -> b -> Option a -> b #

foldl' :: (b -> a -> b) -> b -> Option a -> b #

foldr1 :: (a -> a -> a) -> Option a -> a #

foldl1 :: (a -> a -> a) -> Option a -> a #

toList :: Option a -> [a] #

null :: Option a -> Bool #

length :: Option a -> Int #

elem :: Eq a => a -> Option a -> Bool #

maximum :: Ord a => Option a -> a #

minimum :: Ord a => Option a -> a #

sum :: Num a => Option a -> a #

product :: Num a => Option a -> a #

Foldable NonEmpty 

Methods

fold :: Monoid m => NonEmpty m -> m #

foldMap :: Monoid m => (a -> m) -> NonEmpty a -> m #

foldr :: (a -> b -> b) -> b -> NonEmpty a -> b #

foldr' :: (a -> b -> b) -> b -> NonEmpty a -> b #

foldl :: (b -> a -> b) -> b -> NonEmpty a -> b #

foldl' :: (b -> a -> b) -> b -> NonEmpty a -> b #

foldr1 :: (a -> a -> a) -> NonEmpty a -> a #

foldl1 :: (a -> a -> a) -> NonEmpty a -> a #

toList :: NonEmpty a -> [a] #

null :: NonEmpty a -> Bool #

length :: NonEmpty a -> Int #

elem :: Eq a => a -> NonEmpty a -> Bool #

maximum :: Ord a => NonEmpty a -> a #

minimum :: Ord a => NonEmpty a -> a #

sum :: Num a => NonEmpty a -> a #

product :: Num a => NonEmpty a -> a #

Foldable Complex 

Methods

fold :: Monoid m => Complex m -> m #

foldMap :: Monoid m => (a -> m) -> Complex a -> m #

foldr :: (a -> b -> b) -> b -> Complex a -> b #

foldr' :: (a -> b -> b) -> b -> Complex a -> b #

foldl :: (b -> a -> b) -> b -> Complex a -> b #

foldl' :: (b -> a -> b) -> b -> Complex a -> b #

foldr1 :: (a -> a -> a) -> Complex a -> a #

foldl1 :: (a -> a -> a) -> Complex a -> a #

toList :: Complex a -> [a] #

null :: Complex a -> Bool #

length :: Complex a -> Int #

elem :: Eq a => a -> Complex a -> Bool #

maximum :: Ord a => Complex a -> a #

minimum :: Ord a => Complex a -> a #

sum :: Num a => Complex a -> a #

product :: Num a => Complex a -> a #

Foldable ZipList 

Methods

fold :: Monoid m => ZipList m -> m #

foldMap :: Monoid m => (a -> m) -> ZipList a -> m #

foldr :: (a -> b -> b) -> b -> ZipList a -> b #

foldr' :: (a -> b -> b) -> b -> ZipList a -> b #

foldl :: (b -> a -> b) -> b -> ZipList a -> b #

foldl' :: (b -> a -> b) -> b -> ZipList a -> b #

foldr1 :: (a -> a -> a) -> ZipList a -> a #

foldl1 :: (a -> a -> a) -> ZipList a -> a #

toList :: ZipList a -> [a] #

null :: ZipList a -> Bool #

length :: ZipList a -> Int #

elem :: Eq a => a -> ZipList a -> Bool #

maximum :: Ord a => ZipList a -> a #

minimum :: Ord a => ZipList a -> a #

sum :: Num a => ZipList a -> a #

product :: Num a => ZipList a -> a #

Foldable Dual 

Methods

fold :: Monoid m => Dual m -> m #

foldMap :: Monoid m => (a -> m) -> Dual a -> m #

foldr :: (a -> b -> b) -> b -> Dual a -> b #

foldr' :: (a -> b -> b) -> b -> Dual a -> b #

foldl :: (b -> a -> b) -> b -> Dual a -> b #

foldl' :: (b -> a -> b) -> b -> Dual a -> b #

foldr1 :: (a -> a -> a) -> Dual a -> a #

foldl1 :: (a -> a -> a) -> Dual a -> a #

toList :: Dual a -> [a] #

null :: Dual a -> Bool #

length :: Dual a -> Int #

elem :: Eq a => a -> Dual a -> Bool #

maximum :: Ord a => Dual a -> a #

minimum :: Ord a => Dual a -> a #

sum :: Num a => Dual a -> a #

product :: Num a => Dual a -> a #

Foldable Sum 

Methods

fold :: Monoid m => Sum m -> m #

foldMap :: Monoid m => (a -> m) -> Sum a -> m #

foldr :: (a -> b -> b) -> b -> Sum a -> b #

foldr' :: (a -> b -> b) -> b -> Sum a -> b #

foldl :: (b -> a -> b) -> b -> Sum a -> b #

foldl' :: (b -> a -> b) -> b -> Sum a -> b #

foldr1 :: (a -> a -> a) -> Sum a -> a #

foldl1 :: (a -> a -> a) -> Sum a -> a #

toList :: Sum a -> [a] #

null :: Sum a -> Bool #

length :: Sum a -> Int #

elem :: Eq a => a -> Sum a -> Bool #

maximum :: Ord a => Sum a -> a #

minimum :: Ord a => Sum a -> a #

sum :: Num a => Sum a -> a #

product :: Num a => Sum a -> a #

Foldable Product 

Methods

fold :: Monoid m => Product m -> m #

foldMap :: Monoid m => (a -> m) -> Product a -> m #

foldr :: (a -> b -> b) -> b -> Product a -> b #

foldr' :: (a -> b -> b) -> b -> Product a -> b #

foldl :: (b -> a -> b) -> b -> Product a -> b #

foldl' :: (b -> a -> b) -> b -> Product a -> b #

foldr1 :: (a -> a -> a) -> Product a -> a #

foldl1 :: (a -> a -> a) -> Product a -> a #

toList :: Product a -> [a] #

null :: Product a -> Bool #

length :: Product a -> Int #

elem :: Eq a => a -> Product a -> Bool #

maximum :: Ord a => Product a -> a #

minimum :: Ord a => Product a -> a #

sum :: Num a => Product a -> a #

product :: Num a => Product a -> a #

Foldable First 

Methods

fold :: Monoid m => First m -> m #

foldMap :: Monoid m => (a -> m) -> First a -> m #

foldr :: (a -> b -> b) -> b -> First a -> b #

foldr' :: (a -> b -> b) -> b -> First a -> b #

foldl :: (b -> a -> b) -> b -> First a -> b #

foldl' :: (b -> a -> b) -> b -> First a -> b #

foldr1 :: (a -> a -> a) -> First a -> a #

foldl1 :: (a -> a -> a) -> First a -> a #

toList :: First a -> [a] #

null :: First a -> Bool #

length :: First a -> Int #

elem :: Eq a => a -> First a -> Bool #

maximum :: Ord a => First a -> a #

minimum :: Ord a => First a -> a #

sum :: Num a => First a -> a #

product :: Num a => First a -> a #

Foldable Last 

Methods

fold :: Monoid m => Last m -> m #

foldMap :: Monoid m => (a -> m) -> Last a -> m #

foldr :: (a -> b -> b) -> b -> Last a -> b #

foldr' :: (a -> b -> b) -> b -> Last a -> b #

foldl :: (b -> a -> b) -> b -> Last a -> b #

foldl' :: (b -> a -> b) -> b -> Last a -> b #

foldr1 :: (a -> a -> a) -> Last a -> a #

foldl1 :: (a -> a -> a) -> Last a -> a #

toList :: Last a -> [a] #

null :: Last a -> Bool #

length :: Last a -> Int #

elem :: Eq a => a -> Last a -> Bool #

maximum :: Ord a => Last a -> a #

minimum :: Ord a => Last a -> a #

sum :: Num a => Last a -> a #

product :: Num a => Last a -> a #

Foldable Digit 

Methods

fold :: Monoid m => Digit m -> m #

foldMap :: Monoid m => (a -> m) -> Digit a -> m #

foldr :: (a -> b -> b) -> b -> Digit a -> b #

foldr' :: (a -> b -> b) -> b -> Digit a -> b #

foldl :: (b -> a -> b) -> b -> Digit a -> b #

foldl' :: (b -> a -> b) -> b -> Digit a -> b #

foldr1 :: (a -> a -> a) -> Digit a -> a #

foldl1 :: (a -> a -> a) -> Digit a -> a #

toList :: Digit a -> [a] #

null :: Digit a -> Bool #

length :: Digit a -> Int #

elem :: Eq a => a -> Digit a -> Bool #

maximum :: Ord a => Digit a -> a #

minimum :: Ord a => Digit a -> a #

sum :: Num a => Digit a -> a #

product :: Num a => Digit a -> a #

Foldable Node 

Methods

fold :: Monoid m => Node m -> m #

foldMap :: Monoid m => (a -> m) -> Node a -> m #

foldr :: (a -> b -> b) -> b -> Node a -> b #

foldr' :: (a -> b -> b) -> b -> Node a -> b #

foldl :: (b -> a -> b) -> b -> Node a -> b #

foldl' :: (b -> a -> b) -> b -> Node a -> b #

foldr1 :: (a -> a -> a) -> Node a -> a #

foldl1 :: (a -> a -> a) -> Node a -> a #

toList :: Node a -> [a] #

null :: Node a -> Bool #

length :: Node a -> Int #

elem :: Eq a => a -> Node a -> Bool #

maximum :: Ord a => Node a -> a #

minimum :: Ord a => Node a -> a #

sum :: Num a => Node a -> a #

product :: Num a => Node a -> a #

Foldable Elem 

Methods

fold :: Monoid m => Elem m -> m #

foldMap :: Monoid m => (a -> m) -> Elem a -> m #

foldr :: (a -> b -> b) -> b -> Elem a -> b #

foldr' :: (a -> b -> b) -> b -> Elem a -> b #

foldl :: (b -> a -> b) -> b -> Elem a -> b #

foldl' :: (b -> a -> b) -> b -> Elem a -> b #

foldr1 :: (a -> a -> a) -> Elem a -> a #

foldl1 :: (a -> a -> a) -> Elem a -> a #

toList :: Elem a -> [a] #

null :: Elem a -> Bool #

length :: Elem a -> Int #

elem :: Eq a => a -> Elem a -> Bool #

maximum :: Ord a => Elem a -> a #

minimum :: Ord a => Elem a -> a #

sum :: Num a => Elem a -> a #

product :: Num a => Elem a -> a #

Foldable FingerTree 

Methods

fold :: Monoid m => FingerTree m -> m #

foldMap :: Monoid m => (a -> m) -> FingerTree a -> m #

foldr :: (a -> b -> b) -> b -> FingerTree a -> b #

foldr' :: (a -> b -> b) -> b -> FingerTree a -> b #

foldl :: (b -> a -> b) -> b -> FingerTree a -> b #

foldl' :: (b -> a -> b) -> b -> FingerTree a -> b #

foldr1 :: (a -> a -> a) -> FingerTree a -> a #

foldl1 :: (a -> a -> a) -> FingerTree a -> a #

toList :: FingerTree a -> [a] #

null :: FingerTree a -> Bool #

length :: FingerTree a -> Int #

elem :: Eq a => a -> FingerTree a -> Bool #

maximum :: Ord a => FingerTree a -> a #

minimum :: Ord a => FingerTree a -> a #

sum :: Num a => FingerTree a -> a #

product :: Num a => FingerTree a -> a #

Foldable Seq 

Methods

fold :: Monoid m => Seq m -> m #

foldMap :: Monoid m => (a -> m) -> Seq a -> m #

foldr :: (a -> b -> b) -> b -> Seq a -> b #

foldr' :: (a -> b -> b) -> b -> Seq a -> b #

foldl :: (b -> a -> b) -> b -> Seq a -> b #

foldl' :: (b -> a -> b) -> b -> Seq a -> b #

foldr1 :: (a -> a -> a) -> Seq a -> a #

foldl1 :: (a -> a -> a) -> Seq a -> a #

toList :: Seq a -> [a] #

null :: Seq a -> Bool #

length :: Seq a -> Int #

elem :: Eq a => a -> Seq a -> Bool #

maximum :: Ord a => Seq a -> a #

minimum :: Ord a => Seq a -> a #

sum :: Num a => Seq a -> a #

product :: Num a => Seq a -> a #

Foldable ViewL 

Methods

fold :: Monoid m => ViewL m -> m #

foldMap :: Monoid m => (a -> m) -> ViewL a -> m #

foldr :: (a -> b -> b) -> b -> ViewL a -> b #

foldr' :: (a -> b -> b) -> b -> ViewL a -> b #

foldl :: (b -> a -> b) -> b -> ViewL a -> b #

foldl' :: (b -> a -> b) -> b -> ViewL a -> b #

foldr1 :: (a -> a -> a) -> ViewL a -> a #

foldl1 :: (a -> a -> a) -> ViewL a -> a #

toList :: ViewL a -> [a] #

null :: ViewL a -> Bool #

length :: ViewL a -> Int #

elem :: Eq a => a -> ViewL a -> Bool #

maximum :: Ord a => ViewL a -> a #

minimum :: Ord a => ViewL a -> a #

sum :: Num a => ViewL a -> a #

product :: Num a => ViewL a -> a #

Foldable ViewR 

Methods

fold :: Monoid m => ViewR m -> m #

foldMap :: Monoid m => (a -> m) -> ViewR a -> m #

foldr :: (a -> b -> b) -> b -> ViewR a -> b #

foldr' :: (a -> b -> b) -> b -> ViewR a -> b #

foldl :: (b -> a -> b) -> b -> ViewR a -> b #

foldl' :: (b -> a -> b) -> b -> ViewR a -> b #

foldr1 :: (a -> a -> a) -> ViewR a -> a #

foldl1 :: (a -> a -> a) -> ViewR a -> a #

toList :: ViewR a -> [a] #

null :: ViewR a -> Bool #

length :: ViewR a -> Int #

elem :: Eq a => a -> ViewR a -> Bool #

maximum :: Ord a => ViewR a -> a #

minimum :: Ord a => ViewR a -> a #

sum :: Num a => ViewR a -> a #

product :: Num a => ViewR a -> a #

Foldable IntMap 

Methods

fold :: Monoid m => IntMap m -> m #

foldMap :: Monoid m => (a -> m) -> IntMap a -> m #

foldr :: (a -> b -> b) -> b -> IntMap a -> b #

foldr' :: (a -> b -> b) -> b -> IntMap a -> b #

foldl :: (b -> a -> b) -> b -> IntMap a -> b #

foldl' :: (b -> a -> b) -> b -> IntMap a -> b #

foldr1 :: (a -> a -> a) -> IntMap a -> a #

foldl1 :: (a -> a -> a) -> IntMap a -> a #

toList :: IntMap a -> [a] #

null :: IntMap a -> Bool #

length :: IntMap a -> Int #

elem :: Eq a => a -> IntMap a -> Bool #

maximum :: Ord a => IntMap a -> a #

minimum :: Ord a => IntMap a -> a #

sum :: Num a => IntMap a -> a #

product :: Num a => IntMap a -> a #

Foldable Set 

Methods

fold :: Monoid m => Set m -> m #

foldMap :: Monoid m => (a -> m) -> Set a -> m #

foldr :: (a -> b -> b) -> b -> Set a -> b #

foldr' :: (a -> b -> b) -> b -> Set a -> b #

foldl :: (b -> a -> b) -> b -> Set a -> b #

foldl' :: (b -> a -> b) -> b -> Set a -> b #

foldr1 :: (a -> a -> a) -> Set a -> a #

foldl1 :: (a -> a -> a) -> Set a -> a #

toList :: Set a -> [a] #

null :: Set a -> Bool #

length :: Set a -> Int #

elem :: Eq a => a -> Set a -> Bool #

maximum :: Ord a => Set a -> a #

minimum :: Ord a => Set a -> a #

sum :: Num a => Set a -> a #

product :: Num a => Set a -> a #

Foldable HashSet 

Methods

fold :: Monoid m => HashSet m -> m #

foldMap :: Monoid m => (a -> m) -> HashSet a -> m #

foldr :: (a -> b -> b) -> b -> HashSet a -> b #

foldr' :: (a -> b -> b) -> b -> HashSet a -> b #

foldl :: (b -> a -> b) -> b -> HashSet a -> b #

foldl' :: (b -> a -> b) -> b -> HashSet a -> b #

foldr1 :: (a -> a -> a) -> HashSet a -> a #

foldl1 :: (a -> a -> a) -> HashSet a -> a #

toList :: HashSet a -> [a] #

null :: HashSet a -> Bool #

length :: HashSet a -> Int #

elem :: Eq a => a -> HashSet a -> Bool #

maximum :: Ord a => HashSet a -> a #

minimum :: Ord a => HashSet a -> a #

sum :: Num a => HashSet a -> a #

product :: Num a => HashSet a -> a #

Foldable (Either a) 

Methods

fold :: Monoid m => Either a m -> m #

foldMap :: Monoid m => (a -> m) -> Either a a -> m #

foldr :: (a -> b -> b) -> b -> Either a a -> b #

foldr' :: (a -> b -> b) -> b -> Either a a -> b #

foldl :: (b -> a -> b) -> b -> Either a a -> b #

foldl' :: (b -> a -> b) -> b -> Either a a -> b #

foldr1 :: (a -> a -> a) -> Either a a -> a #

foldl1 :: (a -> a -> a) -> Either a a -> a #

toList :: Either a a -> [a] #

null :: Either a a -> Bool #

length :: Either a a -> Int #

elem :: Eq a => a -> Either a a -> Bool #

maximum :: Ord a => Either a a -> a #

minimum :: Ord a => Either a a -> a #

sum :: Num a => Either a a -> a #

product :: Num a => Either a a -> a #

Foldable f => Foldable (Rec1 f) 

Methods

fold :: Monoid m => Rec1 f m -> m #

foldMap :: Monoid m => (a -> m) -> Rec1 f a -> m #

foldr :: (a -> b -> b) -> b -> Rec1 f a -> b #

foldr' :: (a -> b -> b) -> b -> Rec1 f a -> b #

foldl :: (b -> a -> b) -> b -> Rec1 f a -> b #

foldl' :: (b -> a -> b) -> b -> Rec1 f a -> b #

foldr1 :: (a -> a -> a) -> Rec1 f a -> a #

foldl1 :: (a -> a -> a) -> Rec1 f a -> a #

toList :: Rec1 f a -> [a] #

null :: Rec1 f a -> Bool #

length :: Rec1 f a -> Int #

elem :: Eq a => a -> Rec1 f a -> Bool #

maximum :: Ord a => Rec1 f a -> a #

minimum :: Ord a => Rec1 f a -> a #

sum :: Num a => Rec1 f a -> a #

product :: Num a => Rec1 f a -> a #

Foldable (URec Char) 

Methods

fold :: Monoid m => URec Char m -> m #

foldMap :: Monoid m => (a -> m) -> URec Char a -> m #

foldr :: (a -> b -> b) -> b -> URec Char a -> b #

foldr' :: (a -> b -> b) -> b -> URec Char a -> b #

foldl :: (b -> a -> b) -> b -> URec Char a -> b #

foldl' :: (b -> a -> b) -> b -> URec Char a -> b #

foldr1 :: (a -> a -> a) -> URec Char a -> a #

foldl1 :: (a -> a -> a) -> URec Char a -> a #

toList :: URec Char a -> [a] #

null :: URec Char a -> Bool #

length :: URec Char a -> Int #

elem :: Eq a => a -> URec Char a -> Bool #

maximum :: Ord a => URec Char a -> a #

minimum :: Ord a => URec Char a -> a #

sum :: Num a => URec Char a -> a #

product :: Num a => URec Char a -> a #

Foldable (URec Double) 

Methods

fold :: Monoid m => URec Double m -> m #

foldMap :: Monoid m => (a -> m) -> URec Double a -> m #

foldr :: (a -> b -> b) -> b -> URec Double a -> b #

foldr' :: (a -> b -> b) -> b -> URec Double a -> b #

foldl :: (b -> a -> b) -> b -> URec Double a -> b #

foldl' :: (b -> a -> b) -> b -> URec Double a -> b #

foldr1 :: (a -> a -> a) -> URec Double a -> a #

foldl1 :: (a -> a -> a) -> URec Double a -> a #

toList :: URec Double a -> [a] #

null :: URec Double a -> Bool #

length :: URec Double a -> Int #

elem :: Eq a => a -> URec Double a -> Bool #

maximum :: Ord a => URec Double a -> a #

minimum :: Ord a => URec Double a -> a #

sum :: Num a => URec Double a -> a #

product :: Num a => URec Double a -> a #

Foldable (URec Float) 

Methods

fold :: Monoid m => URec Float m -> m #

foldMap :: Monoid m => (a -> m) -> URec Float a -> m #

foldr :: (a -> b -> b) -> b -> URec Float a -> b #

foldr' :: (a -> b -> b) -> b -> URec Float a -> b #

foldl :: (b -> a -> b) -> b -> URec Float a -> b #

foldl' :: (b -> a -> b) -> b -> URec Float a -> b #

foldr1 :: (a -> a -> a) -> URec Float a -> a #

foldl1 :: (a -> a -> a) -> URec Float a -> a #

toList :: URec Float a -> [a] #

null :: URec Float a -> Bool #

length :: URec Float a -> Int #

elem :: Eq a => a -> URec Float a -> Bool #

maximum :: Ord a => URec Float a -> a #

minimum :: Ord a => URec Float a -> a #

sum :: Num a => URec Float a -> a #

product :: Num a => URec Float a -> a #

Foldable (URec Int) 

Methods

fold :: Monoid m => URec Int m -> m #

foldMap :: Monoid m => (a -> m) -> URec Int a -> m #

foldr :: (a -> b -> b) -> b -> URec Int a -> b #

foldr' :: (a -> b -> b) -> b -> URec Int a -> b #

foldl :: (b -> a -> b) -> b -> URec Int a -> b #

foldl' :: (b -> a -> b) -> b -> URec Int a -> b #

foldr1 :: (a -> a -> a) -> URec Int a -> a #

foldl1 :: (a -> a -> a) -> URec Int a -> a #

toList :: URec Int a -> [a] #

null :: URec Int a -> Bool #

length :: URec Int a -> Int #

elem :: Eq a => a -> URec Int a -> Bool #

maximum :: Ord a => URec Int a -> a #

minimum :: Ord a => URec Int a -> a #

sum :: Num a => URec Int a -> a #

product :: Num a => URec Int a -> a #

Foldable (URec Word) 

Methods

fold :: Monoid m => URec Word m -> m #

foldMap :: Monoid m => (a -> m) -> URec Word a -> m #

foldr :: (a -> b -> b) -> b -> URec Word a -> b #

foldr' :: (a -> b -> b) -> b -> URec Word a -> b #

foldl :: (b -> a -> b) -> b -> URec Word a -> b #

foldl' :: (b -> a -> b) -> b -> URec Word a -> b #

foldr1 :: (a -> a -> a) -> URec Word a -> a #

foldl1 :: (a -> a -> a) -> URec Word a -> a #

toList :: URec Word a -> [a] #

null :: URec Word a -> Bool #

length :: URec Word a -> Int #

elem :: Eq a => a -> URec Word a -> Bool #

maximum :: Ord a => URec Word a -> a #

minimum :: Ord a => URec Word a -> a #

sum :: Num a => URec Word a -> a #

product :: Num a => URec Word a -> a #

Foldable (URec (Ptr ())) 

Methods

fold :: Monoid m => URec (Ptr ()) m -> m #

foldMap :: Monoid m => (a -> m) -> URec (Ptr ()) a -> m #

foldr :: (a -> b -> b) -> b -> URec (Ptr ()) a -> b #

foldr' :: (a -> b -> b) -> b -> URec (Ptr ()) a -> b #

foldl :: (b -> a -> b) -> b -> URec (Ptr ()) a -> b #

foldl' :: (b -> a -> b) -> b -> URec (Ptr ()) a -> b #

foldr1 :: (a -> a -> a) -> URec (Ptr ()) a -> a #

foldl1 :: (a -> a -> a) -> URec (Ptr ()) a -> a #

toList :: URec (Ptr ()) a -> [a] #

null :: URec (Ptr ()) a -> Bool #

length :: URec (Ptr ()) a -> Int #

elem :: Eq a => a -> URec (Ptr ()) a -> Bool #

maximum :: Ord a => URec (Ptr ()) a -> a #

minimum :: Ord a => URec (Ptr ()) a -> a #

sum :: Num a => URec (Ptr ()) a -> a #

product :: Num a => URec (Ptr ()) a -> a #

Foldable ((,) a) 

Methods

fold :: Monoid m => (a, m) -> m #

foldMap :: Monoid m => (a -> m) -> (a, a) -> m #

foldr :: (a -> b -> b) -> b -> (a, a) -> b #

foldr' :: (a -> b -> b) -> b -> (a, a) -> b #

foldl :: (b -> a -> b) -> b -> (a, a) -> b #

foldl' :: (b -> a -> b) -> b -> (a, a) -> b #

foldr1 :: (a -> a -> a) -> (a, a) -> a #

foldl1 :: (a -> a -> a) -> (a, a) -> a #

toList :: (a, a) -> [a] #

null :: (a, a) -> Bool #

length :: (a, a) -> Int #

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

maximum :: Ord a => (a, a) -> a #

minimum :: Ord a => (a, a) -> a #

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

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

Foldable (Array i) 

Methods

fold :: Monoid m => Array i m -> m #

foldMap :: Monoid m => (a -> m) -> Array i a -> m #

foldr :: (a -> b -> b) -> b -> Array i a -> b #

foldr' :: (a -> b -> b) -> b -> Array i a -> b #

foldl :: (b -> a -> b) -> b -> Array i a -> b #

foldl' :: (b -> a -> b) -> b -> Array i a -> b #

foldr1 :: (a -> a -> a) -> Array i a -> a #

foldl1 :: (a -> a -> a) -> Array i a -> a #

toList :: Array i a -> [a] #

null :: Array i a -> Bool #

length :: Array i a -> Int #

elem :: Eq a => a -> Array i a -> Bool #

maximum :: Ord a => Array i a -> a #

minimum :: Ord a => Array i a -> a #

sum :: Num a => Array i a -> a #

product :: Num a => Array i a -> a #

Foldable (Arg a) 

Methods

fold :: Monoid m => Arg a m -> m #

foldMap :: Monoid m => (a -> m) -> Arg a a -> m #

foldr :: (a -> b -> b) -> b -> Arg a a -> b #

foldr' :: (a -> b -> b) -> b -> Arg a a -> b #

foldl :: (b -> a -> b) -> b -> Arg a a -> b #

foldl' :: (b -> a -> b) -> b -> Arg a a -> b #

foldr1 :: (a -> a -> a) -> Arg a a -> a #

foldl1 :: (a -> a -> a) -> Arg a a -> a #

toList :: Arg a a -> [a] #

null :: Arg a a -> Bool #

length :: Arg a a -> Int #

elem :: Eq a => a -> Arg a a -> Bool #

maximum :: Ord a => Arg a a -> a #

minimum :: Ord a => Arg a a -> a #

sum :: Num a => Arg a a -> a #

product :: Num a => Arg a a -> a #

Foldable (Proxy *) 

Methods

fold :: Monoid m => Proxy * m -> m #

foldMap :: Monoid m => (a -> m) -> Proxy * a -> m #

foldr :: (a -> b -> b) -> b -> Proxy * a -> b #

foldr' :: (a -> b -> b) -> b -> Proxy * a -> b #

foldl :: (b -> a -> b) -> b -> Proxy * a -> b #

foldl' :: (b -> a -> b) -> b -> Proxy * a -> b #

foldr1 :: (a -> a -> a) -> Proxy * a -> a #

foldl1 :: (a -> a -> a) -> Proxy * a -> a #

toList :: Proxy * a -> [a] #

null :: Proxy * a -> Bool #

length :: Proxy * a -> Int #

elem :: Eq a => a -> Proxy * a -> Bool #

maximum :: Ord a => Proxy * a -> a #

minimum :: Ord a => Proxy * a -> a #

sum :: Num a => Proxy * a -> a #

product :: Num a => Proxy * a -> a #

Foldable (Map k) 

Methods

fold :: Monoid m => Map k m -> m #

foldMap :: Monoid m => (a -> m) -> Map k a -> m #

foldr :: (a -> b -> b) -> b -> Map k a -> b #

foldr' :: (a -> b -> b) -> b -> Map k a -> b #

foldl :: (b -> a -> b) -> b -> Map k a -> b #

foldl' :: (b -> a -> b) -> b -> Map k a -> b #

foldr1 :: (a -> a -> a) -> Map k a -> a #

foldl1 :: (a -> a -> a) -> Map k a -> a #

toList :: Map k a -> [a] #

null :: Map k a -> Bool #

length :: Map k a -> Int #

elem :: Eq a => a -> Map k a -> Bool #

maximum :: Ord a => Map k a -> a #

minimum :: Ord a => Map k a -> a #

sum :: Num a => Map k a -> a #

product :: Num a => Map k a -> a #

Foldable (HashMap k) 

Methods

fold :: Monoid m => HashMap k m -> m #

foldMap :: Monoid m => (a -> m) -> HashMap k a -> m #

foldr :: (a -> b -> b) -> b -> HashMap k a -> b #

foldr' :: (a -> b -> b) -> b -> HashMap k a -> b #

foldl :: (b -> a -> b) -> b -> HashMap k a -> b #

foldl' :: (b -> a -> b) -> b -> HashMap k a -> b #

foldr1 :: (a -> a -> a) -> HashMap k a -> a #

foldl1 :: (a -> a -> a) -> HashMap k a -> a #

toList :: HashMap k a -> [a] #

null :: HashMap k a -> Bool #

length :: HashMap k a -> Int #

elem :: Eq a => a -> HashMap k a -> Bool #

maximum :: Ord a => HashMap k a -> a #

minimum :: Ord a => HashMap k a -> a #

sum :: Num a => HashMap k a -> a #

product :: Num a => HashMap k a -> a #

Foldable (K1 i c) 

Methods

fold :: Monoid m => K1 i c m -> m #

foldMap :: Monoid m => (a -> m) -> K1 i c a -> m #

foldr :: (a -> b -> b) -> b -> K1 i c a -> b #

foldr' :: (a -> b -> b) -> b -> K1 i c a -> b #

foldl :: (b -> a -> b) -> b -> K1 i c a -> b #

foldl' :: (b -> a -> b) -> b -> K1 i c a -> b #

foldr1 :: (a -> a -> a) -> K1 i c a -> a #

foldl1 :: (a -> a -> a) -> K1 i c a -> a #

toList :: K1 i c a -> [a] #

null :: K1 i c a -> Bool #

length :: K1 i c a -> Int #

elem :: Eq a => a -> K1 i c a -> Bool #

maximum :: Ord a => K1 i c a -> a #

minimum :: Ord a => K1 i c a -> a #

sum :: Num a => K1 i c a -> a #

product :: Num a => K1 i c a -> a #

(Foldable f, Foldable g) => Foldable ((:+:) f g) 

Methods

fold :: Monoid m => (f :+: g) m -> m #

foldMap :: Monoid m => (a -> m) -> (f :+: g) a -> m #

foldr :: (a -> b -> b) -> b -> (f :+: g) a -> b #

foldr' :: (a -> b -> b) -> b -> (f :+: g) a -> b #

foldl :: (b -> a -> b) -> b -> (f :+: g) a -> b #

foldl' :: (b -> a -> b) -> b -> (f :+: g) a -> b #

foldr1 :: (a -> a -> a) -> (f :+: g) a -> a #

foldl1 :: (a -> a -> a) -> (f :+: g) a -> a #

toList :: (f :+: g) a -> [a] #

null :: (f :+: g) a -> Bool #

length :: (f :+: g) a -> Int #

elem :: Eq a => a -> (f :+: g) a -> Bool #

maximum :: Ord a => (f :+: g) a -> a #

minimum :: Ord a => (f :+: g) a -> a #

sum :: Num a => (f :+: g) a -> a #

product :: Num a => (f :+: g) a -> a #

(Foldable f, Foldable g) => Foldable ((:*:) f g) 

Methods

fold :: Monoid m => (f :*: g) m -> m #

foldMap :: Monoid m => (a -> m) -> (f :*: g) a -> m #

foldr :: (a -> b -> b) -> b -> (f :*: g) a -> b #

foldr' :: (a -> b -> b) -> b -> (f :*: g) a -> b #

foldl :: (b -> a -> b) -> b -> (f :*: g) a -> b #

foldl' :: (b -> a -> b) -> b -> (f :*: g) a -> b #

foldr1 :: (a -> a -> a) -> (f :*: g) a -> a #

foldl1 :: (a -> a -> a) -> (f :*: g) a -> a #

toList :: (f :*: g) a -> [a] #

null :: (f :*: g) a -> Bool #

length :: (f :*: g) a -> Int #

elem :: Eq a => a -> (f :*: g) a -> Bool #

maximum :: Ord a => (f :*: g) a -> a #

minimum :: Ord a => (f :*: g) a -> a #

sum :: Num a => (f :*: g) a -> a #

product :: Num a => (f :*: g) a -> a #

(Foldable f, Foldable g) => Foldable ((:.:) f g) 

Methods

fold :: Monoid m => (f :.: g) m -> m #

foldMap :: Monoid m => (a -> m) -> (f :.: g) a -> m #

foldr :: (a -> b -> b) -> b -> (f :.: g) a -> b #

foldr' :: (a -> b -> b) -> b -> (f :.: g) a -> b #

foldl :: (b -> a -> b) -> b -> (f :.: g) a -> b #

foldl' :: (b -> a -> b) -> b -> (f :.: g) a -> b #

foldr1 :: (a -> a -> a) -> (f :.: g) a -> a #

foldl1 :: (a -> a -> a) -> (f :.: g) a -> a #

toList :: (f :.: g) a -> [a] #

null :: (f :.: g) a -> Bool #

length :: (f :.: g) a -> Int #

elem :: Eq a => a -> (f :.: g) a -> Bool #

maximum :: Ord a => (f :.: g) a -> a #

minimum :: Ord a => (f :.: g) a -> a #

sum :: Num a => (f :.: g) a -> a #

product :: Num a => (f :.: g) a -> a #

Foldable (Const * m) 

Methods

fold :: Monoid m => Const * m m -> m #

foldMap :: Monoid m => (a -> m) -> Const * m a -> m #

foldr :: (a -> b -> b) -> b -> Const * m a -> b #

foldr' :: (a -> b -> b) -> b -> Const * m a -> b #

foldl :: (b -> a -> b) -> b -> Const * m a -> b #

foldl' :: (b -> a -> b) -> b -> Const * m a -> b #

foldr1 :: (a -> a -> a) -> Const * m a -> a #

foldl1 :: (a -> a -> a) -> Const * m a -> a #

toList :: Const * m a -> [a] #

null :: Const * m a -> Bool #

length :: Const * m a -> Int #

elem :: Eq a => a -> Const * m a -> Bool #

maximum :: Ord a => Const * m a -> a #

minimum :: Ord a => Const * m a -> a #

sum :: Num a => Const * m a -> a #

product :: Num a => Const * m a -> a #

Foldable f => Foldable (ErrorT e f) 

Methods

fold :: Monoid m => ErrorT e f m -> m #

foldMap :: Monoid m => (a -> m) -> ErrorT e f a -> m #

foldr :: (a -> b -> b) -> b -> ErrorT e f a -> b #

foldr' :: (a -> b -> b) -> b -> ErrorT e f a -> b #

foldl :: (b -> a -> b) -> b -> ErrorT e f a -> b #

foldl' :: (b -> a -> b) -> b -> ErrorT e f a -> b #

foldr1 :: (a -> a -> a) -> ErrorT e f a -> a #

foldl1 :: (a -> a -> a) -> ErrorT e f a -> a #

toList :: ErrorT e f a -> [a] #

null :: ErrorT e f a -> Bool #

length :: ErrorT e f a -> Int #

elem :: Eq a => a -> ErrorT e f a -> Bool #

maximum :: Ord a => ErrorT e f a -> a #

minimum :: Ord a => ErrorT e f a -> a #

sum :: Num a => ErrorT e f a -> a #

product :: Num a => ErrorT e f a -> a #

Foldable f => Foldable (M1 i c f) 

Methods

fold :: Monoid m => M1 i c f m -> m #

foldMap :: Monoid m => (a -> m) -> M1 i c f a -> m #

foldr :: (a -> b -> b) -> b -> M1 i c f a -> b #

foldr' :: (a -> b -> b) -> b -> M1 i c f a -> b #

foldl :: (b -> a -> b) -> b -> M1 i c f a -> b #

foldl' :: (b -> a -> b) -> b -> M1 i c f a -> b #

foldr1 :: (a -> a -> a) -> M1 i c f a -> a #

foldl1 :: (a -> a -> a) -> M1 i c f a -> a #

toList :: M1 i c f a -> [a] #

null :: M1 i c f a -> Bool #

length :: M1 i c f a -> Int #

elem :: Eq a => a -> M1 i c f a -> Bool #

maximum :: Ord a => M1 i c f a -> a #

minimum :: Ord a => M1 i c f a -> a #

sum :: Num a => M1 i c f a -> a #

product :: Num a => M1 i c f a -> a #

toList :: Foldable t => forall a. t a -> [a] #

List of elements of a structure, from left to right.

null :: Foldable t => forall a. t a -> Bool #

Test whether the structure is empty. The default implementation is + optimized for structures that are similar to cons-lists, because there + is no general way to do better.

length :: Foldable t => forall a. t a -> Int #

Returns the size/length of a finite structure as an Int. The + default implementation is optimized for structures that are similar to + cons-lists, because there is no general way to do better.

elem :: Foldable t => forall a. Eq a => a -> t a -> Bool #

Does the element occur in the structure?

class (Functor t, Foldable t) => Traversable t where #

Functors representing data structures that can be traversed from + left to right.

A definition of traverse must satisfy the following laws:

naturality
t . traverse f = traverse (t . f) + for every applicative transformation t
identity
traverse Identity = Identity
composition
traverse (Compose . fmap g . f) = Compose . fmap (traverse g) . traverse f

A definition of sequenceA must satisfy the following laws:

naturality
t . sequenceA = sequenceA . fmap t + for every applicative transformation t
identity
sequenceA . fmap Identity = Identity
composition
sequenceA . fmap Compose = Compose . fmap sequenceA . sequenceA

where an applicative transformation is a function

t :: (Applicative f, Applicative g) => f a -> g a

preserving the Applicative operations, i.e.

and the identity functor Identity and composition of functors Compose + are defined as

  newtype Identity a = Identity a
+
+  instance Functor Identity where
+    fmap f (Identity x) = Identity (f x)
+
+  instance Applicative Identity where
+    pure x = Identity x
+    Identity f <*> Identity x = Identity (f x)
+
+  newtype Compose f g a = Compose (f (g a))
+
+  instance (Functor f, Functor g) => Functor (Compose f g) where
+    fmap f (Compose x) = Compose (fmap (fmap f) x)
+
+  instance (Applicative f, Applicative g) => Applicative (Compose f g) where
+    pure x = Compose (pure (pure x))
+    Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)

(The naturality law is implied by parametricity.)

Instances are similar to Functor, e.g. given a data type

data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)

a suitable instance would be

instance Traversable Tree where
+   traverse f Empty = pure Empty
+   traverse f (Leaf x) = Leaf <$> f x
+   traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r

This is suitable even for abstract types, as the laws for <*> + imply a form of associativity.

The superclass instances should satisfy the following:

Minimal complete definition

traverse | sequenceA

Instances

Traversable [] 

Methods

traverse :: Applicative f => (a -> f b) -> [a] -> f [b] #

sequenceA :: Applicative f => [f a] -> f [a] #

mapM :: Monad m => (a -> m b) -> [a] -> m [b] #

sequence :: Monad m => [m a] -> m [a] #

Traversable Maybe 

Methods

traverse :: Applicative f => (a -> f b) -> Maybe a -> f (Maybe b) #

sequenceA :: Applicative f => Maybe (f a) -> f (Maybe a) #

mapM :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b) #

sequence :: Monad m => Maybe (m a) -> m (Maybe a) #

Traversable V1 

Methods

traverse :: Applicative f => (a -> f b) -> V1 a -> f (V1 b) #

sequenceA :: Applicative f => V1 (f a) -> f (V1 a) #

mapM :: Monad m => (a -> m b) -> V1 a -> m (V1 b) #

sequence :: Monad m => V1 (m a) -> m (V1 a) #

Traversable U1 

Methods

traverse :: Applicative f => (a -> f b) -> U1 a -> f (U1 b) #

sequenceA :: Applicative f => U1 (f a) -> f (U1 a) #

mapM :: Monad m => (a -> m b) -> U1 a -> m (U1 b) #

sequence :: Monad m => U1 (m a) -> m (U1 a) #

Traversable Par1 

Methods

traverse :: Applicative f => (a -> f b) -> Par1 a -> f (Par1 b) #

sequenceA :: Applicative f => Par1 (f a) -> f (Par1 a) #

mapM :: Monad m => (a -> m b) -> Par1 a -> m (Par1 b) #

sequence :: Monad m => Par1 (m a) -> m (Par1 a) #

Traversable Identity 

Methods

traverse :: Applicative f => (a -> f b) -> Identity a -> f (Identity b) #

sequenceA :: Applicative f => Identity (f a) -> f (Identity a) #

mapM :: Monad m => (a -> m b) -> Identity a -> m (Identity b) #

sequence :: Monad m => Identity (m a) -> m (Identity a) #

Traversable Min 

Methods

traverse :: Applicative f => (a -> f b) -> Min a -> f (Min b) #

sequenceA :: Applicative f => Min (f a) -> f (Min a) #

mapM :: Monad m => (a -> m b) -> Min a -> m (Min b) #

sequence :: Monad m => Min (m a) -> m (Min a) #

Traversable Max 

Methods

traverse :: Applicative f => (a -> f b) -> Max a -> f (Max b) #

sequenceA :: Applicative f => Max (f a) -> f (Max a) #

mapM :: Monad m => (a -> m b) -> Max a -> m (Max b) #

sequence :: Monad m => Max (m a) -> m (Max a) #

Traversable First 

Methods

traverse :: Applicative f => (a -> f b) -> First a -> f (First b) #

sequenceA :: Applicative f => First (f a) -> f (First a) #

mapM :: Monad m => (a -> m b) -> First a -> m (First b) #

sequence :: Monad m => First (m a) -> m (First a) #

Traversable Last 

Methods

traverse :: Applicative f => (a -> f b) -> Last a -> f (Last b) #

sequenceA :: Applicative f => Last (f a) -> f (Last a) #

mapM :: Monad m => (a -> m b) -> Last a -> m (Last b) #

sequence :: Monad m => Last (m a) -> m (Last a) #

Traversable Option 

Methods

traverse :: Applicative f => (a -> f b) -> Option a -> f (Option b) #

sequenceA :: Applicative f => Option (f a) -> f (Option a) #

mapM :: Monad m => (a -> m b) -> Option a -> m (Option b) #

sequence :: Monad m => Option (m a) -> m (Option a) #

Traversable NonEmpty 

Methods

traverse :: Applicative f => (a -> f b) -> NonEmpty a -> f (NonEmpty b) #

sequenceA :: Applicative f => NonEmpty (f a) -> f (NonEmpty a) #

mapM :: Monad m => (a -> m b) -> NonEmpty a -> m (NonEmpty b) #

sequence :: Monad m => NonEmpty (m a) -> m (NonEmpty a) #

Traversable Complex 

Methods

traverse :: Applicative f => (a -> f b) -> Complex a -> f (Complex b) #

sequenceA :: Applicative f => Complex (f a) -> f (Complex a) #

mapM :: Monad m => (a -> m b) -> Complex a -> m (Complex b) #

sequence :: Monad m => Complex (m a) -> m (Complex a) #

Traversable ZipList 

Methods

traverse :: Applicative f => (a -> f b) -> ZipList a -> f (ZipList b) #

sequenceA :: Applicative f => ZipList (f a) -> f (ZipList a) #

mapM :: Monad m => (a -> m b) -> ZipList a -> m (ZipList b) #

sequence :: Monad m => ZipList (m a) -> m (ZipList a) #

Traversable Dual 

Methods

traverse :: Applicative f => (a -> f b) -> Dual a -> f (Dual b) #

sequenceA :: Applicative f => Dual (f a) -> f (Dual a) #

mapM :: Monad m => (a -> m b) -> Dual a -> m (Dual b) #

sequence :: Monad m => Dual (m a) -> m (Dual a) #

Traversable Sum 

Methods

traverse :: Applicative f => (a -> f b) -> Sum a -> f (Sum b) #

sequenceA :: Applicative f => Sum (f a) -> f (Sum a) #

mapM :: Monad m => (a -> m b) -> Sum a -> m (Sum b) #

sequence :: Monad m => Sum (m a) -> m (Sum a) #

Traversable Product 

Methods

traverse :: Applicative f => (a -> f b) -> Product a -> f (Product b) #

sequenceA :: Applicative f => Product (f a) -> f (Product a) #

mapM :: Monad m => (a -> m b) -> Product a -> m (Product b) #

sequence :: Monad m => Product (m a) -> m (Product a) #

Traversable First 

Methods

traverse :: Applicative f => (a -> f b) -> First a -> f (First b) #

sequenceA :: Applicative f => First (f a) -> f (First a) #

mapM :: Monad m => (a -> m b) -> First a -> m (First b) #

sequence :: Monad m => First (m a) -> m (First a) #

Traversable Last 

Methods

traverse :: Applicative f => (a -> f b) -> Last a -> f (Last b) #

sequenceA :: Applicative f => Last (f a) -> f (Last a) #

mapM :: Monad m => (a -> m b) -> Last a -> m (Last b) #

sequence :: Monad m => Last (m a) -> m (Last a) #

Traversable Digit 

Methods

traverse :: Applicative f => (a -> f b) -> Digit a -> f (Digit b) #

sequenceA :: Applicative f => Digit (f a) -> f (Digit a) #

mapM :: Monad m => (a -> m b) -> Digit a -> m (Digit b) #

sequence :: Monad m => Digit (m a) -> m (Digit a) #

Traversable Node 

Methods

traverse :: Applicative f => (a -> f b) -> Node a -> f (Node b) #

sequenceA :: Applicative f => Node (f a) -> f (Node a) #

mapM :: Monad m => (a -> m b) -> Node a -> m (Node b) #

sequence :: Monad m => Node (m a) -> m (Node a) #

Traversable Elem 

Methods

traverse :: Applicative f => (a -> f b) -> Elem a -> f (Elem b) #

sequenceA :: Applicative f => Elem (f a) -> f (Elem a) #

mapM :: Monad m => (a -> m b) -> Elem a -> m (Elem b) #

sequence :: Monad m => Elem (m a) -> m (Elem a) #

Traversable FingerTree 

Methods

traverse :: Applicative f => (a -> f b) -> FingerTree a -> f (FingerTree b) #

sequenceA :: Applicative f => FingerTree (f a) -> f (FingerTree a) #

mapM :: Monad m => (a -> m b) -> FingerTree a -> m (FingerTree b) #

sequence :: Monad m => FingerTree (m a) -> m (FingerTree a) #

Traversable Seq 

Methods

traverse :: Applicative f => (a -> f b) -> Seq a -> f (Seq b) #

sequenceA :: Applicative f => Seq (f a) -> f (Seq a) #

mapM :: Monad m => (a -> m b) -> Seq a -> m (Seq b) #

sequence :: Monad m => Seq (m a) -> m (Seq a) #

Traversable ViewL 

Methods

traverse :: Applicative f => (a -> f b) -> ViewL a -> f (ViewL b) #

sequenceA :: Applicative f => ViewL (f a) -> f (ViewL a) #

mapM :: Monad m => (a -> m b) -> ViewL a -> m (ViewL b) #

sequence :: Monad m => ViewL (m a) -> m (ViewL a) #

Traversable ViewR 

Methods

traverse :: Applicative f => (a -> f b) -> ViewR a -> f (ViewR b) #

sequenceA :: Applicative f => ViewR (f a) -> f (ViewR a) #

mapM :: Monad m => (a -> m b) -> ViewR a -> m (ViewR b) #

sequence :: Monad m => ViewR (m a) -> m (ViewR a) #

Traversable IntMap 

Methods

traverse :: Applicative f => (a -> f b) -> IntMap a -> f (IntMap b) #

sequenceA :: Applicative f => IntMap (f a) -> f (IntMap a) #

mapM :: Monad m => (a -> m b) -> IntMap a -> m (IntMap b) #

sequence :: Monad m => IntMap (m a) -> m (IntMap a) #

Traversable (Either a) 

Methods

traverse :: Applicative f => (a -> f b) -> Either a a -> f (Either a b) #

sequenceA :: Applicative f => Either a (f a) -> f (Either a a) #

mapM :: Monad m => (a -> m b) -> Either a a -> m (Either a b) #

sequence :: Monad m => Either a (m a) -> m (Either a a) #

Traversable f => Traversable (Rec1 f) 

Methods

traverse :: Applicative f => (a -> f b) -> Rec1 f a -> f (Rec1 f b) #

sequenceA :: Applicative f => Rec1 f (f a) -> f (Rec1 f a) #

mapM :: Monad m => (a -> m b) -> Rec1 f a -> m (Rec1 f b) #

sequence :: Monad m => Rec1 f (m a) -> m (Rec1 f a) #

Traversable (URec Char) 

Methods

traverse :: Applicative f => (a -> f b) -> URec Char a -> f (URec Char b) #

sequenceA :: Applicative f => URec Char (f a) -> f (URec Char a) #

mapM :: Monad m => (a -> m b) -> URec Char a -> m (URec Char b) #

sequence :: Monad m => URec Char (m a) -> m (URec Char a) #

Traversable (URec Double) 

Methods

traverse :: Applicative f => (a -> f b) -> URec Double a -> f (URec Double b) #

sequenceA :: Applicative f => URec Double (f a) -> f (URec Double a) #

mapM :: Monad m => (a -> m b) -> URec Double a -> m (URec Double b) #

sequence :: Monad m => URec Double (m a) -> m (URec Double a) #

Traversable (URec Float) 

Methods

traverse :: Applicative f => (a -> f b) -> URec Float a -> f (URec Float b) #

sequenceA :: Applicative f => URec Float (f a) -> f (URec Float a) #

mapM :: Monad m => (a -> m b) -> URec Float a -> m (URec Float b) #

sequence :: Monad m => URec Float (m a) -> m (URec Float a) #

Traversable (URec Int) 

Methods

traverse :: Applicative f => (a -> f b) -> URec Int a -> f (URec Int b) #

sequenceA :: Applicative f => URec Int (f a) -> f (URec Int a) #

mapM :: Monad m => (a -> m b) -> URec Int a -> m (URec Int b) #

sequence :: Monad m => URec Int (m a) -> m (URec Int a) #

Traversable (URec Word) 

Methods

traverse :: Applicative f => (a -> f b) -> URec Word a -> f (URec Word b) #

sequenceA :: Applicative f => URec Word (f a) -> f (URec Word a) #

mapM :: Monad m => (a -> m b) -> URec Word a -> m (URec Word b) #

sequence :: Monad m => URec Word (m a) -> m (URec Word a) #

Traversable (URec (Ptr ())) 

Methods

traverse :: Applicative f => (a -> f b) -> URec (Ptr ()) a -> f (URec (Ptr ()) b) #

sequenceA :: Applicative f => URec (Ptr ()) (f a) -> f (URec (Ptr ()) a) #

mapM :: Monad m => (a -> m b) -> URec (Ptr ()) a -> m (URec (Ptr ()) b) #

sequence :: Monad m => URec (Ptr ()) (m a) -> m (URec (Ptr ()) a) #

Traversable ((,) a) 

Methods

traverse :: Applicative f => (a -> f b) -> (a, a) -> f (a, b) #

sequenceA :: Applicative f => (a, f a) -> f (a, a) #

mapM :: Monad m => (a -> m b) -> (a, a) -> m (a, b) #

sequence :: Monad m => (a, m a) -> m (a, a) #

Ix i => Traversable (Array i) 

Methods

traverse :: Applicative f => (a -> f b) -> Array i a -> f (Array i b) #

sequenceA :: Applicative f => Array i (f a) -> f (Array i a) #

mapM :: Monad m => (a -> m b) -> Array i a -> m (Array i b) #

sequence :: Monad m => Array i (m a) -> m (Array i a) #

Traversable (Arg a) 

Methods

traverse :: Applicative f => (a -> f b) -> Arg a a -> f (Arg a b) #

sequenceA :: Applicative f => Arg a (f a) -> f (Arg a a) #

mapM :: Monad m => (a -> m b) -> Arg a a -> m (Arg a b) #

sequence :: Monad m => Arg a (m a) -> m (Arg a a) #

Traversable (Proxy *) 

Methods

traverse :: Applicative f => (a -> f b) -> Proxy * a -> f (Proxy * b) #

sequenceA :: Applicative f => Proxy * (f a) -> f (Proxy * a) #

mapM :: Monad m => (a -> m b) -> Proxy * a -> m (Proxy * b) #

sequence :: Monad m => Proxy * (m a) -> m (Proxy * a) #

Traversable (Map k) 

Methods

traverse :: Applicative f => (a -> f b) -> Map k a -> f (Map k b) #

sequenceA :: Applicative f => Map k (f a) -> f (Map k a) #

mapM :: Monad m => (a -> m b) -> Map k a -> m (Map k b) #

sequence :: Monad m => Map k (m a) -> m (Map k a) #

Traversable (HashMap k) 

Methods

traverse :: Applicative f => (a -> f b) -> HashMap k a -> f (HashMap k b) #

sequenceA :: Applicative f => HashMap k (f a) -> f (HashMap k a) #

mapM :: Monad m => (a -> m b) -> HashMap k a -> m (HashMap k b) #

sequence :: Monad m => HashMap k (m a) -> m (HashMap k a) #

Traversable (K1 i c) 

Methods

traverse :: Applicative f => (a -> f b) -> K1 i c a -> f (K1 i c b) #

sequenceA :: Applicative f => K1 i c (f a) -> f (K1 i c a) #

mapM :: Monad m => (a -> m b) -> K1 i c a -> m (K1 i c b) #

sequence :: Monad m => K1 i c (m a) -> m (K1 i c a) #

(Traversable f, Traversable g) => Traversable ((:+:) f g) 

Methods

traverse :: Applicative f => (a -> f b) -> (f :+: g) a -> f ((f :+: g) b) #

sequenceA :: Applicative f => (f :+: g) (f a) -> f ((f :+: g) a) #

mapM :: Monad m => (a -> m b) -> (f :+: g) a -> m ((f :+: g) b) #

sequence :: Monad m => (f :+: g) (m a) -> m ((f :+: g) a) #

(Traversable f, Traversable g) => Traversable ((:*:) f g) 

Methods

traverse :: Applicative f => (a -> f b) -> (f :*: g) a -> f ((f :*: g) b) #

sequenceA :: Applicative f => (f :*: g) (f a) -> f ((f :*: g) a) #

mapM :: Monad m => (a -> m b) -> (f :*: g) a -> m ((f :*: g) b) #

sequence :: Monad m => (f :*: g) (m a) -> m ((f :*: g) a) #

(Traversable f, Traversable g) => Traversable ((:.:) f g) 

Methods

traverse :: Applicative f => (a -> f b) -> (f :.: g) a -> f ((f :.: g) b) #

sequenceA :: Applicative f => (f :.: g) (f a) -> f ((f :.: g) a) #

mapM :: Monad m => (a -> m b) -> (f :.: g) a -> m ((f :.: g) b) #

sequence :: Monad m => (f :.: g) (m a) -> m ((f :.: g) a) #

Traversable (Const * m) 

Methods

traverse :: Applicative f => (a -> f b) -> Const * m a -> f (Const * m b) #

sequenceA :: Applicative f => Const * m (f a) -> f (Const * m a) #

mapM :: Monad m => (a -> m b) -> Const * m a -> m (Const * m b) #

sequence :: Monad m => Const * m (m a) -> m (Const * m a) #

Traversable f => Traversable (ErrorT e f) 

Methods

traverse :: Applicative f => (a -> f b) -> ErrorT e f a -> f (ErrorT e f b) #

sequenceA :: Applicative f => ErrorT e f (f a) -> f (ErrorT e f a) #

mapM :: Monad m => (a -> m b) -> ErrorT e f a -> m (ErrorT e f b) #

sequence :: Monad m => ErrorT e f (m a) -> m (ErrorT e f a) #

Traversable f => Traversable (M1 i c f) 

Methods

traverse :: Applicative f => (a -> f b) -> M1 i c f a -> f (M1 i c f b) #

sequenceA :: Applicative f => M1 i c f (f a) -> f (M1 i c f a) #

mapM :: Monad m => (a -> m b) -> M1 i c f a -> m (M1 i c f b) #

sequence :: Monad m => M1 i c f (m a) -> m (M1 i c f a) #

class Typeable k a #

The class Typeable allows a concrete representation of a type to + be calculated.

Minimal complete definition

typeRep#

class IsString a where #

Class for string-like datastructures; used by the overloaded string + extension (-XOverloadedStrings in GHC).

Instances

IsString ByteString 
(~) * a Char => IsString [a] 

Methods

fromString :: String -> [a] #

IsString a => IsString (Identity a) 

Methods

fromString :: String -> Identity a #

IsString (Seq Char) 

Methods

fromString :: String -> Seq Char #

IsString a => IsString (Const * a b) 

Methods

fromString :: String -> Const * a b #

class Hashable a where #

The class of types that can be converted to a hash value.

Minimal implementation: hashWithSalt.

Minimal complete definition

Nothing

Instances

Hashable Bool 

Methods

hashWithSalt :: Int -> Bool -> Int #

hash :: Bool -> Int #

Hashable Char 

Methods

hashWithSalt :: Int -> Char -> Int #

hash :: Char -> Int #

Hashable Double 

Methods

hashWithSalt :: Int -> Double -> Int #

hash :: Double -> Int #

Hashable Float 

Methods

hashWithSalt :: Int -> Float -> Int #

hash :: Float -> Int #

Hashable Int 

Methods

hashWithSalt :: Int -> Int -> Int #

hash :: Int -> Int #

Hashable Int8 

Methods

hashWithSalt :: Int -> Int8 -> Int #

hash :: Int8 -> Int #

Hashable Int16 

Methods

hashWithSalt :: Int -> Int16 -> Int #

hash :: Int16 -> Int #

Hashable Int32 

Methods

hashWithSalt :: Int -> Int32 -> Int #

hash :: Int32 -> Int #

Hashable Int64 

Methods

hashWithSalt :: Int -> Int64 -> Int #

hash :: Int64 -> Int #

Hashable Integer 

Methods

hashWithSalt :: Int -> Integer -> Int #

hash :: Integer -> Int #

Hashable Ordering 

Methods

hashWithSalt :: Int -> Ordering -> Int #

hash :: Ordering -> Int #

Hashable Word 

Methods

hashWithSalt :: Int -> Word -> Int #

hash :: Word -> Int #

Hashable Word8 

Methods

hashWithSalt :: Int -> Word8 -> Int #

hash :: Word8 -> Int #

Hashable Word16 

Methods

hashWithSalt :: Int -> Word16 -> Int #

hash :: Word16 -> Int #

Hashable Word32 

Methods

hashWithSalt :: Int -> Word32 -> Int #

hash :: Word32 -> Int #

Hashable Word64 

Methods

hashWithSalt :: Int -> Word64 -> Int #

hash :: Word64 -> Int #

Hashable TypeRep 

Methods

hashWithSalt :: Int -> TypeRep -> Int #

hash :: TypeRep -> Int #

Hashable () 

Methods

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

hash :: () -> Int #

Hashable BigNat 

Methods

hashWithSalt :: Int -> BigNat -> Int #

hash :: BigNat -> Int #

Hashable Natural 

Methods

hashWithSalt :: Int -> Natural -> Int #

hash :: Natural -> Int #

Hashable Void 

Methods

hashWithSalt :: Int -> Void -> Int #

hash :: Void -> Int #

Hashable Version 

Methods

hashWithSalt :: Int -> Version -> Int #

hash :: Version -> Int #

Hashable Unique 

Methods

hashWithSalt :: Int -> Unique -> Int #

hash :: Unique -> Int #

Hashable ThreadId 

Methods

hashWithSalt :: Int -> ThreadId -> Int #

hash :: ThreadId -> Int #

Hashable ShortByteString 
Hashable ByteString 
Hashable ByteString 
Hashable Text 

Methods

hashWithSalt :: Int -> Text -> Int #

hash :: Text -> Int #

Hashable Text 

Methods

hashWithSalt :: Int -> Text -> Int #

hash :: Text -> Int #

Hashable a => Hashable [a] 

Methods

hashWithSalt :: Int -> [a] -> Int #

hash :: [a] -> Int #

Hashable a => Hashable (Maybe a) 

Methods

hashWithSalt :: Int -> Maybe a -> Int #

hash :: Maybe a -> Int #

Hashable a => Hashable (Ratio a) 

Methods

hashWithSalt :: Int -> Ratio a -> Int #

hash :: Ratio a -> Int #

Hashable a => Hashable (Min a) 

Methods

hashWithSalt :: Int -> Min a -> Int #

hash :: Min a -> Int #

Hashable a => Hashable (Max a) 

Methods

hashWithSalt :: Int -> Max a -> Int #

hash :: Max a -> Int #

Hashable a => Hashable (First a) 

Methods

hashWithSalt :: Int -> First a -> Int #

hash :: First a -> Int #

Hashable a => Hashable (Last a) 

Methods

hashWithSalt :: Int -> Last a -> Int #

hash :: Last a -> Int #

Hashable a => Hashable (WrappedMonoid a) 
Hashable a => Hashable (Option a) 

Methods

hashWithSalt :: Int -> Option a -> Int #

hash :: Option a -> Int #

Hashable a => Hashable (NonEmpty a) 

Methods

hashWithSalt :: Int -> NonEmpty a -> Int #

hash :: NonEmpty a -> Int #

Hashable (Fixed a) 

Methods

hashWithSalt :: Int -> Fixed a -> Int #

hash :: Fixed a -> Int #

Hashable (StableName a) 

Methods

hashWithSalt :: Int -> StableName a -> Int #

hash :: StableName a -> Int #

Hashable a => Hashable (HashSet a) 

Methods

hashWithSalt :: Int -> HashSet a -> Int #

hash :: HashSet a -> Int #

(Hashable a, Hashable b) => Hashable (Either a b) 

Methods

hashWithSalt :: Int -> Either a b -> Int #

hash :: Either a b -> Int #

(Hashable a1, Hashable a2) => Hashable (a1, a2) 

Methods

hashWithSalt :: Int -> (a1, a2) -> Int #

hash :: (a1, a2) -> Int #

(Hashable a, Hashable b) => Hashable (Arg a b) 

Methods

hashWithSalt :: Int -> Arg a b -> Int #

hash :: Arg a b -> Int #

(Hashable k, Hashable v) => Hashable (HashMap k v) 

Methods

hashWithSalt :: Int -> HashMap k v -> Int #

hash :: HashMap k v -> Int #

(Hashable a1, Hashable a2, Hashable a3) => Hashable (a1, a2, a3) 

Methods

hashWithSalt :: Int -> (a1, a2, a3) -> Int #

hash :: (a1, a2, a3) -> Int #

(Hashable a1, Hashable a2, Hashable a3, Hashable a4) => Hashable (a1, a2, a3, a4) 

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4) -> Int #

hash :: (a1, a2, a3, a4) -> Int #

(Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5) => Hashable (a1, a2, a3, a4, a5) 

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4, a5) -> Int #

hash :: (a1, a2, a3, a4, a5) -> Int #

(Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5, Hashable a6) => Hashable (a1, a2, a3, a4, a5, a6) 

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4, a5, a6) -> Int #

hash :: (a1, a2, a3, a4, a5, a6) -> Int #

(Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5, Hashable a6, Hashable a7) => Hashable (a1, a2, a3, a4, a5, a6, a7) 

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4, a5, a6, a7) -> Int #

hash :: (a1, a2, a3, a4, a5, a6, a7) -> Int #

class Semigroup a where #

The class of semigroups (types with an associative binary operation).

Since: 4.9.0.0

Minimal complete definition

Nothing

Instances

Semigroup Ordering 
Semigroup () 

Methods

(<>) :: () -> () -> () #

sconcat :: NonEmpty () -> () #

stimes :: Integral b => b -> () -> () #

Semigroup Void 

Methods

(<>) :: Void -> Void -> Void #

sconcat :: NonEmpty Void -> Void #

stimes :: Integral b => b -> Void -> Void #

Semigroup All 

Methods

(<>) :: All -> All -> All #

sconcat :: NonEmpty All -> All #

stimes :: Integral b => b -> All -> All #

Semigroup Any 

Methods

(<>) :: Any -> Any -> Any #

sconcat :: NonEmpty Any -> Any #

stimes :: Integral b => b -> Any -> Any #

Semigroup ByteString 
Semigroup IntSet 
Semigroup [a] 

Methods

(<>) :: [a] -> [a] -> [a] #

sconcat :: NonEmpty [a] -> [a] #

stimes :: Integral b => b -> [a] -> [a] #

Semigroup a => Semigroup (Maybe a) 

Methods

(<>) :: Maybe a -> Maybe a -> Maybe a #

sconcat :: NonEmpty (Maybe a) -> Maybe a #

stimes :: Integral b => b -> Maybe a -> Maybe a #

Semigroup a => Semigroup (Identity a) 

Methods

(<>) :: Identity a -> Identity a -> Identity a #

sconcat :: NonEmpty (Identity a) -> Identity a #

stimes :: Integral b => b -> Identity a -> Identity a #

Ord a => Semigroup (Min a) 

Methods

(<>) :: Min a -> Min a -> Min a #

sconcat :: NonEmpty (Min a) -> Min a #

stimes :: Integral b => b -> Min a -> Min a #

Ord a => Semigroup (Max a) 

Methods

(<>) :: Max a -> Max a -> Max a #

sconcat :: NonEmpty (Max a) -> Max a #

stimes :: Integral b => b -> Max a -> Max a #

Semigroup (First a) 

Methods

(<>) :: First a -> First a -> First a #

sconcat :: NonEmpty (First a) -> First a #

stimes :: Integral b => b -> First a -> First a #

Semigroup (Last a) 

Methods

(<>) :: Last a -> Last a -> Last a #

sconcat :: NonEmpty (Last a) -> Last a #

stimes :: Integral b => b -> Last a -> Last a #

Monoid m => Semigroup (WrappedMonoid m) 
Semigroup a => Semigroup (Option a) 

Methods

(<>) :: Option a -> Option a -> Option a #

sconcat :: NonEmpty (Option a) -> Option a #

stimes :: Integral b => b -> Option a -> Option a #

Semigroup (NonEmpty a) 

Methods

(<>) :: NonEmpty a -> NonEmpty a -> NonEmpty a #

sconcat :: NonEmpty (NonEmpty a) -> NonEmpty a #

stimes :: Integral b => b -> NonEmpty a -> NonEmpty a #

Semigroup a => Semigroup (Dual a) 

Methods

(<>) :: Dual a -> Dual a -> Dual a #

sconcat :: NonEmpty (Dual a) -> Dual a #

stimes :: Integral b => b -> Dual a -> Dual a #

Semigroup (Endo a) 

Methods

(<>) :: Endo a -> Endo a -> Endo a #

sconcat :: NonEmpty (Endo a) -> Endo a #

stimes :: Integral b => b -> Endo a -> Endo a #

Num a => Semigroup (Sum a) 

Methods

(<>) :: Sum a -> Sum a -> Sum a #

sconcat :: NonEmpty (Sum a) -> Sum a #

stimes :: Integral b => b -> Sum a -> Sum a #

Num a => Semigroup (Product a) 

Methods

(<>) :: Product a -> Product a -> Product a #

sconcat :: NonEmpty (Product a) -> Product a #

stimes :: Integral b => b -> Product a -> Product a #

Semigroup (First a) 

Methods

(<>) :: First a -> First a -> First a #

sconcat :: NonEmpty (First a) -> First a #

stimes :: Integral b => b -> First a -> First a #

Semigroup (Last a) 

Methods

(<>) :: Last a -> Last a -> Last a #

sconcat :: NonEmpty (Last a) -> Last a #

stimes :: Integral b => b -> Last a -> Last a #

Semigroup (Seq a) 

Methods

(<>) :: Seq a -> Seq a -> Seq a #

sconcat :: NonEmpty (Seq a) -> Seq a #

stimes :: Integral b => b -> Seq a -> Seq a #

Semigroup (IntMap a) 

Methods

(<>) :: IntMap a -> IntMap a -> IntMap a #

sconcat :: NonEmpty (IntMap a) -> IntMap a #

stimes :: Integral b => b -> IntMap a -> IntMap a #

Ord a => Semigroup (Set a) 

Methods

(<>) :: Set a -> Set a -> Set a #

sconcat :: NonEmpty (Set a) -> Set a #

stimes :: Integral b => b -> Set a -> Set a #

(Hashable a, Eq a) => Semigroup (HashSet a) 

Methods

(<>) :: HashSet a -> HashSet a -> HashSet a #

sconcat :: NonEmpty (HashSet a) -> HashSet a #

stimes :: Integral b => b -> HashSet a -> HashSet a #

Semigroup b => Semigroup (a -> b) 

Methods

(<>) :: (a -> b) -> (a -> b) -> a -> b #

sconcat :: NonEmpty (a -> b) -> a -> b #

stimes :: Integral b => b -> (a -> b) -> a -> b #

Semigroup (Either a b) 

Methods

(<>) :: Either a b -> Either a b -> Either a b #

sconcat :: NonEmpty (Either a b) -> Either a b #

stimes :: Integral b => b -> Either a b -> Either a b #

(Semigroup a, Semigroup b) => Semigroup (a, b) 

Methods

(<>) :: (a, b) -> (a, b) -> (a, b) #

sconcat :: NonEmpty (a, b) -> (a, b) #

stimes :: Integral b => b -> (a, b) -> (a, b) #

Semigroup (Proxy k s) 

Methods

(<>) :: Proxy k s -> Proxy k s -> Proxy k s #

sconcat :: NonEmpty (Proxy k s) -> Proxy k s #

stimes :: Integral b => b -> Proxy k s -> Proxy k s #

Ord k => Semigroup (Map k v) 

Methods

(<>) :: Map k v -> Map k v -> Map k v #

sconcat :: NonEmpty (Map k v) -> Map k v #

stimes :: Integral b => b -> Map k v -> Map k v #

(Eq k, Hashable k) => Semigroup (HashMap k v) 

Methods

(<>) :: HashMap k v -> HashMap k v -> HashMap k v #

sconcat :: NonEmpty (HashMap k v) -> HashMap k v #

stimes :: Integral b => b -> HashMap k v -> HashMap k v #

(Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c) 

Methods

(<>) :: (a, b, c) -> (a, b, c) -> (a, b, c) #

sconcat :: NonEmpty (a, b, c) -> (a, b, c) #

stimes :: Integral b => b -> (a, b, c) -> (a, b, c) #

Semigroup a => Semigroup (Const k a b) 

Methods

(<>) :: Const k a b -> Const k a b -> Const k a b #

sconcat :: NonEmpty (Const k a b) -> Const k a b #

stimes :: Integral b => b -> Const k a b -> Const k a b #

Alternative f => Semigroup (Alt * f a) 

Methods

(<>) :: Alt * f a -> Alt * f a -> Alt * f a #

sconcat :: NonEmpty (Alt * f a) -> Alt * f a #

stimes :: Integral b => b -> Alt * f a -> Alt * f a #

(Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d) 

Methods

(<>) :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

sconcat :: NonEmpty (a, b, c, d) -> (a, b, c, d) #

stimes :: Integral b => b -> (a, b, c, d) -> (a, b, c, d) #

(Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e) 

Methods

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

sconcat :: NonEmpty (a, b, c, d, e) -> (a, b, c, d, e) #

stimes :: Integral b => b -> (a, b, c, d, e) -> (a, b, c, d, e) #

class Monoid a where #

The class of monoids (types with an associative binary operation that + has an identity). Instances should satisfy the following laws:

  • mappend mempty x = x
  • mappend x mempty = x
  • mappend x (mappend y z) = mappend (mappend x y) z
  • mconcat = foldr mappend mempty

The method names refer to the monoid of lists under concatenation, + but there are many other instances.

Some types can be viewed as a monoid in more than one way, + e.g. both addition and multiplication on numbers. + In such cases we often define newtypes and make those instances + of Monoid, e.g. Sum and Product.

Minimal complete definition

mempty, mappend

Instances

Monoid Ordering 
Monoid () 

Methods

mempty :: () #

mappend :: () -> () -> () #

mconcat :: [()] -> () #

Monoid All 

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

Monoid Any 

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

Monoid ByteString 
Monoid IntSet 
Monoid [a] 

Methods

mempty :: [a] #

mappend :: [a] -> [a] -> [a] #

mconcat :: [[a]] -> [a] #

Monoid a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to + http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be + turned into a monoid simply by adjoining an element e not in S + and defining e*e = e and e*s = s = s*e for all s ∈ S." Since + there is no "Semigroup" typeclass providing just mappend, we + use Monoid instead.

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

mconcat :: [Maybe a] -> Maybe a #

Monoid a => Monoid (IO a) 

Methods

mempty :: IO a #

mappend :: IO a -> IO a -> IO a #

mconcat :: [IO a] -> IO a #

Ord a => Monoid (Max a) 

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

mconcat :: [Max a] -> Max a #

Ord a => Monoid (Min a) 

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

mconcat :: [Min a] -> Min a #

Monoid a => Monoid (Identity a) 

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

mconcat :: [Identity a] -> Identity a #

(Ord a, Bounded a) => Monoid (Min a) 

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

mconcat :: [Min a] -> Min a #

(Ord a, Bounded a) => Monoid (Max a) 

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

mconcat :: [Max a] -> Max a #

Monoid m => Monoid (WrappedMonoid m) 
Semigroup a => Monoid (Option a) 

Methods

mempty :: Option a #

mappend :: Option a -> Option a -> Option a #

mconcat :: [Option a] -> Option a #

Monoid a => Monoid (Dual a) 

Methods

mempty :: Dual a #

mappend :: Dual a -> Dual a -> Dual a #

mconcat :: [Dual a] -> Dual a #

Monoid (Endo a) 

Methods

mempty :: Endo a #

mappend :: Endo a -> Endo a -> Endo a #

mconcat :: [Endo a] -> Endo a #

Num a => Monoid (Sum a) 

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

mconcat :: [Sum a] -> Sum a #

Num a => Monoid (Product a) 

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

mconcat :: [Product a] -> Product a #

Monoid (First a) 

Methods

mempty :: First a #

mappend :: First a -> First a -> First a #

mconcat :: [First a] -> First a #

Monoid (Last a) 

Methods

mempty :: Last a #

mappend :: Last a -> Last a -> Last a #

mconcat :: [Last a] -> Last a #

Monoid (Seq a) 

Methods

mempty :: Seq a #

mappend :: Seq a -> Seq a -> Seq a #

mconcat :: [Seq a] -> Seq a #

Monoid (IntMap a) 

Methods

mempty :: IntMap a #

mappend :: IntMap a -> IntMap a -> IntMap a #

mconcat :: [IntMap a] -> IntMap a #

Ord a => Monoid (Set a) 

Methods

mempty :: Set a #

mappend :: Set a -> Set a -> Set a #

mconcat :: [Set a] -> Set a #

(Hashable a, Eq a) => Monoid (HashSet a) 

Methods

mempty :: HashSet a #

mappend :: HashSet a -> HashSet a -> HashSet a #

mconcat :: [HashSet a] -> HashSet a #

Monoid b => Monoid (a -> b) 

Methods

mempty :: a -> b #

mappend :: (a -> b) -> (a -> b) -> a -> b #

mconcat :: [a -> b] -> a -> b #

(Monoid a, Monoid b) => Monoid (a, b) 

Methods

mempty :: (a, b) #

mappend :: (a, b) -> (a, b) -> (a, b) #

mconcat :: [(a, b)] -> (a, b) #

Monoid (Proxy k s) 

Methods

mempty :: Proxy k s #

mappend :: Proxy k s -> Proxy k s -> Proxy k s #

mconcat :: [Proxy k s] -> Proxy k s #

Ord k => Monoid (Map k v) 

Methods

mempty :: Map k v #

mappend :: Map k v -> Map k v -> Map k v #

mconcat :: [Map k v] -> Map k v #

(Eq k, Hashable k) => Monoid (HashMap k v) 

Methods

mempty :: HashMap k v #

mappend :: HashMap k v -> HashMap k v -> HashMap k v #

mconcat :: [HashMap k v] -> HashMap k v #

(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) 

Methods

mempty :: (a, b, c) #

mappend :: (a, b, c) -> (a, b, c) -> (a, b, c) #

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

Monoid a => Monoid (Const k a b) 

Methods

mempty :: Const k a b #

mappend :: Const k a b -> Const k a b -> Const k a b #

mconcat :: [Const k a b] -> Const k a b #

Alternative f => Monoid (Alt * f a) 

Methods

mempty :: Alt * f a #

mappend :: Alt * f a -> Alt * f a -> Alt * f a #

mconcat :: [Alt * f a] -> Alt * f a #

(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) 

Methods

mempty :: (a, b, c, d) #

mappend :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

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

(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) 

Methods

mempty :: (a, b, c, d, e) #

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

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

Numeric

class Num a where #

Basic numeric class.

Minimal complete definition

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

Instances

Num Int 

Methods

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

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

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

negate :: Int -> Int #

abs :: Int -> Int #

signum :: Int -> Int #

fromInteger :: Integer -> Int #

Num Int8 

Methods

(+) :: Int8 -> Int8 -> Int8 #

(-) :: Int8 -> Int8 -> Int8 #

(*) :: Int8 -> Int8 -> Int8 #

negate :: Int8 -> Int8 #

abs :: Int8 -> Int8 #

signum :: Int8 -> Int8 #

fromInteger :: Integer -> Int8 #

Num Int16 
Num Int32 
Num Int64 
Num Integer 
Num Word 

Methods

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

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

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

negate :: Word -> Word #

abs :: Word -> Word #

signum :: Word -> Word #

fromInteger :: Integer -> Word #

Num Word8 
Num Word16 
Num Word32 
Num Word64 
Num CodePoint 

Methods

(+) :: CodePoint -> CodePoint -> CodePoint #

(-) :: CodePoint -> CodePoint -> CodePoint #

(*) :: CodePoint -> CodePoint -> CodePoint #

negate :: CodePoint -> CodePoint #

abs :: CodePoint -> CodePoint #

signum :: CodePoint -> CodePoint #

fromInteger :: Integer -> CodePoint #

Num DecoderState 

Methods

(+) :: DecoderState -> DecoderState -> DecoderState #

(-) :: DecoderState -> DecoderState -> DecoderState #

(*) :: DecoderState -> DecoderState -> DecoderState #

negate :: DecoderState -> DecoderState #

abs :: DecoderState -> DecoderState #

signum :: DecoderState -> DecoderState #

fromInteger :: Integer -> DecoderState #

Integral a => Num (Ratio a) 

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 #

Num a => Num (Identity a) 
Num a => Num (Min a) 

Methods

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

(-) :: Min a -> Min a -> Min a #

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

negate :: Min a -> Min a #

abs :: Min a -> Min a #

signum :: Min a -> Min a #

fromInteger :: Integer -> Min a #

Num a => Num (Max a) 

Methods

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

(-) :: Max a -> Max a -> Max a #

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

negate :: Max a -> Max a #

abs :: Max a -> Max a #

signum :: Max a -> Max a #

fromInteger :: Integer -> Max a #

RealFloat a => Num (Complex a) 

Methods

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

(-) :: Complex a -> Complex a -> Complex a #

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

negate :: Complex a -> Complex a #

abs :: Complex a -> Complex a #

signum :: Complex a -> Complex a #

fromInteger :: Integer -> Complex a #

Num a => Num (Sum a) 

Methods

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

(-) :: Sum a -> Sum a -> Sum a #

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

negate :: Sum a -> Sum a #

abs :: Sum a -> Sum a #

signum :: Sum a -> Sum a #

fromInteger :: Integer -> Sum a #

Num a => Num (Product a) 

Methods

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

(-) :: Product a -> Product a -> Product a #

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

negate :: Product a -> Product a #

abs :: Product a -> Product a #

signum :: Product a -> Product a #

fromInteger :: Integer -> Product a #

Num a => Num (Const k a b) 

Methods

(+) :: Const k a b -> Const k a b -> Const k a b #

(-) :: Const k a b -> Const k a b -> Const k a b #

(*) :: Const k a b -> Const k a b -> Const k a b #

negate :: Const k a b -> Const k a b #

abs :: Const k a b -> Const k a b #

signum :: Const k a b -> Const k a b #

fromInteger :: Integer -> Const k a b #

Num (f a) => Num (Alt k f a) 

Methods

(+) :: Alt k f a -> Alt k f a -> Alt k f a #

(-) :: Alt k f a -> Alt k f a -> Alt k f a #

(*) :: Alt k f a -> Alt k f a -> Alt k f a #

negate :: Alt k f a -> Alt k f a #

abs :: Alt k f a -> Alt k f a #

signum :: Alt k f a -> Alt k f a #

fromInteger :: Integer -> Alt k f a #

class (Num a, Ord a) => Real a where #

Instances

Real Int 

Methods

toRational :: Int -> Rational #

Real Int8 

Methods

toRational :: Int8 -> Rational #

Real Int16 

Methods

toRational :: Int16 -> Rational #

Real Int32 

Methods

toRational :: Int32 -> Rational #

Real Int64 

Methods

toRational :: Int64 -> Rational #

Real Integer 
Real Word 

Methods

toRational :: Word -> Rational #

Real Word8 

Methods

toRational :: Word8 -> Rational #

Real Word16 
Real Word32 
Real Word64 
Integral a => Real (Ratio a) 

Methods

toRational :: Ratio a -> Rational #

Real a => Real (Identity a) 

Methods

toRational :: Identity a -> Rational #

Real a => Real (Const k a b) 

Methods

toRational :: Const k a b -> Rational #

class (Real a, Enum a) => Integral a where #

Integral numbers, supporting integer division.

Minimal complete definition

quotRem, toInteger

Instances

Integral Int 

Methods

quot :: Int -> Int -> Int #

rem :: Int -> Int -> Int #

div :: Int -> Int -> Int #

mod :: Int -> Int -> Int #

quotRem :: Int -> Int -> (Int, Int) #

divMod :: Int -> Int -> (Int, Int) #

toInteger :: Int -> Integer #

Integral Int8 

Methods

quot :: Int8 -> Int8 -> Int8 #

rem :: Int8 -> Int8 -> Int8 #

div :: Int8 -> Int8 -> Int8 #

mod :: Int8 -> Int8 -> Int8 #

quotRem :: Int8 -> Int8 -> (Int8, Int8) #

divMod :: Int8 -> Int8 -> (Int8, Int8) #

toInteger :: Int8 -> Integer #

Integral Int16 
Integral Int32 
Integral Int64 
Integral Integer 
Integral Word 

Methods

quot :: Word -> Word -> Word #

rem :: Word -> Word -> Word #

div :: Word -> Word -> Word #

mod :: Word -> Word -> Word #

quotRem :: Word -> Word -> (Word, Word) #

divMod :: Word -> Word -> (Word, Word) #

toInteger :: Word -> Integer #

Integral Word8 
Integral Word16 
Integral Word32 
Integral Word64 
Integral a => Integral (Identity a) 
Integral a => Integral (Const k a b) 

Methods

quot :: Const k a b -> Const k a b -> Const k a b #

rem :: Const k a b -> Const k a b -> Const k a b #

div :: Const k a b -> Const k a b -> Const k a b #

mod :: Const k a b -> Const k a b -> Const k a b #

quotRem :: Const k a b -> Const k a b -> (Const k a b, Const k a b) #

divMod :: Const k a b -> Const k a b -> (Const k a b, Const k a b) #

toInteger :: Const k a b -> Integer #

class Num a => Fractional a where #

Fractional numbers, supporting real division.

Minimal complete definition

fromRational, (recip | (/))

Instances

Integral a => Fractional (Ratio a) 

Methods

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

recip :: Ratio a -> Ratio a #

fromRational :: Rational -> Ratio a #

Fractional a => Fractional (Identity a) 
RealFloat a => Fractional (Complex a) 

Methods

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

recip :: Complex a -> Complex a #

fromRational :: Rational -> Complex a #

Fractional a => Fractional (Const k a b) 

Methods

(/) :: Const k a b -> Const k a b -> Const k a b #

recip :: Const k a b -> Const k a b #

fromRational :: Rational -> Const k a b #

class Fractional a => Floating a where #

Trigonometric and hyperbolic functions and related functions.

Minimal complete definition

pi, exp, log, sin, cos, asin, acos, atan, sinh, cosh, asinh, acosh, atanh

Instances

Floating Double 
Floating Float 
Floating a => Floating (Identity a) 
RealFloat a => Floating (Complex a) 

Methods

pi :: Complex a #

exp :: Complex a -> Complex a #

log :: Complex a -> Complex a #

sqrt :: Complex a -> Complex a #

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

logBase :: Complex a -> Complex a -> Complex a #

sin :: Complex a -> Complex a #

cos :: Complex a -> Complex a #

tan :: Complex a -> Complex a #

asin :: Complex a -> Complex a #

acos :: Complex a -> Complex a #

atan :: Complex a -> Complex a #

sinh :: Complex a -> Complex a #

cosh :: Complex a -> Complex a #

tanh :: Complex a -> Complex a #

asinh :: Complex a -> Complex a #

acosh :: Complex a -> Complex a #

atanh :: Complex a -> Complex a #

log1p :: Complex a -> Complex a #

expm1 :: Complex a -> Complex a #

log1pexp :: Complex a -> Complex a #

log1mexp :: Complex a -> Complex a #

Floating a => Floating (Const k a b) 

Methods

pi :: Const k a b #

exp :: Const k a b -> Const k a b #

log :: Const k a b -> Const k a b #

sqrt :: Const k a b -> Const k a b #

(**) :: Const k a b -> Const k a b -> Const k a b #

logBase :: Const k a b -> Const k a b -> Const k a b #

sin :: Const k a b -> Const k a b #

cos :: Const k a b -> Const k a b #

tan :: Const k a b -> Const k a b #

asin :: Const k a b -> Const k a b #

acos :: Const k a b -> Const k a b #

atan :: Const k a b -> Const k a b #

sinh :: Const k a b -> Const k a b #

cosh :: Const k a b -> Const k a b #

tanh :: Const k a b -> Const k a b #

asinh :: Const k a b -> Const k a b #

acosh :: Const k a b -> Const k a b #

atanh :: Const k a b -> Const k a b #

log1p :: Const k a b -> Const k a b #

expm1 :: Const k a b -> Const k a b #

log1pexp :: Const k a b -> Const k a b #

log1mexp :: Const k a b -> Const k a b #

class (Real a, Fractional a) => RealFrac a where #

Extracting components of fractions.

Minimal complete definition

properFraction

Instances

Integral a => RealFrac (Ratio a) 

Methods

properFraction :: Integral b => Ratio a -> (b, Ratio a) #

truncate :: Integral b => Ratio a -> b #

round :: Integral b => Ratio a -> b #

ceiling :: Integral b => Ratio a -> b #

floor :: Integral b => Ratio a -> b #

RealFrac a => RealFrac (Identity a) 

Methods

properFraction :: Integral b => Identity a -> (b, Identity a) #

truncate :: Integral b => Identity a -> b #

round :: Integral b => Identity a -> b #

ceiling :: Integral b => Identity a -> b #

floor :: Integral b => Identity a -> b #

RealFrac a => RealFrac (Const k a b) 

Methods

properFraction :: Integral b => Const k a b -> (b, Const k a b) #

truncate :: Integral b => Const k a b -> b #

round :: Integral b => Const k a b -> b #

ceiling :: Integral b => Const k a b -> b #

floor :: Integral b => Const k a b -> b #

class (RealFrac a, Floating a) => RealFloat a where #

Efficient, machine-independent access to the components of a + floating-point number.

Instances

RealFloat Double 
RealFloat Float 
RealFloat a => RealFloat (Identity a) 
RealFloat a => RealFloat (Const k a b) 

Methods

floatRadix :: Const k a b -> Integer #

floatDigits :: Const k a b -> Int #

floatRange :: Const k a b -> (Int, Int) #

decodeFloat :: Const k a b -> (Integer, Int) #

encodeFloat :: Integer -> Int -> Const k a b #

exponent :: Const k a b -> Int #

significand :: Const k a b -> Const k a b #

scaleFloat :: Int -> Const k a b -> Const k a b #

isNaN :: Const k a b -> Bool #

isInfinite :: Const k a b -> Bool #

isDenormalized :: Const k a b -> Bool #

isNegativeZero :: Const k a b -> Bool #

isIEEE :: Const k a b -> Bool #

atan2 :: Const k a b -> Const k a b -> Const k a b #

Functions

($) :: (a -> b) -> a -> b infixr 0 #

Application operator. This operator is redundant, since ordinary + application (f x) means the same as (f $ x). However, $ has + low, right-associative binding precedence, so it sometimes allows + parentheses to be omitted; for example:

    f $ g $ h x  =  f (g (h x))

It is also useful in higher-order situations, such as map ($ 0) xs, + or zipWith ($) fs xs.

(&) :: a -> (a -> b) -> b infixl 1 #

& is a reverse application operator. This provides notational + convenience. Its precedence is one higher than that of the forward + application operator $, which allows & to be nested in $.

Since: 4.8.0.0

($!) :: (a -> b) -> a -> b infixr 0 #

Strict (call-by-value) application operator. It takes a function and an + argument, evaluates the argument to weak head normal form (WHNF), then calls + the function with that value.

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

Boolean "and"

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

Boolean "or"

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

Function composition.

not :: Bool -> Bool #

Boolean "not"

otherwise :: Bool #

otherwise is defined as the value True. It helps to make + guards more readable. eg.

 f x | x < 0     = ...
+     | otherwise = ...

fst :: (a, b) -> a #

Extract the first component of a pair.

snd :: (a, b) -> b #

Extract the second component of a pair.

id :: a -> a #

Identity function.

maybe :: b -> (a -> b) -> Maybe a -> b #

The maybe function takes a default value, a function, and a Maybe + value. If the Maybe value is Nothing, the function returns the + default value. Otherwise, it applies the function to the value inside + the Just and returns the result.

Examples

Basic usage:

>>> maybe False odd (Just 3)
+True
+
>>> maybe False odd Nothing
+False
+

Read an integer from a string using readMaybe. If we succeed, + return twice the integer; that is, apply (*2) to it. If instead + we fail to parse an integer, return 0 by default:

>>> import Text.Read ( readMaybe )
+>>> maybe 0 (*2) (readMaybe "5")
+10
+>>> maybe 0 (*2) (readMaybe "")
+0
+

Apply show to a Maybe Int. If we have Just n, we want to show + the underlying Int n. But if we have Nothing, we return the + empty string instead of (for example) "Nothing":

>>> maybe "" show (Just 5)
+"5"
+>>> maybe "" show Nothing
+""
+

either :: (a -> c) -> (b -> c) -> Either a b -> c #

Case analysis for the Either type. + If the value is Left a, apply the first function to a; + if it is Right b, apply the second function to b.

Examples

We create two values of type Either String Int, one using the + Left constructor and another using the Right constructor. Then + we apply "either" the length function (if we have a String) + or the "times-two" function (if we have an Int):

>>> let s = Left "foo" :: Either String Int
+>>> let n = Right 3 :: Either String Int
+>>> either length (*2) s
+3
+>>> either length (*2) n
+6
+

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

flip f takes its (first) two arguments in the reverse order of f.

const :: a -> b -> a #

const x is a unary function which evaluates to x for all inputs.

For instance,

>>> map (const 42) [0..3]
+[42,42,42,42]
+

odd :: Integral a => a -> Bool #

even :: Integral a => a -> Bool #

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

uncurry converts a curried function to a function on pairs.

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

curry converts an uncurried function to a curried function.

asTypeOf :: a -> a -> a #

asTypeOf is a type-restricted version of const. It is usually + used as an infix operator, and its typing forces its first argument + (which is usually overloaded) to have the same type as the second.

seq :: a -> b -> b #

The value of seq a b is bottom if a is bottom, and + otherwise equal to b. seq is usually introduced to + improve performance by avoiding unneeded laziness.

A note on evaluation order: the expression seq a b does + not guarantee that a will be evaluated before b. + The only guarantee given by seq is that the both a + and b will be evaluated before seq returns a value. + In particular, this means that b may be evaluated before + a. If you need to guarantee a specific order of evaluation, + you must use the function pseq from the "parallel" package.

fix :: (a -> a) -> a #

fix f is the least fixed point of the function f, + i.e. the least defined x such that f x = x.

Numeric

(^) :: (Num a, Integral b) => a -> b -> a infixr 8 #

raise a number to a non-negative integral power

(^^) :: (Fractional a, Integral b) => a -> b -> a infixr 8 #

raise a number to an integral power

subtract :: Num a => a -> a -> a #

the same as flip (-).

Because - is treated specially in the Haskell grammar, + (- e) is not a section, but an application of prefix negation. + However, (subtract exp) is equivalent to the disallowed section.

fromIntegral :: (Integral a, Num b) => a -> b #

general coercion from integral types

realToFrac :: (Real a, Fractional b) => a -> b #

general coercion to fractional types

Foldable

sum :: (Foldable f, Num a) => f a -> a Source #

Get the sum of the elements in a Foldable.

This is not the same as the function from Foldable; instead, + this function uses a strict left fold.

Since: 0.1.0.0

product :: (Foldable f, Num a) => f a -> a Source #

Get the product of the elements in a Foldable.

This is not the same as the function from Foldable; instead, + this function uses a strict left fold.

Since: 0.1.0.0

foldrM :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m b #

Monadic fold over the elements of a structure, + associating to the right, i.e. from right to left.

foldlM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b #

Monadic fold over the elements of a structure, + associating to the left, i.e. from left to right.

traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f () #

Map each element of a structure to an action, evaluate these + actions from left to right, and ignore the results. For a version + that doesn't ignore the results see traverse.

for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f () #

for_ is traverse_ with its arguments flipped. For a version + that doesn't ignore the results see for.

>>> for_ [1..4] print
+1
+2
+3
+4
+

sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f () #

Evaluate each action in the structure from left to right, and + ignore the results. For a version that doesn't ignore the results + see sequenceA.

asum :: (Foldable t, Alternative f) => t (f a) -> f a #

The sum of a collection of actions, generalizing concat.

mapM_ :: (Applicative m, Foldable f) => (a -> m b) -> f a -> m () Source #

Synonym for traverse_; different from base to generalize to + Applicative.

Since: 0.1.0.0

forM_ :: (Applicative m, Foldable f) => f a -> (a -> m b) -> m () Source #

Flipped version of mapM_.

Since: 0.1.0.0

sequence_ :: (Applicative m, Foldable f) => f (m a) -> m () Source #

Synonym for sequence_; different from base to generalize to + Applicative.

Since: 0.1.0.0

msum :: (Foldable t, MonadPlus m) => t (m a) -> m a #

The sum of a collection of actions, generalizing concat. + As of base 4.8.0.0, msum is just asum, specialized to MonadPlus.

concat :: Foldable t => t [a] -> [a] #

The concatenation of all the elements of a container of lists.

concatMap :: Foldable t => (a -> [b]) -> t a -> [b] #

Map a function over all the elements of a container and concatenate + the resulting lists.

and :: Foldable t => t Bool -> Bool #

and returns the conjunction of a container of Bools. For the + result to be True, the container must be finite; False, however, + results from a False value finitely far from the left end.

or :: Foldable t => t Bool -> Bool #

or returns the disjunction of a container of Bools. For the + result to be False, the container must be finite; True, however, + results from a True value finitely far from the left end.

any :: Foldable t => (a -> Bool) -> t a -> Bool #

Determines whether any element of the structure satisfies the predicate.

all :: Foldable t => (a -> Bool) -> t a -> Bool #

Determines whether all elements of the structure satisfy the predicate.

notElem :: (Foldable t, Eq a) => a -> t a -> Bool infix 4 #

notElem is the negation of elem.

find :: Foldable t => (a -> Bool) -> t a -> Maybe a #

The find function takes a predicate and a structure and returns + the leftmost element of the structure matching the predicate, or + Nothing if there is no such element.

Traversable

mapM :: (Applicative m, Traversable t) => (a -> m b) -> t a -> m (t b) Source #

Synonym for traverse; different from base to generalize to + Applicative.

Since: 0.1.0.0

sequence :: (Applicative m, Traversable t) => t (m a) -> m (t a) Source #

Synonym for sequenceA; different from base to generalize to + Applicative.

Since: 0.1.0.0

for :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b) #

for is traverse with its arguments flipped. For a version + that ignores the results see for_.

forM :: (Applicative m, Traversable t) => t a -> (a -> m b) -> m (t b) Source #

Flipped version of mapM.

Since: 0.1.0.0

mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) #

The mapAccumL function behaves like a combination of fmap + and foldl; it applies a function to each element of a structure, + passing an accumulating parameter from left to right, and returning + a final value of this accumulator together with the new structure.

mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) #

The mapAccumR function behaves like a combination of fmap + and foldr; it applies a function to each element of a structure, + passing an accumulating parameter from right to left, and returning + a final value of this accumulator together with the new structure.

Functor

($>) :: Functor f => f a -> b -> f b infixl 4 #

Flipped version of <$.

Examples

Replace the contents of a Maybe Int with a constant String:

>>> Nothing $> "foo"
+Nothing
+>>> Just 90210 $> "foo"
+Just "foo"
+

Replace the contents of an Either Int Int with a constant + String, resulting in an Either Int String:

>>> Left 8675309 $> "foo"
+Left 8675309
+>>> Right 8675309 $> "foo"
+Right "foo"
+

Replace each element of a list with a constant String:

>>> [1,2,3] $> "foo"
+["foo","foo","foo"]
+

Replace the second element of a pair with a constant String:

>>> (1,2) $> "foo"
+(1,"foo")
+

Since: 4.7.0.0

(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 #

An infix synonym for fmap.

The name of this operator is an allusion to $. + Note the similarities between their types:

 ($)  ::              (a -> b) ->   a ->   b
+(<$>) :: Functor f => (a -> b) -> f a -> f b

Whereas $ is function application, <$> is function + application lifted over a Functor.

Examples

Convert from a Maybe Int to a Maybe String using show:

>>> show <$> Nothing
+Nothing
+>>> show <$> Just 3
+Just "3"
+

Convert from an Either Int Int to an Either Int + String using show:

>>> show <$> Left 17
+Left 17
+>>> show <$> Right 17
+Right "17"
+

Double each element of a list:

>>> (*2) <$> [1,2,3]
+[2,4,6]
+

Apply even to the second element of a pair:

>>> even <$> (2,2)
+(2,True)
+

void :: Functor f => f a -> f () #

void value discards or ignores the result of evaluation, such + as the return value of an IO action.

Examples

Replace the contents of a Maybe Int with unit:

>>> void Nothing
+Nothing
+>>> void (Just 3)
+Just ()
+

Replace the contents of an Either Int Int with unit, + resulting in an Either Int '()':

>>> void (Left 8675309)
+Left 8675309
+>>> void (Right 8675309)
+Right ()
+

Replace every element of a list with unit:

>>> void [1,2,3]
+[(),(),()]
+

Replace the second element of a pair with unit:

>>> void (1,2)
+(1,())
+

Discard the result of an IO action:

>>> mapM print [1,2]
+1
+2
+[(),()]
+>>> void $ mapM print [1,2]
+1
+2
+

Applicative

liftA :: Applicative f => (a -> b) -> f a -> f b #

Lift a function to actions. + This function may be used as a value for fmap in a Functor instance.

liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c #

Lift a binary function to actions.

liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d #

Lift a ternary function to actions.

Alternative

optional :: Alternative f => f a -> f (Maybe a) #

One or none.

Monad

(=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 #

Same as >>=, but with the arguments interchanged.

(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 #

Left-to-right Kleisli composition of monads.

(<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c infixr 1 #

Right-to-left Kleisli composition of monads. (>=>), with the arguments flipped.

Note how this operator resembles function composition (.):

(.)   ::            (b ->   c) -> (a ->   b) -> a ->   c
+(<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c

forever :: Applicative f => f a -> f b #

forever act repeats the action infinitely.

join :: Monad m => m (m a) -> m a #

The join function is the conventional monad join operator. It + is used to remove one level of monadic structure, projecting its + bound argument into the outer level.

foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b #

The foldM function is analogous to foldl, except that its result is +encapsulated in a monad. Note that foldM works from left-to-right over +the list arguments. This could be an issue where (>>) and the `folded +function' are not commutative.

      foldM f a1 [x1, x2, ..., xm]

==

      do
+        a2 <- f a1 x1
+        a3 <- f a2 x2
+        ...
+        f am xm

If right-to-left evaluation is required, the input list should be reversed.

Note: foldM is the same as foldlM

foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m () #

Like foldM, but discards the result.

replicateM_ :: Applicative m => Int -> m a -> m () #

Like replicateM, but discards the result.

guard :: Alternative f => Bool -> f () #

guard b is pure () if b is True, + and empty if b is False.

when :: Applicative f => Bool -> f () -> f () #

Conditional execution of Applicative expressions. For example,

when debug (putStrLn "Debugging")

will output the string Debugging if the Boolean value debug + is True, and otherwise do nothing.

unless :: Applicative f => Bool -> f () -> f () #

The reverse of when.

liftM :: Monad m => (a1 -> r) -> m a1 -> m r #

Promote a function to a monad.

ap :: Monad m => m (a -> b) -> m a -> m b #

In many situations, the liftM operations can be replaced by uses of +ap, which promotes function application.

      return f `ap` x1 `ap` ... `ap` xn

is equivalent to

      liftMn f x1 x2 ... xn

(<$!>) :: Monad m => (a -> b) -> m a -> m b infixl 4 #

Strict version of <$>.

Since: 4.8.0.0

Concurrent

threadDelay :: Int -> IO () #

Suspends the current thread for a given number of microseconds + (GHC only).

There is no guarantee that the thread will be rescheduled promptly + when the delay has expired, but the thread will never continue to + run earlier than specified.

data MVar a :: * -> * #

An MVar (pronounced "em-var") is a synchronising variable, used +for communication between concurrent threads. It can be thought of +as a a box, which may be empty or full.

Instances

Eq (MVar a) 

Methods

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

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

NFData (MVar a)

NOTE: Only strict in the reference and not the referenced value.

Since: 1.4.2.0

Methods

rnf :: MVar a -> () #

newEmptyMVar :: IO (MVar a) #

Create an MVar which is initially empty.

newMVar :: a -> IO (MVar a) #

Create an MVar which contains the supplied value.

takeMVar :: MVar a -> IO a #

Return the contents of the MVar. If the MVar is currently + empty, takeMVar will wait until it is full. After a takeMVar, + the MVar is left empty.

There are two further important properties of takeMVar:

  • takeMVar is single-wakeup. That is, if there are multiple + threads blocked in takeMVar, and the MVar becomes full, + only one thread will be woken up. The runtime guarantees that + the woken thread completes its takeMVar operation.
  • When multiple threads are blocked on an MVar, they are + woken up in FIFO order. This is useful for providing + fairness properties of abstractions built using MVars.

putMVar :: MVar a -> a -> IO () #

Put a value into an MVar. If the MVar is currently full, + putMVar will wait until it becomes empty.

There are two further important properties of putMVar:

  • putMVar is single-wakeup. That is, if there are multiple + threads blocked in putMVar, and the MVar becomes empty, + only one thread will be woken up. The runtime guarantees that + the woken thread completes its putMVar operation.
  • When multiple threads are blocked on an MVar, they are + woken up in FIFO order. This is useful for providing + fairness properties of abstractions built using MVars.

readMVar :: MVar a -> IO a #

Atomically read the contents of an MVar. If the MVar is + currently empty, readMVar will wait until its full. + readMVar is guaranteed to receive the next putMVar.

readMVar is multiple-wakeup, so when multiple readers are + blocked on an MVar, all of them are woken up at the same time.

Compatibility note: Prior to base 4.7, readMVar was a combination + of takeMVar and putMVar. This mean that in the presence of + other threads attempting to putMVar, readMVar could block. + Furthermore, readMVar would not receive the next putMVar if there + was already a pending thread blocked on takeMVar. The old behavior + can be recovered by implementing 'readMVar as follows:

 readMVar :: MVar a -> IO a
+ readMVar m =
+   mask_ $ do
+     a <- takeMVar m
+     putMVar m a
+     return a
+

swapMVar :: MVar a -> a -> IO a #

Take a value from an MVar, put a new value into the MVar and + return the value taken. This function is atomic only if there are + no other producers for this MVar.

tryTakeMVar :: MVar a -> IO (Maybe a) #

A non-blocking version of takeMVar. The tryTakeMVar function + returns immediately, with Nothing if the MVar was empty, or + Just a if the MVar was full with contents a. After tryTakeMVar, + the MVar is left empty.

tryPutMVar :: MVar a -> a -> IO Bool #

A non-blocking version of putMVar. The tryPutMVar function + attempts to put the value a into the MVar, returning True if + it was successful, or False otherwise.

isEmptyMVar :: MVar a -> IO Bool #

Check whether a given MVar is empty.

Notice that the boolean value returned is just a snapshot of + the state of the MVar. By the time you get to react on its result, + the MVar may have been filled (or emptied) - so be extremely + careful when using this operation. Use tryTakeMVar instead if possible.

withMVar :: MVar a -> (a -> IO b) -> IO b #

withMVar is an exception-safe wrapper for operating on the contents + of an MVar. This operation is exception-safe: it will replace the + original contents of the MVar if an exception is raised (see + Control.Exception). However, it is only atomic if there are no + other producers for this MVar.

withMVarMasked :: MVar a -> (a -> IO b) -> IO b #

Like withMVar, but the IO action in the second argument is executed + with asynchronous exceptions masked.

Since: 4.7.0.0

modifyMVar_ :: MVar a -> (a -> IO a) -> IO () #

An exception-safe wrapper for modifying the contents of an MVar. + Like withMVar, modifyMVar will replace the original contents of + the MVar if an exception is raised during the operation. This + function is only atomic if there are no other producers for this + MVar.

modifyMVar :: MVar a -> (a -> IO (a, b)) -> IO b #

A slight variation on modifyMVar_ that allows a value to be + returned (b) in addition to the modified value of the MVar.

modifyMVarMasked_ :: MVar a -> (a -> IO a) -> IO () #

Like modifyMVar_, but the IO action in the second argument is executed with + asynchronous exceptions masked.

Since: 4.6.0.0

modifyMVarMasked :: MVar a -> (a -> IO (a, b)) -> IO b #

Like modifyMVar, but the IO action in the second argument is executed with + asynchronous exceptions masked.

Since: 4.6.0.0

tryReadMVar :: MVar a -> IO (Maybe a) #

A non-blocking version of readMVar. The tryReadMVar function + returns immediately, with Nothing if the MVar was empty, or + Just a if the MVar was full with contents a.

Since: 4.7.0.0

mkWeakMVar :: MVar a -> IO () -> IO (Weak (MVar a)) #

Make a Weak pointer to an MVar, using the second argument as + a finalizer to run when MVar is garbage-collected

Since: 4.6.0.0

data Chan a :: * -> * #

Chan is an abstract type representing an unbounded FIFO channel.

Instances

Eq (Chan a) 

Methods

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

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

newChan :: IO (Chan a) #

Build and returns a new instance of Chan.

writeChan :: Chan a -> a -> IO () #

Write a value to a Chan.

readChan :: Chan a -> IO a #

Read the next value from the Chan.

dupChan :: Chan a -> IO (Chan a) #

Duplicate a Chan: the duplicate channel begins empty, but data written to + either channel from then on will be available from both. Hence this creates + a kind of broadcast channel, where data written by anyone is seen by + everyone else.

(Note that a duplicated channel is not equal to its original. + So: fmap (c /=) $ dupChan c returns True for all c.)

Reader

asks #

Arguments

:: MonadReader r m 
=> (r -> a)

The selector function to apply to the environment.

-> m a 

Retrieves a function of the current environment.

Exceptions

throwIO :: (MonadThrow m, Exception e) => e -> m a #

Synonym for throw

Since: 0.1.0.0

throwM :: (MonadThrow m, Exception e) => e -> m a #

Synonym for throw

Since: 0.1.0.0

throwTo :: (Exception e, MonadIO m) => ThreadId -> e -> m () #

Throw an asynchronous exception to another thread

It's usually a better idea to use the async package, see + https://github.com/fpco/safe-exceptions#quickstart

Since: 0.1.0.0

catch :: (MonadCatch m, Exception e) => m a -> (e -> m a) -> m a #

Same as upstream catch, but will not catch asynchronous + exceptions

Since: 0.1.0.0

catchIO :: MonadCatch m => m a -> (IOException -> m a) -> m a #

catch specialized to only catching IOExceptions

Since: 0.1.3.0

catchAny :: MonadCatch m => m a -> (SomeException -> m a) -> m a #

catch specialized to catch all synchronous exception

Since: 0.1.0.0

catchDeep :: (MonadCatch m, MonadIO m, Exception e, NFData a) => m a -> (e -> m a) -> m a #

Same as catch, but fully force evaluation of the result value + to find all impure exceptions.

Since: 0.1.1.0

catchAnyDeep :: (MonadCatch m, MonadIO m, NFData a) => m a -> (SomeException -> m a) -> m a #

catchDeep specialized to catch all synchronous exception

Since: 0.1.1.0

handle :: (MonadCatch m, Exception e) => (e -> m a) -> m a -> m a #

Flipped version of catch

Since: 0.1.0.0

handleIO :: MonadCatch m => (IOException -> m a) -> m a -> m a #

handle specialized to only catching IOExceptions

Since: 0.1.3.0

handleAny :: MonadCatch m => (SomeException -> m a) -> m a -> m a #

Flipped version of catchAny

Since: 0.1.0.0

handleDeep :: (MonadCatch m, Exception e, MonadIO m, NFData a) => (e -> m a) -> m a -> m a #

Flipped version of catchDeep

Since: 0.1.1.0

handleAnyDeep :: (MonadCatch m, MonadIO m, NFData a) => (SomeException -> m a) -> m a -> m a #

Flipped version of catchAnyDeep

Since: 0.1.1.0

try :: (MonadCatch m, Exception e) => m a -> m (Either e a) #

Same as upstream try, but will not catch asynchronous + exceptions

Since: 0.1.0.0

tryIO :: MonadCatch m => m a -> m (Either IOException a) #

try specialized to only catching IOExceptions

Since: 0.1.3.0

tryAny :: MonadCatch m => m a -> m (Either SomeException a) #

try specialized to catch all synchronous exceptions

Since: 0.1.0.0

tryDeep :: (MonadCatch m, MonadIO m, Exception e, NFData a) => m a -> m (Either e a) #

Same as try, but fully force evaluation of the result value + to find all impure exceptions.

Since: 0.1.1.0

tryAnyDeep :: (MonadCatch m, MonadIO m, NFData a) => m a -> m (Either SomeException a) #

tryDeep specialized to catch all synchronous exceptions

Since: 0.1.1.0

onException :: MonadMask m => m a -> m b -> m a #

Async safe version of onException

Since: 0.1.0.0

bracket :: MonadMask m => m a -> (a -> m b) -> (a -> m c) -> m c #

Async safe version of bracket

Since: 0.1.0.0

bracket_ :: MonadMask m => m a -> m b -> m c -> m c #

Async safe version of bracket_

Since: 0.1.0.0

finally :: MonadMask m => m a -> m b -> m a #

Async safe version of finally

Since: 0.1.0.0

withException :: (MonadMask m, Exception e) => m a -> (e -> m b) -> m a #

Like onException, but provides the handler the thrown + exception.

Since: 0.1.0.0

bracketOnError :: MonadMask m => m a -> (a -> m b) -> (a -> m c) -> m c #

Async safe version of bracketOnError

Since: 0.1.0.0

bracketOnError_ :: MonadMask m => m a -> m b -> m c -> m c #

Async safe version of bracketOnError_

Since: 0.1.0.0

displayException :: Exception e => e -> String #

Render this exception value in a human-friendly manner.

Default implementation: show.

Since: 4.8.0.0

Arrow

(&&&) :: Arrow a => forall b c c'. a b c -> a b c' -> a b (c, c') #

Fanout: send the input to both argument arrows and combine + their output.

The default definition may be overridden with a more efficient + version if desired.

(***) :: Arrow a => forall b c b' c'. a b c -> a b' c' -> a (b, b') (c, c') #

Split the input between the two argument arrows and combine + their output. Note that this is in general not a functor.

The default definition may be overridden with a more efficient + version if desired.

Maybe

mapMaybe :: (a -> Maybe b) -> [a] -> [b] #

The mapMaybe function is a version of map which can throw + out elements. In particular, the functional argument returns + something of type Maybe b. If this is Nothing, no element + is added on to the result list. If it is Just b, then b is + included in the result list.

Examples

Using mapMaybe f x is a shortcut for catMaybes $ map f x + in most cases:

>>> import Text.Read ( readMaybe )
+>>> let readMaybeInt = readMaybe :: String -> Maybe Int
+>>> mapMaybe readMaybeInt ["1", "Foo", "3"]
+[1,3]
+>>> catMaybes $ map readMaybeInt ["1", "Foo", "3"]
+[1,3]
+

If we map the Just constructor, the entire list should be returned:

>>> mapMaybe Just [1,2,3]
+[1,2,3]
+

catMaybes :: [Maybe a] -> [a] #

The catMaybes function takes a list of Maybes and returns + a list of all the Just values.

Examples

Basic usage:

>>> catMaybes [Just 1, Nothing, Just 3]
+[1,3]
+

When constructing a list of Maybe values, catMaybes can be used + to return all of the "success" results (if the list is the result + of a map, then mapMaybe would be more appropriate):

>>> import Text.Read ( readMaybe )
+>>> [readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ]
+[Just 1,Nothing,Just 3]
+>>> catMaybes $ [readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ]
+[1,3]
+

fromMaybe :: a -> Maybe a -> a #

The fromMaybe function takes a default value and and Maybe + value. If the Maybe is Nothing, it returns the default values; + otherwise, it returns the value contained in the Maybe.

Examples

Basic usage:

>>> fromMaybe "" (Just "Hello, World!")
+"Hello, World!"
+
>>> fromMaybe "" Nothing
+""
+

Read an integer from a string using readMaybe. If we fail to + parse an integer, we want to return 0 by default:

>>> import Text.Read ( readMaybe )
+>>> fromMaybe 0 (readMaybe "5")
+5
+>>> fromMaybe 0 (readMaybe "")
+0
+

isJust :: Maybe a -> Bool #

The isJust function returns True iff its argument is of the + form Just _.

Examples

Basic usage:

>>> isJust (Just 3)
+True
+
>>> isJust (Just ())
+True
+
>>> isJust Nothing
+False
+

Only the outer constructor is taken into consideration:

>>> isJust (Just Nothing)
+True
+

isNothing :: Maybe a -> Bool #

The isNothing function returns True iff its argument is Nothing.

Examples

Basic usage:

>>> isNothing (Just 3)
+False
+
>>> isNothing (Just ())
+False
+
>>> isNothing Nothing
+True
+

Only the outer constructor is taken into consideration:

>>> isNothing (Just Nothing)
+False
+

listToMaybe :: [a] -> Maybe a #

The listToMaybe function returns Nothing on an empty list + or Just a where a is the first element of the list.

Examples

Basic usage:

>>> listToMaybe []
+Nothing
+
>>> listToMaybe [9]
+Just 9
+
>>> listToMaybe [1,2,3]
+Just 1
+

Composing maybeToList with listToMaybe should be the identity + on singleton/empty lists:

>>> maybeToList $ listToMaybe [5]
+[5]
+>>> maybeToList $ listToMaybe []
+[]
+

But not on lists with more than one element:

>>> maybeToList $ listToMaybe [1,2,3]
+[1]
+

Either

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.

Examples

Basic usage:

>>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
+>>> partitionEithers list
+(["foo","bar","baz"],[3,7])
+

The pair returned by partitionEithers x should be the same + pair as (lefts x, rights x):

>>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
+>>> partitionEithers list == (lefts list, rights list)
+True
+

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

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

Examples

Basic usage:

>>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
+>>> lefts list
+["foo","bar","baz"]
+

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

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

Examples

Basic usage:

>>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
+>>> rights list
+[3,7]
+

Ord

on :: (b -> b -> c) -> (a -> b) -> a -> a -> c infixl 0 #

(*) `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)

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

Say

say :: MonadIO m => Text -> m () #

Send a Text to standard output, appending a newline, and chunking the + data. By default, the chunk size is 2048 characters, so any messages below + that size will be sent as one contiguous unit. If larger messages are used, + it is possible for interleaving with other threads to occur.

Since: 0.1.0.0

sayString :: MonadIO m => String -> m () #

Same as say, but operates on a String. Note that this will + force the entire String into memory at once, and will fail for + infinite Strings.

Since: 0.1.0.0

sayShow :: (MonadIO m, Show a) => a -> m () #

Same as say, but for instances of Show.

If your Show instance generates infinite output, this will fail. However, + an infinite result for show would generally be considered an invalid + instance anyway.

Since: 0.1.0.0

sayErr :: MonadIO m => Text -> m () #

Same as say, but data is sent to standard error.

Since: 0.1.0.0

sayErrString :: MonadIO m => String -> m () #

Same as sayString, but data is sent to standard error.

Since: 0.1.0.0

sayErrShow :: (MonadIO m, Show a) => a -> m () #

Same as sayShow, but data is sent to standard error.

Since: 0.1.0.0

hSay :: MonadIO m => Handle -> Text -> m () #

Same as say, but data is sent to the provided Handle.

Since: 0.1.0.0

hSayString :: MonadIO m => Handle -> String -> m () #

Same as sayString, but data is sent to the provided Handle.

Since: 0.1.0.0

hSayShow :: (MonadIO m, Show a) => Handle -> a -> m () #

Same as sayShow, but data is sent to the provided Handle.

Since: 0.1.0.0

IORef

data IORef a :: * -> * #

A mutable variable in the IO monad

Instances

Eq (IORef a) 

Methods

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

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

NFData (IORef a)

NOTE: Only strict in the reference and not the referenced value.

Since: 1.4.2.0

Methods

rnf :: IORef a -> () #

newIORef :: a -> IO (IORef a) #

Build a new IORef

readIORef :: IORef a -> IO a #

Read the value of an IORef

writeIORef :: IORef a -> a -> IO () #

Write a new value into an IORef

modifyIORef :: IORef a -> (a -> a) -> IO () #

Mutate the contents of an IORef.

Be warned that modifyIORef does not apply the function strictly. This + means if the program calls modifyIORef many times, but seldomly uses the + value, thunks will pile up in memory resulting in a space leak. This is a + common mistake made when using an IORef as a counter. For example, the + following will likely produce a stack overflow:

ref <- newIORef 0
+replicateM_ 1000000 $ modifyIORef ref (+1)
+readIORef ref >>= print

To avoid this problem, use modifyIORef' instead.

modifyIORef' :: IORef a -> (a -> a) -> IO () #

Strict version of modifyIORef

Since: 4.6.0.0

atomicModifyIORef :: IORef a -> (a -> (a, b)) -> IO b #

Atomically modifies the contents of an IORef.

This function is useful for using IORef in a safe way in a multithreaded + program. If you only have one IORef, then using atomicModifyIORef to + access and modify it will prevent race conditions.

Extending the atomicity to multiple IORefs is problematic, so it + is recommended that if you need to do anything more complicated + then using MVar instead is a good idea.

atomicModifyIORef does not apply the function strictly. This is important + to know even if all you are doing is replacing the value. For example, this + will leak memory:

ref <- newIORef '1'
+forever $ atomicModifyIORef ref (\_ -> ('2', ()))

Use atomicModifyIORef' or atomicWriteIORef to avoid this problem.

atomicModifyIORef' :: IORef a -> (a -> (a, b)) -> IO b #

Strict version of atomicModifyIORef. This forces both the value stored + in the IORef as well as the value returned.

Since: 4.6.0.0

atomicWriteIORef :: IORef a -> a -> IO () #

Variant of writeIORef with the "barrier to reordering" property that + atomicModifyIORef has.

Since: 4.6.0.0

mkWeakIORef :: IORef a -> IO () -> IO (Weak (IORef a)) #

Make a Weak pointer to an IORef, using the second argument as a finalizer + to run when IORef is garbage-collected

IO

data Handle :: * #

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.

Instances

Eq Handle 

Methods

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

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

Show Handle 

stdin :: Handle #

A handle managing input from the Haskell program's standard input channel.

stdout :: Handle #

A handle managing output to the Haskell program's standard output channel.

stderr :: Handle #

A handle managing output to the Haskell program's standard error channel.

hClose :: Handle -> IO () #

Computation hClose hdl makes handle hdl closed. Before the + computation finishes, if hdl is writable its buffer is flushed as + for hFlush. + Performing hClose on a handle that has already been closed has no effect; + doing so is not an error. All other operations on a closed handle will fail. + If hClose fails for any reason, any further operations (apart from + hClose) on the handle will still fail as if hdl had been successfully + closed.

withBinaryFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r #

withBinaryFile name mode act opens a file using openBinaryFile + and passes the resulting handle to the computation act. The handle + will be closed on exit from withBinaryFile, whether by normal + termination or by raising an exception.

readFile :: FilePath -> IO ByteString #

Read an entire file strictly into a ByteString.

writeFile :: FilePath -> ByteString -> IO () #

Write a ByteString to a file.

readFileUtf8 :: MonadIO m => FilePath -> m Text Source #

Read a file assuming a UTF-8 character encoding.

This leverages decodeUtf8, so in the event of a character + encoding issue, replacement characters will be used.

Since: 0.1.0.0

writeFileUtf8 :: MonadIO m => FilePath -> Text -> m () Source #

Write a file using a UTF-8 character encoding.

Since: 0.1.0.0

Character encoding

encodeUtf8 :: Text -> ByteString #

Encode text using UTF-8 encoding.

decodeUtf8 :: ByteString -> Text Source #

A total function for decoding a ByteString into Text using a + UTF-8 character encoding. This uses lenientDecode in the case of + any encoding errors.

Since: 0.1.0.0

deepseq

class NFData a where #

A class of types that can be fully evaluated.

Since: 1.1.0.0

Minimal complete definition

Nothing

Instances

NFData Bool 

Methods

rnf :: Bool -> () #

NFData Char 

Methods

rnf :: Char -> () #

NFData Double 

Methods

rnf :: Double -> () #

NFData Float 

Methods

rnf :: Float -> () #

NFData Int 

Methods

rnf :: Int -> () #

NFData Int8 

Methods

rnf :: Int8 -> () #

NFData Int16 

Methods

rnf :: Int16 -> () #

NFData Int32 

Methods

rnf :: Int32 -> () #

NFData Int64 

Methods

rnf :: Int64 -> () #

NFData Integer 

Methods

rnf :: Integer -> () #

NFData Word 

Methods

rnf :: Word -> () #

NFData Word8 

Methods

rnf :: Word8 -> () #

NFData Word16 

Methods

rnf :: Word16 -> () #

NFData Word32 

Methods

rnf :: Word32 -> () #

NFData Word64 

Methods

rnf :: Word64 -> () #

NFData CallStack

Since: 1.4.2.0

Methods

rnf :: CallStack -> () #

NFData TypeRep

NOTE: Only defined for base-4.8.0.0 and later

Since: 1.4.0.0

Methods

rnf :: TypeRep -> () #

NFData () 

Methods

rnf :: () -> () #

NFData TyCon

NOTE: Only defined for base-4.8.0.0 and later

Since: 1.4.0.0

Methods

rnf :: TyCon -> () #

NFData Natural

Since: 1.4.0.0

Methods

rnf :: Natural -> () #

NFData Void

Defined as rnf = absurd.

Since: 1.4.0.0

Methods

rnf :: Void -> () #

NFData Version

Since: 1.3.0.0

Methods

rnf :: Version -> () #

NFData Unique

Since: 1.4.0.0

Methods

rnf :: Unique -> () #

NFData ThreadId

Since: 1.4.0.0

Methods

rnf :: ThreadId -> () #

NFData ExitCode

Since: 1.4.2.0

Methods

rnf :: ExitCode -> () #

NFData CChar

Since: 1.4.0.0

Methods

rnf :: CChar -> () #

NFData CSChar

Since: 1.4.0.0

Methods

rnf :: CSChar -> () #

NFData CUChar

Since: 1.4.0.0

Methods

rnf :: CUChar -> () #

NFData CShort

Since: 1.4.0.0

Methods

rnf :: CShort -> () #

NFData CUShort

Since: 1.4.0.0

Methods

rnf :: CUShort -> () #

NFData CInt

Since: 1.4.0.0

Methods

rnf :: CInt -> () #

NFData CUInt

Since: 1.4.0.0

Methods

rnf :: CUInt -> () #

NFData CLong

Since: 1.4.0.0

Methods

rnf :: CLong -> () #

NFData CULong

Since: 1.4.0.0

Methods

rnf :: CULong -> () #

NFData CLLong

Since: 1.4.0.0

Methods

rnf :: CLLong -> () #

NFData CULLong

Since: 1.4.0.0

Methods

rnf :: CULLong -> () #

NFData CFloat

Since: 1.4.0.0

Methods

rnf :: CFloat -> () #

NFData CDouble

Since: 1.4.0.0

Methods

rnf :: CDouble -> () #

NFData CPtrdiff

Since: 1.4.0.0

Methods

rnf :: CPtrdiff -> () #

NFData CSize

Since: 1.4.0.0

Methods

rnf :: CSize -> () #

NFData CWchar

Since: 1.4.0.0

Methods

rnf :: CWchar -> () #

NFData CSigAtomic

Since: 1.4.0.0

Methods

rnf :: CSigAtomic -> () #

NFData CClock

Since: 1.4.0.0

Methods

rnf :: CClock -> () #

NFData CTime

Since: 1.4.0.0

Methods

rnf :: CTime -> () #

NFData CUSeconds

Since: 1.4.0.0

Methods

rnf :: CUSeconds -> () #

NFData CSUSeconds

Since: 1.4.0.0

Methods

rnf :: CSUSeconds -> () #

NFData CFile

Since: 1.4.0.0

Methods

rnf :: CFile -> () #

NFData CFpos

Since: 1.4.0.0

Methods

rnf :: CFpos -> () #

NFData CJmpBuf

Since: 1.4.0.0

Methods

rnf :: CJmpBuf -> () #

NFData CIntPtr

Since: 1.4.0.0

Methods

rnf :: CIntPtr -> () #

NFData CUIntPtr

Since: 1.4.0.0

Methods

rnf :: CUIntPtr -> () #

NFData CIntMax

Since: 1.4.0.0

Methods

rnf :: CIntMax -> () #

NFData CUIntMax

Since: 1.4.0.0

Methods

rnf :: CUIntMax -> () #

NFData All

Since: 1.4.0.0

Methods

rnf :: All -> () #

NFData Any

Since: 1.4.0.0

Methods

rnf :: Any -> () #

NFData Fingerprint

Since: 1.4.0.0

Methods

rnf :: Fingerprint -> () #

NFData SrcLoc

Since: 1.4.2.0

Methods

rnf :: SrcLoc -> () #

NFData ByteString 

Methods

rnf :: ByteString -> () #

NFData IntSet 

Methods

rnf :: IntSet -> () #

NFData UnicodeException 

Methods

rnf :: UnicodeException -> () #

NFData a => NFData [a] 

Methods

rnf :: [a] -> () #

NFData a => NFData (Maybe a) 

Methods

rnf :: Maybe a -> () #

NFData a => NFData (Ratio a) 

Methods

rnf :: Ratio a -> () #

NFData (Ptr a)

Since: 1.4.2.0

Methods

rnf :: Ptr a -> () #

NFData (FunPtr a)

Since: 1.4.2.0

Methods

rnf :: FunPtr a -> () #

NFData a => NFData (Identity a)

Since: 1.4.0.0

Methods

rnf :: Identity a -> () #

NFData a => NFData (Min a)

Since: 1.4.2.0

Methods

rnf :: Min a -> () #

NFData a => NFData (Max a)

Since: 1.4.2.0

Methods

rnf :: Max a -> () #

NFData a => NFData (First a)

Since: 1.4.2.0

Methods

rnf :: First a -> () #

NFData a => NFData (Last a)

Since: 1.4.2.0

Methods

rnf :: Last a -> () #

NFData m => NFData (WrappedMonoid m)

Since: 1.4.2.0

Methods

rnf :: WrappedMonoid m -> () #

NFData a => NFData (Option a)

Since: 1.4.2.0

Methods

rnf :: Option a -> () #

NFData a => NFData (NonEmpty a)

Since: 1.4.2.0

Methods

rnf :: NonEmpty a -> () #

NFData (Fixed a)

Since: 1.3.0.0

Methods

rnf :: Fixed a -> () #

NFData a => NFData (Complex a) 

Methods

rnf :: Complex a -> () #

NFData (StableName a)

Since: 1.4.0.0

Methods

rnf :: StableName a -> () #

NFData a => NFData (ZipList a)

Since: 1.4.0.0

Methods

rnf :: ZipList a -> () #

NFData a => NFData (Dual a)

Since: 1.4.0.0

Methods

rnf :: Dual a -> () #

NFData a => NFData (Sum a)

Since: 1.4.0.0

Methods

rnf :: Sum a -> () #

NFData a => NFData (Product a)

Since: 1.4.0.0

Methods

rnf :: Product a -> () #

NFData a => NFData (First a)

Since: 1.4.0.0

Methods

rnf :: First a -> () #

NFData a => NFData (Last a)

Since: 1.4.0.0

Methods

rnf :: Last a -> () #

NFData (IORef a)

NOTE: Only strict in the reference and not the referenced value.

Since: 1.4.2.0

Methods

rnf :: IORef a -> () #

NFData a => NFData (Down a)

Since: 1.4.0.0

Methods

rnf :: Down a -> () #

NFData (MVar a)

NOTE: Only strict in the reference and not the referenced value.

Since: 1.4.2.0

Methods

rnf :: MVar a -> () #

NFData a => NFData (Digit a) 

Methods

rnf :: Digit a -> () #

NFData a => NFData (Node a) 

Methods

rnf :: Node a -> () #

NFData a => NFData (Elem a) 

Methods

rnf :: Elem a -> () #

NFData a => NFData (FingerTree a) 

Methods

rnf :: FingerTree a -> () #

NFData a => NFData (Seq a) 

Methods

rnf :: Seq a -> () #

NFData a => NFData (IntMap a) 

Methods

rnf :: IntMap a -> () #

NFData a => NFData (Set a) 

Methods

rnf :: Set a -> () #

NFData a => NFData (Array a) 

Methods

rnf :: Array a -> () #

NFData a => NFData (HashSet a) 

Methods

rnf :: HashSet a -> () #

NFData (a -> b)

This instance is for convenience and consistency with seq. + This assumes that WHNF is equivalent to NF for functions.

Since: 1.3.0.0

Methods

rnf :: (a -> b) -> () #

(NFData a, NFData b) => NFData (Either a b) 

Methods

rnf :: Either a b -> () #

(NFData a, NFData b) => NFData (a, b) 

Methods

rnf :: (a, b) -> () #

(NFData a, NFData b) => NFData (Array a b) 

Methods

rnf :: Array a b -> () #

(NFData a, NFData b) => NFData (Arg a b)

Since: 1.4.2.0

Methods

rnf :: Arg a b -> () #

NFData (Proxy k a)

Since: 1.4.0.0

Methods

rnf :: Proxy k a -> () #

NFData (STRef s a)

NOTE: Only strict in the reference and not the referenced value.

Since: 1.4.2.0

Methods

rnf :: STRef s a -> () #

(NFData k, NFData a) => NFData (Map k a) 

Methods

rnf :: Map k a -> () #

(NFData k, NFData v) => NFData (Leaf k v) 

Methods

rnf :: Leaf k v -> () #

(NFData k, NFData v) => NFData (HashMap k v) 

Methods

rnf :: HashMap k v -> () #

(NFData a, NFData b, NFData c) => NFData (a, b, c) 

Methods

rnf :: (a, b, c) -> () #

NFData a => NFData (Const k a b)

Since: 1.4.0.0

Methods

rnf :: Const k a b -> () #

(NFData a, NFData b, NFData c, NFData d) => NFData (a, b, c, d) 

Methods

rnf :: (a, b, c, d) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => NFData (a1, a2, a3, a4, a5) 

Methods

rnf :: (a1, a2, a3, a4, a5) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => NFData (a1, a2, a3, a4, a5, a6) 

Methods

rnf :: (a1, a2, a3, a4, a5, a6) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => NFData (a1, a2, a3, a4, a5, a6, a7) 

Methods

rnf :: (a1, a2, a3, a4, a5, a6, a7) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8) => NFData (a1, a2, a3, a4, a5, a6, a7, a8) 

Methods

rnf :: (a1, a2, a3, a4, a5, a6, a7, a8) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8, NFData a9) => NFData (a1, a2, a3, a4, a5, a6, a7, a8, a9) 

Methods

rnf :: (a1, a2, a3, a4, a5, a6, a7, a8, a9) -> () #

deepseq :: NFData a => a -> b -> b #

deepseq: fully evaluates the first argument, before returning the + second.

The name deepseq is used to illustrate the relationship to seq: + where seq is shallow in the sense that it only evaluates the top + level of its argument, deepseq traverses the entire data structure + evaluating it completely.

deepseq can be useful for forcing pending exceptions, + eradicating space leaks, or forcing lazy I/O to happen. It is + also useful in conjunction with parallel Strategies (see the + parallel package).

There is no guarantee about the ordering of evaluation. The + implementation may evaluate the components of the structure in + any order or in parallel. To impose an actual order on + evaluation, use pseq from Control.Parallel in the + parallel package.

Since: 1.1.0.0

($!!) :: NFData a => (a -> b) -> a -> b infixr 0 #

the deep analogue of $!. In the expression f $!! x, x is + fully evaluated before the function f is applied to it.

Since: 1.2.0.0

force :: NFData a => a -> a #

a variant of deepseq that is useful in some circumstances:

force x = x `deepseq` x

force x fully evaluates x, and then returns it. Note that + force x only performs evaluation when the value of force x + itself is demanded, so essentially it turns shallow evaluation into + deep evaluation.

force can be conveniently used in combination with ViewPatterns:

{-# LANGUAGE BangPatterns, ViewPatterns #-}
+import Control.DeepSeq
+
+someFun :: ComplexData -> SomeResult
+someFun (force -> !arg) = {- 'arg' will be fully evaluated -}

Another useful application is to combine force with + evaluate in order to force deep evaluation + relative to other IO operations:

import Control.Exception (evaluate)
+import Control.DeepSeq
+
+main = do
+  result <- evaluate $ force $ pureComputation
+  {- 'result' will be fully evaluated at this point -}
+  return ()

Since: 1.2.0.0

Monoids

(++) :: Monoid m => m -> m -> m infixr 5 Source #

Operator version of mappend.

In base, this operator is known as <>. However, this is the name + of the operator for Semigroup as well. Once Semigroup is a + superclass of Monoid, this historical accident will be + unimportant. In the meanwhile, SafePrelude deals with this + situation by making <> the Semigroup operator, and ++ the + Monoid operator.

Since: 0.1.0.0

Read

readMaybe :: Read a => String -> Maybe a #

Parse a string using the Read instance. + Succeeds if there is exactly one valid result.

Since: 4.6.0.0

readEither :: Read a => String -> Either String a #

Parse a string using the Read instance. + Succeeds if there is exactly one valid result. + A Left value indicates a parse error.

Since: 4.6.0.0

\ No newline at end of file diff --git a/static/safe-prelude/doc-index-124.html b/static/safe-prelude/doc-index-124.html new file mode 100644 index 0000000..3b22916 --- /dev/null +++ b/static/safe-prelude/doc-index-124.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - |)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - |

||SafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-36.html b/static/safe-prelude/doc-index-36.html new file mode 100644 index 0000000..df1f941 --- /dev/null +++ b/static/safe-prelude/doc-index-36.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - $)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - $

$SafePrelude
$!SafePrelude
$!!SafePrelude
$>SafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-38.html b/static/safe-prelude/doc-index-38.html new file mode 100644 index 0000000..983e23f --- /dev/null +++ b/static/safe-prelude/doc-index-38.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - &)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - &

&SafePrelude
&&SafePrelude
&&&SafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-42.html b/static/safe-prelude/doc-index-42.html new file mode 100644 index 0000000..52d6ac4 --- /dev/null +++ b/static/safe-prelude/doc-index-42.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - *)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - *

*SafePrelude
**SafePrelude
***SafePrelude
*>SafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-43.html b/static/safe-prelude/doc-index-43.html new file mode 100644 index 0000000..75b1bf0 --- /dev/null +++ b/static/safe-prelude/doc-index-43.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - +)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - +

+SafePrelude
++SafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-45.html b/static/safe-prelude/doc-index-45.html new file mode 100644 index 0000000..d358b56 --- /dev/null +++ b/static/safe-prelude/doc-index-45.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - -)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - -

-SafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-46.html b/static/safe-prelude/doc-index-46.html new file mode 100644 index 0000000..badd4da --- /dev/null +++ b/static/safe-prelude/doc-index-46.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - .)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - .

.SafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-47.html b/static/safe-prelude/doc-index-47.html new file mode 100644 index 0000000..f4d345f --- /dev/null +++ b/static/safe-prelude/doc-index-47.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - /)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - /

/SafePrelude
/=SafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-60.html b/static/safe-prelude/doc-index-60.html new file mode 100644 index 0000000..d849766 --- /dev/null +++ b/static/safe-prelude/doc-index-60.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - <)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - <

<SafePrelude
<$SafePrelude
<$!>SafePrelude
<$>SafePrelude
<*SafePrelude
<*>SafePrelude
<=SafePrelude
<=<SafePrelude
<>SafePrelude
<|>SafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-61.html b/static/safe-prelude/doc-index-61.html new file mode 100644 index 0000000..865d154 --- /dev/null +++ b/static/safe-prelude/doc-index-61.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - =)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - =

=<<SafePrelude
==SafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-62.html b/static/safe-prelude/doc-index-62.html new file mode 100644 index 0000000..edddb40 --- /dev/null +++ b/static/safe-prelude/doc-index-62.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - >)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - >

>SafePrelude
>=SafePrelude
>=>SafePrelude
>>SafePrelude
>>=SafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-94.html b/static/safe-prelude/doc-index-94.html new file mode 100644 index 0000000..17fbfed --- /dev/null +++ b/static/safe-prelude/doc-index-94.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - ^)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - ^

^SafePrelude
^^SafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-A.html b/static/safe-prelude/doc-index-A.html new file mode 100644 index 0000000..2a845bb --- /dev/null +++ b/static/safe-prelude/doc-index-A.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - A)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - A

absSafePrelude
acosSafePrelude
acoshSafePrelude
allSafePrelude
AlternativeSafePrelude
andSafePrelude
anySafePrelude
apSafePrelude
AppendModeSafePrelude
ApplicativeSafePrelude
asinSafePrelude
asinhSafePrelude
askSafePrelude
asksSafePrelude
asTypeOfSafePrelude
asumSafePrelude
atanSafePrelude
atan2SafePrelude
atanhSafePrelude
atomicModifyIORefSafePrelude
atomicModifyIORef'SafePrelude
atomicWriteIORefSafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-All.html b/static/safe-prelude/doc-index-All.html new file mode 100644 index 0000000..459536a --- /dev/null +++ b/static/safe-prelude/doc-index-All.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index

$SafePrelude
$!SafePrelude
$!!SafePrelude
$>SafePrelude
&SafePrelude
&&SafePrelude
&&&SafePrelude
*SafePrelude
**SafePrelude
***SafePrelude
*>SafePrelude
+SafePrelude
++SafePrelude
-SafePrelude
.SafePrelude
/SafePrelude
/=SafePrelude
<SafePrelude
<$SafePrelude
<$!>SafePrelude
<$>SafePrelude
<*SafePrelude
<*>SafePrelude
<=SafePrelude
<=<SafePrelude
<>SafePrelude
<|>SafePrelude
=<<SafePrelude
==SafePrelude
>SafePrelude
>=SafePrelude
>=>SafePrelude
>>SafePrelude
>>=SafePrelude
absSafePrelude
acosSafePrelude
acoshSafePrelude
allSafePrelude
AlternativeSafePrelude
andSafePrelude
anySafePrelude
apSafePrelude
AppendModeSafePrelude
ApplicativeSafePrelude
asinSafePrelude
asinhSafePrelude
askSafePrelude
asksSafePrelude
asTypeOfSafePrelude
asumSafePrelude
atanSafePrelude
atan2SafePrelude
atanhSafePrelude
atomicModifyIORefSafePrelude
atomicModifyIORef'SafePrelude
atomicWriteIORefSafePrelude
BoolSafePrelude
BoundedSafePrelude
bracketSafePrelude
bracketOnErrorSafePrelude
bracketOnError_SafePrelude
bracket_SafePrelude
ByteStringSafePrelude
catchSafePrelude
catchAnySafePrelude
catchAnyDeepSafePrelude
catchDeepSafePrelude
catchIOSafePrelude
catMaybesSafePrelude
ceilingSafePrelude
ChanSafePrelude
CharSafePrelude
compareSafePrelude
comparingSafePrelude
concatSafePrelude
concatMapSafePrelude
constSafePrelude
cosSafePrelude
coshSafePrelude
currySafePrelude
decodeFloatSafePrelude
decodeUtf8SafePrelude
deepseqSafePrelude
displayExceptionSafePrelude
divSafePrelude
divModSafePrelude
DoubleSafePrelude
dupChanSafePrelude
EitherSafePrelude
eitherSafePrelude
elemSafePrelude
emptySafePrelude
encodeFloatSafePrelude
encodeUtf8SafePrelude
EQSafePrelude
EqSafePrelude
evenSafePrelude
ExceptionSafePrelude
expSafePrelude
exponentSafePrelude
failSafePrelude
FalseSafePrelude
FilePathSafePrelude
finallySafePrelude
findSafePrelude
fixSafePrelude
flipSafePrelude
FloatSafePrelude
floatDigitsSafePrelude
FloatingSafePrelude
floatRadixSafePrelude
floatRangeSafePrelude
floorSafePrelude
fmapSafePrelude
foldSafePrelude
FoldableSafePrelude
foldlSafePrelude
foldl'SafePrelude
foldlMSafePrelude
foldMSafePrelude
foldMapSafePrelude
foldM_SafePrelude
foldrSafePrelude
foldr'SafePrelude
foldrMSafePrelude
forSafePrelude
forceSafePrelude
foreverSafePrelude
forMSafePrelude
forM_SafePrelude
for_SafePrelude
FractionalSafePrelude
fromExceptionSafePrelude
fromIntegerSafePrelude
fromIntegralSafePrelude
fromMaybeSafePrelude
fromRationalSafePrelude
fromStringSafePrelude
fstSafePrelude
FunctorSafePrelude
GTSafePrelude
guardSafePrelude
HandleSafePrelude
handleSafePrelude
handleAnySafePrelude
handleAnyDeepSafePrelude
handleDeepSafePrelude
handleIOSafePrelude
hashSafePrelude
HashableSafePrelude
HashMapSafePrelude
HashSetSafePrelude
hashWithSaltSafePrelude
hCloseSafePrelude
hSaySafePrelude
hSayShowSafePrelude
hSayStringSafePrelude
idSafePrelude
Identity 
1 (Data Constructor)SafePrelude
2 (Type/Class)SafePrelude
IntSafePrelude
Int16SafePrelude
Int32SafePrelude
Int64SafePrelude
Int8SafePrelude
IntegerSafePrelude
IntegralSafePrelude
IntMapSafePrelude
IntSetSafePrelude
IOSafePrelude
IOModeSafePrelude
IORefSafePrelude
isDenormalizedSafePrelude
isEmptyMVarSafePrelude
isIEEESafePrelude
isInfiniteSafePrelude
isJustSafePrelude
isNaNSafePrelude
isNegativeZeroSafePrelude
isNothingSafePrelude
IsStringSafePrelude
joinSafePrelude
JustSafePrelude
LeftSafePrelude
leftsSafePrelude
lengthSafePrelude
liftSafePrelude
liftASafePrelude
liftA2SafePrelude
liftA3SafePrelude
liftIOSafePrelude
liftMSafePrelude
listToMaybeSafePrelude
localSafePrelude
logSafePrelude
logBaseSafePrelude
LTSafePrelude
manySafePrelude
MapSafePrelude
mapAccumLSafePrelude
mapAccumRSafePrelude
mapMSafePrelude
mapMaybeSafePrelude
mapM_SafePrelude
mappendSafePrelude
maxSafePrelude
maxBoundSafePrelude
MaybeSafePrelude
maybeSafePrelude
mconcatSafePrelude
memptySafePrelude
minSafePrelude
minBoundSafePrelude
mkWeakIORefSafePrelude
mkWeakMVarSafePrelude
modSafePrelude
modifyIORefSafePrelude
modifyIORef'SafePrelude
modifyMVarSafePrelude
modifyMVarMaskedSafePrelude
modifyMVarMasked_SafePrelude
modifyMVar_SafePrelude
MonadSafePrelude
MonadCatchSafePrelude
MonadIOSafePrelude
MonadMaskSafePrelude
MonadReaderSafePrelude
MonadThrowSafePrelude
MonadTransSafePrelude
MonoidSafePrelude
msumSafePrelude
MVarSafePrelude
negateSafePrelude
newChanSafePrelude
newEmptyMVarSafePrelude
newIORefSafePrelude
newMVarSafePrelude
NFDataSafePrelude
notSafePrelude
notElemSafePrelude
NothingSafePrelude
nullSafePrelude
NumSafePrelude
oddSafePrelude
onSafePrelude
onExceptionSafePrelude
optionalSafePrelude
orSafePrelude
OrdSafePrelude
OrderingSafePrelude
otherwiseSafePrelude
partitionEithersSafePrelude
piSafePrelude
productSafePrelude
properFractionSafePrelude
Proxy 
1 (Data Constructor)SafePrelude
2 (Type/Class)SafePrelude
pureSafePrelude
putMVarSafePrelude
quotSafePrelude
quotRemSafePrelude
RationalSafePrelude
ReadSafePrelude
readChanSafePrelude
readEitherSafePrelude
readerSafePrelude
readFileSafePrelude
readFileUtf8SafePrelude
readIORefSafePrelude
readListSafePrelude
readListPrecSafePrelude
readMaybeSafePrelude
ReadModeSafePrelude
readMVarSafePrelude
readPrecSafePrelude
readsPrecSafePrelude
ReadWriteModeSafePrelude
RealSafePrelude
RealFloatSafePrelude
RealFracSafePrelude
realToFracSafePrelude
recipSafePrelude
remSafePrelude
replicateM_SafePrelude
returnSafePrelude
RightSafePrelude
rightsSafePrelude
rnfSafePrelude
roundSafePrelude
runIdentitySafePrelude
saySafePrelude
sayErrSafePrelude
sayErrShowSafePrelude
sayErrStringSafePrelude
sayShowSafePrelude
sayStringSafePrelude
scaleFloatSafePrelude
sconcatSafePrelude
SemigroupSafePrelude
SeqSafePrelude
seqSafePrelude
sequenceSafePrelude
sequenceASafePrelude
sequenceA_SafePrelude
sequence_SafePrelude
SetSafePrelude
ShowSafePrelude
showSafePrelude
showListSafePrelude
showsPrecSafePrelude
significandSafePrelude
signumSafePrelude
sinSafePrelude
sinhSafePrelude
sndSafePrelude
someSafePrelude
SomeAsyncException 
1 (Data Constructor)SafePrelude
2 (Type/Class)SafePrelude
SomeException 
1 (Data Constructor)SafePrelude
2 (Type/Class)SafePrelude
sqrtSafePrelude
stderrSafePrelude
stdinSafePrelude
stdoutSafePrelude
stimesSafePrelude
StringSafePrelude
subtractSafePrelude
sumSafePrelude
swapMVarSafePrelude
takeMVarSafePrelude
tanSafePrelude
tanhSafePrelude
TextSafePrelude
threadDelaySafePrelude
throwIOSafePrelude
throwMSafePrelude
throwToSafePrelude
toExceptionSafePrelude
toIntegerSafePrelude
toListSafePrelude
toRationalSafePrelude
TraversableSafePrelude
traverseSafePrelude
traverse_SafePrelude
TrueSafePrelude
truncateSafePrelude
trySafePrelude
tryAnySafePrelude
tryAnyDeepSafePrelude
tryDeepSafePrelude
tryIOSafePrelude
tryPutMVarSafePrelude
tryReadMVarSafePrelude
tryTakeMVarSafePrelude
TypeableSafePrelude
uncurrySafePrelude
unlessSafePrelude
voidSafePrelude
whenSafePrelude
withBinaryFileSafePrelude
withExceptionSafePrelude
withMVarSafePrelude
withMVarMaskedSafePrelude
WordSafePrelude
Word16SafePrelude
Word32SafePrelude
Word64SafePrelude
Word8SafePrelude
writeChanSafePrelude
writeFileSafePrelude
writeFileUtf8SafePrelude
writeIORefSafePrelude
WriteModeSafePrelude
^SafePrelude
^^SafePrelude
||SafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-B.html b/static/safe-prelude/doc-index-B.html new file mode 100644 index 0000000..2b09f62 --- /dev/null +++ b/static/safe-prelude/doc-index-B.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - B)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - B

BoolSafePrelude
BoundedSafePrelude
bracketSafePrelude
bracketOnErrorSafePrelude
bracketOnError_SafePrelude
bracket_SafePrelude
ByteStringSafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-C.html b/static/safe-prelude/doc-index-C.html new file mode 100644 index 0000000..2f1c305 --- /dev/null +++ b/static/safe-prelude/doc-index-C.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - C)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - C

catchSafePrelude
catchAnySafePrelude
catchAnyDeepSafePrelude
catchDeepSafePrelude
catchIOSafePrelude
catMaybesSafePrelude
ceilingSafePrelude
ChanSafePrelude
CharSafePrelude
compareSafePrelude
comparingSafePrelude
concatSafePrelude
concatMapSafePrelude
constSafePrelude
cosSafePrelude
coshSafePrelude
currySafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-D.html b/static/safe-prelude/doc-index-D.html new file mode 100644 index 0000000..fd75c67 --- /dev/null +++ b/static/safe-prelude/doc-index-D.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - D)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - D

decodeFloatSafePrelude
decodeUtf8SafePrelude
deepseqSafePrelude
displayExceptionSafePrelude
divSafePrelude
divModSafePrelude
DoubleSafePrelude
dupChanSafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-E.html b/static/safe-prelude/doc-index-E.html new file mode 100644 index 0000000..7c8acc6 --- /dev/null +++ b/static/safe-prelude/doc-index-E.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - E)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - E

EitherSafePrelude
eitherSafePrelude
elemSafePrelude
emptySafePrelude
encodeFloatSafePrelude
encodeUtf8SafePrelude
EQSafePrelude
EqSafePrelude
evenSafePrelude
ExceptionSafePrelude
expSafePrelude
exponentSafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-F.html b/static/safe-prelude/doc-index-F.html new file mode 100644 index 0000000..04eb01f --- /dev/null +++ b/static/safe-prelude/doc-index-F.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - F)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - F

failSafePrelude
FalseSafePrelude
FilePathSafePrelude
finallySafePrelude
findSafePrelude
fixSafePrelude
flipSafePrelude
FloatSafePrelude
floatDigitsSafePrelude
FloatingSafePrelude
floatRadixSafePrelude
floatRangeSafePrelude
floorSafePrelude
fmapSafePrelude
foldSafePrelude
FoldableSafePrelude
foldlSafePrelude
foldl'SafePrelude
foldlMSafePrelude
foldMSafePrelude
foldMapSafePrelude
foldM_SafePrelude
foldrSafePrelude
foldr'SafePrelude
foldrMSafePrelude
forSafePrelude
forceSafePrelude
foreverSafePrelude
forMSafePrelude
forM_SafePrelude
for_SafePrelude
FractionalSafePrelude
fromExceptionSafePrelude
fromIntegerSafePrelude
fromIntegralSafePrelude
fromMaybeSafePrelude
fromRationalSafePrelude
fromStringSafePrelude
fstSafePrelude
FunctorSafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-G.html b/static/safe-prelude/doc-index-G.html new file mode 100644 index 0000000..54aa39f --- /dev/null +++ b/static/safe-prelude/doc-index-G.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - G)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - G

GTSafePrelude
guardSafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-H.html b/static/safe-prelude/doc-index-H.html new file mode 100644 index 0000000..eb0941f --- /dev/null +++ b/static/safe-prelude/doc-index-H.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - H)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - H

HandleSafePrelude
handleSafePrelude
handleAnySafePrelude
handleAnyDeepSafePrelude
handleDeepSafePrelude
handleIOSafePrelude
hashSafePrelude
HashableSafePrelude
HashMapSafePrelude
HashSetSafePrelude
hashWithSaltSafePrelude
hCloseSafePrelude
hSaySafePrelude
hSayShowSafePrelude
hSayStringSafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-I.html b/static/safe-prelude/doc-index-I.html new file mode 100644 index 0000000..54cbf5f --- /dev/null +++ b/static/safe-prelude/doc-index-I.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - I)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - I

idSafePrelude
Identity 
1 (Data Constructor)SafePrelude
2 (Type/Class)SafePrelude
IntSafePrelude
Int16SafePrelude
Int32SafePrelude
Int64SafePrelude
Int8SafePrelude
IntegerSafePrelude
IntegralSafePrelude
IntMapSafePrelude
IntSetSafePrelude
IOSafePrelude
IOModeSafePrelude
IORefSafePrelude
isDenormalizedSafePrelude
isEmptyMVarSafePrelude
isIEEESafePrelude
isInfiniteSafePrelude
isJustSafePrelude
isNaNSafePrelude
isNegativeZeroSafePrelude
isNothingSafePrelude
IsStringSafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-J.html b/static/safe-prelude/doc-index-J.html new file mode 100644 index 0000000..3794ff2 --- /dev/null +++ b/static/safe-prelude/doc-index-J.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - J)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - J

joinSafePrelude
JustSafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-L.html b/static/safe-prelude/doc-index-L.html new file mode 100644 index 0000000..b2148c4 --- /dev/null +++ b/static/safe-prelude/doc-index-L.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - L)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - L

LeftSafePrelude
leftsSafePrelude
lengthSafePrelude
liftSafePrelude
liftASafePrelude
liftA2SafePrelude
liftA3SafePrelude
liftIOSafePrelude
liftMSafePrelude
listToMaybeSafePrelude
localSafePrelude
logSafePrelude
logBaseSafePrelude
LTSafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-M.html b/static/safe-prelude/doc-index-M.html new file mode 100644 index 0000000..f6225c9 --- /dev/null +++ b/static/safe-prelude/doc-index-M.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - M)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - M

manySafePrelude
MapSafePrelude
mapAccumLSafePrelude
mapAccumRSafePrelude
mapMSafePrelude
mapMaybeSafePrelude
mapM_SafePrelude
mappendSafePrelude
maxSafePrelude
maxBoundSafePrelude
MaybeSafePrelude
maybeSafePrelude
mconcatSafePrelude
memptySafePrelude
minSafePrelude
minBoundSafePrelude
mkWeakIORefSafePrelude
mkWeakMVarSafePrelude
modSafePrelude
modifyIORefSafePrelude
modifyIORef'SafePrelude
modifyMVarSafePrelude
modifyMVarMaskedSafePrelude
modifyMVarMasked_SafePrelude
modifyMVar_SafePrelude
MonadSafePrelude
MonadCatchSafePrelude
MonadIOSafePrelude
MonadMaskSafePrelude
MonadReaderSafePrelude
MonadThrowSafePrelude
MonadTransSafePrelude
MonoidSafePrelude
msumSafePrelude
MVarSafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-N.html b/static/safe-prelude/doc-index-N.html new file mode 100644 index 0000000..0950e94 --- /dev/null +++ b/static/safe-prelude/doc-index-N.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - N)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - N

negateSafePrelude
newChanSafePrelude
newEmptyMVarSafePrelude
newIORefSafePrelude
newMVarSafePrelude
NFDataSafePrelude
notSafePrelude
notElemSafePrelude
NothingSafePrelude
nullSafePrelude
NumSafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-O.html b/static/safe-prelude/doc-index-O.html new file mode 100644 index 0000000..2c2380a --- /dev/null +++ b/static/safe-prelude/doc-index-O.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - O)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - O

oddSafePrelude
onSafePrelude
onExceptionSafePrelude
optionalSafePrelude
orSafePrelude
OrdSafePrelude
OrderingSafePrelude
otherwiseSafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-P.html b/static/safe-prelude/doc-index-P.html new file mode 100644 index 0000000..f1e15ee --- /dev/null +++ b/static/safe-prelude/doc-index-P.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - P)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - P

partitionEithersSafePrelude
piSafePrelude
productSafePrelude
properFractionSafePrelude
Proxy 
1 (Data Constructor)SafePrelude
2 (Type/Class)SafePrelude
pureSafePrelude
putMVarSafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-Q.html b/static/safe-prelude/doc-index-Q.html new file mode 100644 index 0000000..24aa1ca --- /dev/null +++ b/static/safe-prelude/doc-index-Q.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - Q)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - Q

quotSafePrelude
quotRemSafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-R.html b/static/safe-prelude/doc-index-R.html new file mode 100644 index 0000000..bfc8131 --- /dev/null +++ b/static/safe-prelude/doc-index-R.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - R)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - R

RationalSafePrelude
ReadSafePrelude
readChanSafePrelude
readEitherSafePrelude
readerSafePrelude
readFileSafePrelude
readFileUtf8SafePrelude
readIORefSafePrelude
readListSafePrelude
readListPrecSafePrelude
readMaybeSafePrelude
ReadModeSafePrelude
readMVarSafePrelude
readPrecSafePrelude
readsPrecSafePrelude
ReadWriteModeSafePrelude
RealSafePrelude
RealFloatSafePrelude
RealFracSafePrelude
realToFracSafePrelude
recipSafePrelude
remSafePrelude
replicateM_SafePrelude
returnSafePrelude
RightSafePrelude
rightsSafePrelude
rnfSafePrelude
roundSafePrelude
runIdentitySafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-S.html b/static/safe-prelude/doc-index-S.html new file mode 100644 index 0000000..314cfce --- /dev/null +++ b/static/safe-prelude/doc-index-S.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - S)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - S

saySafePrelude
sayErrSafePrelude
sayErrShowSafePrelude
sayErrStringSafePrelude
sayShowSafePrelude
sayStringSafePrelude
scaleFloatSafePrelude
sconcatSafePrelude
SemigroupSafePrelude
SeqSafePrelude
seqSafePrelude
sequenceSafePrelude
sequenceASafePrelude
sequenceA_SafePrelude
sequence_SafePrelude
SetSafePrelude
ShowSafePrelude
showSafePrelude
showListSafePrelude
showsPrecSafePrelude
significandSafePrelude
signumSafePrelude
sinSafePrelude
sinhSafePrelude
sndSafePrelude
someSafePrelude
SomeAsyncException 
1 (Data Constructor)SafePrelude
2 (Type/Class)SafePrelude
SomeException 
1 (Data Constructor)SafePrelude
2 (Type/Class)SafePrelude
sqrtSafePrelude
stderrSafePrelude
stdinSafePrelude
stdoutSafePrelude
stimesSafePrelude
StringSafePrelude
subtractSafePrelude
sumSafePrelude
swapMVarSafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-T.html b/static/safe-prelude/doc-index-T.html new file mode 100644 index 0000000..da11ff3 --- /dev/null +++ b/static/safe-prelude/doc-index-T.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - T)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - T

takeMVarSafePrelude
tanSafePrelude
tanhSafePrelude
TextSafePrelude
threadDelaySafePrelude
throwIOSafePrelude
throwMSafePrelude
throwToSafePrelude
toExceptionSafePrelude
toIntegerSafePrelude
toListSafePrelude
toRationalSafePrelude
TraversableSafePrelude
traverseSafePrelude
traverse_SafePrelude
TrueSafePrelude
truncateSafePrelude
trySafePrelude
tryAnySafePrelude
tryAnyDeepSafePrelude
tryDeepSafePrelude
tryIOSafePrelude
tryPutMVarSafePrelude
tryReadMVarSafePrelude
tryTakeMVarSafePrelude
TypeableSafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-U.html b/static/safe-prelude/doc-index-U.html new file mode 100644 index 0000000..1890df9 --- /dev/null +++ b/static/safe-prelude/doc-index-U.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - U)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - U

uncurrySafePrelude
unlessSafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-V.html b/static/safe-prelude/doc-index-V.html new file mode 100644 index 0000000..2337e67 --- /dev/null +++ b/static/safe-prelude/doc-index-V.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - V)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - V

voidSafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index-W.html b/static/safe-prelude/doc-index-W.html new file mode 100644 index 0000000..5872b60 --- /dev/null +++ b/static/safe-prelude/doc-index-W.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index - W)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

Index - W

whenSafePrelude
withBinaryFileSafePrelude
withExceptionSafePrelude
withMVarSafePrelude
withMVarMaskedSafePrelude
WordSafePrelude
Word16SafePrelude
Word32SafePrelude
Word64SafePrelude
Word8SafePrelude
writeChanSafePrelude
writeFileSafePrelude
writeFileUtf8SafePrelude
writeIORefSafePrelude
WriteModeSafePrelude
\ No newline at end of file diff --git a/static/safe-prelude/doc-index.html b/static/safe-prelude/doc-index.html new file mode 100644 index 0000000..746ffe8 --- /dev/null +++ b/static/safe-prelude/doc-index.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety (Index)

safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

\ No newline at end of file diff --git a/static/safe-prelude/frames.html b/static/safe-prelude/frames.html new file mode 100644 index 0000000..e86edb6 --- /dev/null +++ b/static/safe-prelude/frames.html @@ -0,0 +1,30 @@ + + + + + + + + + + + + + + + diff --git a/static/safe-prelude/haddock-util.js b/static/safe-prelude/haddock-util.js new file mode 100644 index 0000000..fc7743f --- /dev/null +++ b/static/safe-prelude/haddock-util.js @@ -0,0 +1,344 @@ +// Haddock JavaScript utilities + +var rspace = /\s\s+/g, + rtrim = /^\s+|\s+$/g; + +function spaced(s) { return (" " + s + " ").replace(rspace, " "); } +function trim(s) { return s.replace(rtrim, ""); } + +function hasClass(elem, value) { + var className = spaced(elem.className || ""); + return className.indexOf( " " + value + " " ) >= 0; +} + +function addClass(elem, value) { + var className = spaced(elem.className || ""); + if ( className.indexOf( " " + value + " " ) < 0 ) { + elem.className = trim(className + " " + value); + } +} + +function removeClass(elem, value) { + var className = spaced(elem.className || ""); + className = className.replace(" " + value + " ", " "); + elem.className = trim(className); +} + +function toggleClass(elem, valueOn, valueOff, bool) { + if (bool == null) { bool = ! hasClass(elem, valueOn); } + if (bool) { + removeClass(elem, valueOff); + addClass(elem, valueOn); + } + else { + removeClass(elem, valueOn); + addClass(elem, valueOff); + } + return bool; +} + + +function makeClassToggle(valueOn, valueOff) +{ + return function(elem, bool) { + return toggleClass(elem, valueOn, valueOff, bool); + } +} + +toggleShow = makeClassToggle("show", "hide"); +toggleCollapser = makeClassToggle("collapser", "expander"); + +function toggleSection(id) +{ + var b = toggleShow(document.getElementById("section." + id)); + toggleCollapser(document.getElementById("control." + id), b); + rememberCollapsed(id, b); + return b; +} + +var collapsed = {}; +function rememberCollapsed(id, b) +{ + if(b) + delete collapsed[id] + else + collapsed[id] = null; + + var sections = []; + for(var i in collapsed) + { + if(collapsed.hasOwnProperty(i)) + sections.push(i); + } + // cookie specific to this page; don't use setCookie which sets path=/ + document.cookie = "collapsed=" + escape(sections.join('+')); +} + +function restoreCollapsed() +{ + var cookie = getCookie("collapsed"); + if(!cookie) + return; + + var ids = cookie.split('+'); + for(var i in ids) + { + if(document.getElementById("section." + ids[i])) + toggleSection(ids[i]); + } +} + +function setCookie(name, value) { + document.cookie = name + "=" + escape(value) + ";path=/;"; +} + +function clearCookie(name) { + document.cookie = name + "=;path=/;expires=Thu, 01-Jan-1970 00:00:01 GMT;"; +} + +function getCookie(name) { + var nameEQ = name + "="; + var ca = document.cookie.split(';'); + for(var i=0;i < ca.length;i++) { + var c = ca[i]; + while (c.charAt(0)==' ') c = c.substring(1,c.length); + if (c.indexOf(nameEQ) == 0) { + return unescape(c.substring(nameEQ.length,c.length)); + } + } + return null; +} + + + +var max_results = 75; // 50 is not enough to search for map in the base libraries +var shown_range = null; +var last_search = null; + +function quick_search() +{ + perform_search(false); +} + +function full_search() +{ + perform_search(true); +} + + +function perform_search(full) +{ + var text = document.getElementById("searchbox").value.toLowerCase(); + if (text == last_search && !full) return; + last_search = text; + + var table = document.getElementById("indexlist"); + var status = document.getElementById("searchmsg"); + var children = table.firstChild.childNodes; + + // first figure out the first node with the prefix + var first = bisect(-1); + var last = (first == -1 ? -1 : bisect(1)); + + if (first == -1) + { + table.className = ""; + status.innerHTML = "No results found, displaying all"; + } + else if (first == 0 && last == children.length - 1) + { + table.className = ""; + status.innerHTML = ""; + } + else if (last - first >= max_results && !full) + { + table.className = ""; + status.innerHTML = "More than " + max_results + ", press Search to display"; + } + else + { + // decide what you need to clear/show + if (shown_range) + setclass(shown_range[0], shown_range[1], "indexrow"); + setclass(first, last, "indexshow"); + shown_range = [first, last]; + table.className = "indexsearch"; + status.innerHTML = ""; + } + + + function setclass(first, last, status) + { + for (var i = first; i <= last; i++) + { + children[i].className = status; + } + } + + + // do a binary search, treating 0 as ... + // return either -1 (no 0's found) or location of most far match + function bisect(dir) + { + var first = 0, finish = children.length - 1; + var mid, success = false; + + while (finish - first > 3) + { + mid = Math.floor((finish + first) / 2); + + var i = checkitem(mid); + if (i == 0) i = dir; + if (i == -1) + finish = mid; + else + first = mid; + } + var a = (dir == 1 ? first : finish); + var b = (dir == 1 ? finish : first); + for (var i = b; i != a - dir; i -= dir) + { + if (checkitem(i) == 0) return i; + } + return -1; + } + + + // from an index, decide what the result is + // 0 = match, -1 is lower, 1 is higher + function checkitem(i) + { + var s = getitem(i).toLowerCase().substr(0, text.length); + if (s == text) return 0; + else return (s > text ? -1 : 1); + } + + + // from an index, get its string + // this abstracts over alternates + function getitem(i) + { + for ( ; i >= 0; i--) + { + var s = children[i].firstChild.firstChild.data; + if (s.indexOf(' ') == -1) + return s; + } + return ""; // should never be reached + } +} + +function setSynopsis(filename) { + if (parent.window.synopsis && parent.window.synopsis.location) { + if (parent.window.synopsis.location.replace) { + // In Firefox this avoids adding the change to the history. + parent.window.synopsis.location.replace(filename); + } else { + parent.window.synopsis.location = filename; + } + } +} + +function addMenuItem(html) { + var menu = document.getElementById("page-menu"); + if (menu) { + var btn = menu.firstChild.cloneNode(false); + btn.innerHTML = html; + menu.appendChild(btn); + } +} + +function adjustForFrames() { + var bodyCls; + + if (parent.location.href == window.location.href) { + // not in frames, so add Frames button + addMenuItem("Frames"); + bodyCls = "no-frame"; + } + else { + bodyCls = "in-frame"; + } + addClass(document.body, bodyCls); +} + +function reframe() { + setCookie("haddock-reframe", document.URL); + window.location = "frames.html"; +} + +function postReframe() { + var s = getCookie("haddock-reframe"); + if (s) { + parent.window.main.location = s; + clearCookie("haddock-reframe"); + } +} + +function styles() { + var i, a, es = document.getElementsByTagName("link"), rs = []; + for (i = 0; a = es[i]; i++) { + if(a.rel.indexOf("style") != -1 && a.title) { + rs.push(a); + } + } + return rs; +} + +function addStyleMenu() { + var as = styles(); + var i, a, btns = ""; + for(i=0; a = as[i]; i++) { + btns += "
  • " + + a.title + "
  • " + } + if (as.length > 1) { + var h = "
    " + + "Style ▾" + + "" + + "
    "; + addMenuItem(h); + } +} + +function setActiveStyleSheet(title) { + var as = styles(); + var i, a, found; + for(i=0; a = as[i]; i++) { + a.disabled = true; + // need to do this always, some browsers are edge triggered + if(a.title == title) { + found = a; + } + } + if (found) { + found.disabled = false; + setCookie("haddock-style", title); + } + else { + as[0].disabled = false; + clearCookie("haddock-style"); + } + styleMenu(false); +} + +function resetStyle() { + var s = getCookie("haddock-style"); + if (s) setActiveStyleSheet(s); +} + + +function styleMenu(show) { + var m = document.getElementById('style-menu'); + if (m) toggleShow(m, show); +} + + +function pageLoad() { + addStyleMenu(); + adjustForFrames(); + resetStyle(); + restoreCollapsed(); +} + diff --git a/static/safe-prelude/hslogo-16.png b/static/safe-prelude/hslogo-16.png new file mode 100644 index 0000000..0ff8579 Binary files /dev/null and b/static/safe-prelude/hslogo-16.png differ diff --git a/static/safe-prelude/index-frames.html b/static/safe-prelude/index-frames.html new file mode 100644 index 0000000..42db267 --- /dev/null +++ b/static/safe-prelude/index-frames.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

    Modules

    \ No newline at end of file diff --git a/static/safe-prelude/index.html b/static/safe-prelude/index.html new file mode 100644 index 0000000..b1b34c7 --- /dev/null +++ b/static/safe-prelude/index.html @@ -0,0 +1,4 @@ +safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

    safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

    safe-prelude-0.1.0.0: A Haskell prelude optimized for safety

    Please see README.md

    Modules

    \ No newline at end of file diff --git a/static/safe-prelude/mini_SafePrelude.html b/static/safe-prelude/mini_SafePrelude.html new file mode 100644 index 0000000..e2cf42b --- /dev/null +++ b/static/safe-prelude/mini_SafePrelude.html @@ -0,0 +1,4 @@ +SafePrelude

    SafePrelude

    Types

    data Maybe a

    data Ordering

    data Bool

    data Char

    data IO a

    data Either a b

    data ByteString

    data Text

    data Map k a

    data HashMap k v

    data IntMap a

    data Set a

    data HashSet a

    data IntSet

    data Seq a

    data Identity a

    data SomeException

    data SomeAsyncException

    type String

    type FilePath

    Numbers

    data Word

    data Word8

    data Word16

    data Word32

    data Word64

    data Int

    data Int8

    data Int16

    data Int32

    data Int64

    data Integer

    type Rational

    data Float

    data Double

    data Proxy k t

    Type classes

    class Ord a

    class Eq a

    class Bounded a

    class Show a

    class Read a

    class Functor f

    class Applicative f

    class Alternative f

    class Monad m

    class MonadIO m

    class MonadTrans t

    class MonadReader r m

    class MonadThrow m

    class Exception e

    class MonadCatch m

    class MonadMask m

    class Foldable t

    toList

    null

    length

    elem

    class Traversable t

    class Typeable k a

    class IsString a

    class Hashable a

    class Semigroup a

    class Monoid a

    Numeric

    class Num a

    class Real a

    class Integral a

    class Fractional a

    class Floating a

    class RealFrac a

    class RealFloat a

    Functions

    ($)

    (&)

    ($!)

    (&&)

    (||)

    (.)

    not

    otherwise

    fst

    snd

    id

    maybe

    either

    flip

    const

    odd

    even

    uncurry

    curry

    asTypeOf

    seq

    fix

    Numeric

    (^)

    (^^)

    subtract

    fromIntegral

    realToFrac

    Foldable

    sum

    product

    foldrM

    foldlM

    traverse_

    for_

    sequenceA_

    asum

    mapM_

    forM_

    sequence_

    msum

    concat

    concatMap

    and

    or

    any

    all

    notElem

    find

    Traversable

    mapM

    sequence

    for

    forM

    mapAccumL

    mapAccumR

    Functor

    ($>)

    (<$>)

    void

    Applicative

    liftA

    liftA2

    liftA3

    Alternative

    optional

    Monad

    (=<<)

    (>=>)

    (<=<)

    forever

    join

    foldM

    foldM_

    replicateM_

    guard

    when

    unless

    liftM

    ap

    (<$!>)

    Concurrent

    threadDelay

    data MVar a

    newEmptyMVar

    newMVar

    takeMVar

    putMVar

    readMVar

    swapMVar

    tryTakeMVar

    tryPutMVar

    isEmptyMVar

    withMVar

    withMVarMasked

    modifyMVar_

    modifyMVar

    modifyMVarMasked_

    modifyMVarMasked

    tryReadMVar

    mkWeakMVar

    data Chan a

    newChan

    writeChan

    readChan

    dupChan

    Reader

    asks

    Exceptions

    throwIO

    throwM

    throwTo

    catch

    catchIO

    catchAny

    catchDeep

    catchAnyDeep

    handle

    handleIO

    handleAny

    handleDeep

    handleAnyDeep

    try

    tryIO

    tryAny

    tryDeep

    tryAnyDeep

    onException

    bracket

    bracket_

    finally

    withException

    bracketOnError

    bracketOnError_

    displayException

    Arrow

    (&&&)

    (***)

    Maybe

    mapMaybe

    catMaybes

    fromMaybe

    isJust

    isNothing

    listToMaybe

    Either

    partitionEithers

    lefts

    rights

    Ord

    on

    comparing

    Say

    say

    sayString

    sayShow

    sayErr

    sayErrString

    sayErrShow

    hSay

    hSayString

    hSayShow

    IORef

    data IORef a

    newIORef

    readIORef

    writeIORef

    modifyIORef

    modifyIORef'

    atomicModifyIORef

    atomicModifyIORef'

    atomicWriteIORef

    mkWeakIORef

    IO

    data Handle

    data IOMode

    stdin

    stdout

    stderr

    hClose

    withBinaryFile

    readFile

    writeFile

    readFileUtf8

    writeFileUtf8

    Character encoding

    encodeUtf8

    decodeUtf8

    deepseq

    class NFData a

    deepseq

    ($!!)

    force

    Monoids

    (++)

    Read

    readMaybe

    readEither

    \ No newline at end of file diff --git a/static/safe-prelude/minus.gif b/static/safe-prelude/minus.gif new file mode 100644 index 0000000..1deac2f Binary files /dev/null and b/static/safe-prelude/minus.gif differ diff --git a/static/safe-prelude/ocean.css b/static/safe-prelude/ocean.css new file mode 100644 index 0000000..3ebb14d --- /dev/null +++ b/static/safe-prelude/ocean.css @@ -0,0 +1,610 @@ +/* @group Fundamentals */ + +* { margin: 0; padding: 0 } + +/* Is this portable? */ +html { + background-color: white; + width: 100%; + height: 100%; +} + +body { + background: white; + color: black; + text-align: left; + min-height: 100%; + position: relative; +} + +p { + margin: 0.8em 0; +} + +ul, ol { + margin: 0.8em 0 0.8em 2em; +} + +dl { + margin: 0.8em 0; +} + +dt { + font-weight: bold; +} +dd { + margin-left: 2em; +} + +a { text-decoration: none; } +a[href]:link { color: rgb(196,69,29); } +a[href]:visited { color: rgb(171,105,84); } +a[href]:hover { text-decoration:underline; } + +a[href].def:link, a[href].def:visited { color: black; } +a[href].def:hover { color: rgb(78, 98, 114); } + +/* @end */ + +/* @group Fonts & Sizes */ + +/* Basic technique & IE workarounds from YUI 3 + For reasons, see: + http://yui.yahooapis.com/3.1.1/build/cssfonts/fonts.css + */ + +body { + font:13px/1.4 sans-serif; + *font-size:small; /* for IE */ + *font:x-small; /* for IE in quirks mode */ +} + +h1 { font-size: 146.5%; /* 19pt */ } +h2 { font-size: 131%; /* 17pt */ } +h3 { font-size: 116%; /* 15pt */ } +h4 { font-size: 100%; /* 13pt */ } +h5 { font-size: 100%; /* 13pt */ } + +select, input, button, textarea { + font:99% sans-serif; +} + +table { + font-size:inherit; + font:100%; +} + +pre, code, kbd, samp, tt, .src { + font-family:monospace; + *font-size:108%; + line-height: 124%; +} + +.links, .link { + font-size: 85%; /* 11pt */ +} + +#module-header .caption { + font-size: 182%; /* 24pt */ +} + +.info { + font-size: 85%; /* 11pt */ +} + +#table-of-contents, #synopsis { + /* font-size: 85%; /* 11pt */ +} + + +/* @end */ + +/* @group Common */ + +.caption, h1, h2, h3, h4, h5, h6 { + font-weight: bold; + color: rgb(78,98,114); + margin: 0.8em 0 0.4em; +} + +* + h1, * + h2, * + h3, * + h4, * + h5, * + h6 { + margin-top: 2em; +} + +h1 + h2, h2 + h3, h3 + h4, h4 + h5, h5 + h6 { + margin-top: inherit; +} + +ul.links { + list-style: none; + text-align: left; + float: right; + display: inline-table; + margin: 0 0 0 1em; +} + +ul.links li { + display: inline; + border-left: 1px solid #d5d5d5; + white-space: nowrap; + padding: 0; +} + +ul.links li a { + padding: 0.2em 0.5em; +} + +.hide { display: none; } +.show { display: inherit; } +.clear { clear: both; } + +.collapser { + background-image: url(minus.gif); + background-repeat: no-repeat; +} +.expander { + background-image: url(plus.gif); + background-repeat: no-repeat; +} +.collapser, .expander { + padding-left: 14px; + margin-left: -14px; + cursor: pointer; +} +p.caption.collapser, +p.caption.expander { + background-position: 0 0.4em; +} + +.instance.collapser, .instance.expander { + margin-left: 0px; + background-position: left center; + min-width: 9px; + min-height: 9px; +} + + +pre { + padding: 0.25em; + margin: 0.8em 0; + background: rgb(229,237,244); + overflow: auto; + border-bottom: 0.25em solid white; + /* white border adds some space below the box to compensate + for visual extra space that paragraphs have between baseline + and the bounding box */ +} + +.src { + background: #f0f0f0; + padding: 0.2em 0.5em; +} + +.keyword { font-weight: normal; } +.def { font-weight: bold; } + +@media print { + #footer { display: none; } +} + +/* @end */ + +/* @group Page Structure */ + +#content { + margin: 0 auto; + padding: 0 2em 6em; +} + +#package-header { + background: rgb(41,56,69); + border-top: 5px solid rgb(78,98,114); + color: #ddd; + padding: 0.2em; + position: relative; + text-align: left; +} + +#package-header .caption { + background: url(hslogo-16.png) no-repeat 0em; + color: white; + margin: 0 2em; + font-weight: normal; + font-style: normal; + padding-left: 2em; +} + +#package-header a:link, #package-header a:visited { color: white; } +#package-header a:hover { background: rgb(78,98,114); } + +#module-header .caption { + color: rgb(78,98,114); + font-weight: bold; + border-bottom: 1px solid #ddd; +} + +table.info { + float: right; + padding: 0.5em 1em; + border: 1px solid #ddd; + color: rgb(78,98,114); + background-color: #fff; + max-width: 40%; + border-spacing: 0; + position: relative; + top: -0.5em; + margin: 0 0 0 2em; +} + +.info th { + padding: 0 1em 0 0; +} + +div#style-menu-holder { + position: relative; + z-index: 2; + display: inline; +} + +#style-menu { + position: absolute; + z-index: 1; + overflow: visible; + background: #374c5e; + margin: 0; + text-align: center; + right: 0; + padding: 0; + top: 1.25em; +} + +#style-menu li { + display: list-item; + border-style: none; + margin: 0; + padding: 0; + color: #000; + list-style-type: none; +} + +#style-menu li + li { + border-top: 1px solid #919191; +} + +#style-menu a { + width: 6em; + padding: 3px; + display: block; +} + +#footer { + background: #ddd; + border-top: 1px solid #aaa; + padding: 0.5em 0; + color: #666; + text-align: center; + position: absolute; + bottom: 0; + width: 100%; + height: 3em; +} + +/* @end */ + +/* @group Front Matter */ + +#table-of-contents { + float: right; + clear: right; + background: #faf9dc; + border: 1px solid #d8d7ad; + padding: 0.5em 1em; + max-width: 20em; + margin: 0.5em 0 1em 1em; +} + +#table-of-contents .caption { + text-align: center; + margin: 0; +} + +#table-of-contents ul { + list-style: none; + margin: 0; +} + +#table-of-contents ul ul { + margin-left: 2em; +} + +#description .caption { + display: none; +} + +#synopsis { + display: none; +} + +.no-frame #synopsis { + display: block; + position: fixed; + right: 0; + height: 80%; + top: 10%; + padding: 0; + max-width: 75%; +} + +#synopsis .caption { + float: left; + width: 29px; + color: rgba(255,255,255,0); + height: 110px; + margin: 0; + font-size: 1px; + padding: 0; +} + +#synopsis p.caption.collapser { + background: url(synopsis.png) no-repeat -64px -8px; +} + +#synopsis p.caption.expander { + background: url(synopsis.png) no-repeat 0px -8px; +} + +#synopsis ul { + height: 100%; + overflow: auto; + padding: 0.5em; + margin: 0; +} + +#synopsis ul ul { + overflow: hidden; +} + +#synopsis ul, +#synopsis ul li.src { + background-color: #faf9dc; + white-space: nowrap; + list-style: none; + margin-left: 0; +} + +/* @end */ + +/* @group Main Content */ + +#interface div.top { margin: 2em 0; } +#interface h1 + div.top, +#interface h2 + div.top, +#interface h3 + div.top, +#interface h4 + div.top, +#interface h5 + div.top { + margin-top: 1em; +} +#interface .src .selflink, +#interface .src .link { + float: right; + color: #919191; + background: #f0f0f0; + padding: 0 0.5em 0.2em; + margin: 0 -0.5em 0 0; +} +#interface .src .selflink { + border-left: 1px solid #919191; + margin: 0 -0.5em 0 0.5em; +} + +#interface span.fixity { + color: #919191; + border-left: 1px solid #919191; + padding: 0.2em 0.5em 0.2em 0.5em; + margin: 0 -1em 0 1em; +} + +#interface span.rightedge { + border-left: 1px solid #919191; + padding: 0.2em 0 0.2em 0; + margin: 0 0 0 1em; +} + +#interface table { border-spacing: 2px; } +#interface td { + vertical-align: top; + padding-left: 0.5em; +} +#interface td.src { + white-space: nowrap; +} +#interface td.doc p { + margin: 0; +} +#interface td.doc p + p { + margin-top: 0.8em; +} + +.clearfix:after { + clear: both; + content: " "; + display: block; + height: 0; + visibility: hidden; +} + +.subs ul { + list-style: none; + display: table; + margin: 0; +} + +.subs ul li { + display: table-row; +} + +.subs ul li dfn { + display: table-cell; + font-style: normal; + font-weight: bold; + margin: 1px 0; + white-space: nowrap; +} + +.subs ul li > .doc { + display: table-cell; + padding-left: 0.5em; + margin-bottom: 0.5em; +} + +.subs ul li > .doc p { + margin: 0; +} + +/* Render short-style data instances */ +.inst ul { + height: 100%; + padding: 0.5em; + margin: 0; +} + +.inst, .inst li { + list-style: none; + margin-left: 1em; +} + +/* Workaround for bug in Firefox (issue #384) */ +.inst-left { + float: left; +} + +.top p.src { + border-top: 1px solid #ccc; +} + +.subs, .doc { + /* use this selector for one level of indent */ + padding-left: 2em; +} + +.warning { + color: red; +} + +.arguments { + margin-top: -0.4em; +} +.arguments .caption { + display: none; +} + +.fields { padding-left: 1em; } + +.fields .caption { display: none; } + +.fields p { margin: 0 0; } + +/* this seems bulky to me +.methods, .constructors { + background: #f8f8f8; + border: 1px solid #eee; +} +*/ + +/* @end */ + +/* @group Auxillary Pages */ + + +.extension-list { + list-style-type: none; + margin-left: 0; +} + +#mini { + margin: 0 auto; + padding: 0 1em 1em; +} + +#mini > * { + font-size: 93%; /* 12pt */ +} + +#mini #module-list .caption, +#mini #module-header .caption { + font-size: 125%; /* 15pt */ +} + +#mini #interface h1, +#mini #interface h2, +#mini #interface h3, +#mini #interface h4 { + font-size: 109%; /* 13pt */ + margin: 1em 0 0; +} + +#mini #interface .top, +#mini #interface .src { + margin: 0; +} + +#mini #module-list ul { + list-style: none; + margin: 0; +} + +#alphabet ul { + list-style: none; + padding: 0; + margin: 0.5em 0 0; + text-align: center; +} + +#alphabet li { + display: inline; + margin: 0 0.25em; +} + +#alphabet a { + font-weight: bold; +} + +#index .caption, +#module-list .caption { font-size: 131%; /* 17pt */ } + +#index table { + margin-left: 2em; +} + +#index .src { + font-weight: bold; +} +#index .alt { + font-size: 77%; /* 10pt */ + font-style: italic; + padding-left: 2em; +} + +#index td + td { + padding-left: 1em; +} + +#module-list ul { + list-style: none; + margin: 0 0 0 2em; +} + +#module-list li { + clear: right; +} + +#module-list span.collapser, +#module-list span.expander { + background-position: 0 0.3em; +} + +#module-list .package { + float: right; +} + +/* @end */ diff --git a/static/safe-prelude/plus.gif b/static/safe-prelude/plus.gif new file mode 100644 index 0000000..2d15c14 Binary files /dev/null and b/static/safe-prelude/plus.gif differ diff --git a/static/safe-prelude/safe-prelude.haddock b/static/safe-prelude/safe-prelude.haddock new file mode 100644 index 0000000..59a0013 Binary files /dev/null and b/static/safe-prelude/safe-prelude.haddock differ diff --git a/static/safe-prelude/safe-prelude.txt b/static/safe-prelude/safe-prelude.txt new file mode 100644 index 0000000..788ad9d --- /dev/null +++ b/static/safe-prelude/safe-prelude.txt @@ -0,0 +1,2999 @@ +-- Hoogle documentation, generated by Haddock +-- See Hoogle, http://www.haskell.org/hoogle/ + + +-- | A Haskell prelude optimized for safety +-- +-- Please see README.md +@package safe-prelude +@version 0.1.0.0 + +module SafePrelude + +-- | The Maybe type encapsulates an optional value. A value of type +-- Maybe a either contains a value of type a +-- (represented as Just a), or it is empty (represented +-- as Nothing). Using Maybe is a good way to deal with +-- errors or exceptional cases without resorting to drastic measures such +-- as error. +-- +-- The Maybe type is also a monad. It is a simple kind of error +-- monad, where all errors are represented by Nothing. A richer +-- error monad can be built using the Either type. +data Maybe a :: * -> * +Nothing :: Maybe a +Just :: a -> Maybe a +data Ordering :: * +LT :: Ordering +EQ :: Ordering +GT :: Ordering +data Bool :: * +False :: Bool +True :: Bool + +-- | The character type Char is an enumeration whose values +-- represent Unicode (or equivalently ISO/IEC 10646) characters (see +-- http://www.unicode.org/ for details). This set extends the ISO +-- 8859-1 (Latin-1) character set (the first 256 characters), which is +-- itself an extension of the ASCII character set (the first 128 +-- characters). A character literal in Haskell has type Char. +-- +-- To convert a Char to or from the corresponding Int value +-- defined by Unicode, use toEnum and fromEnum from the +-- Enum class respectively (or equivalently ord and +-- chr). +data Char :: * + +-- | A value of type IO a is a computation which, when +-- performed, does some I/O before returning a value of type a. +-- +-- There is really only one way to "perform" an I/O action: bind it to +-- Main.main in your program. When your program is run, the I/O +-- will be performed. It isn't possible to perform I/O from an arbitrary +-- function, unless that function is itself in the IO monad and +-- called at some point, directly or indirectly, from Main.main. +-- +-- IO is a monad, so IO actions can be combined using +-- either the do-notation or the >> and >>= +-- operations from the Monad class. +data IO a :: * -> * + +-- | The Either type represents values with two possibilities: a +-- value of type Either a b is either Left +-- a or Right b. +-- +-- The Either type is sometimes used to represent a value which is +-- either correct or an error; by convention, the Left constructor +-- is used to hold an error value and the Right constructor is +-- used to hold a correct value (mnemonic: "right" also means "correct"). +-- +--

    Examples

    +-- +-- The type Either String Int is the type +-- of values which can be either a String or an Int. The +-- Left constructor can be used only on Strings, and the +-- Right constructor can be used only on Ints: +-- +--
    +--   >>> let s = Left "foo" :: Either String Int
    +--   
    +--   >>> s
    +--   Left "foo"
    +--   
    +--   >>> let n = Right 3 :: Either String Int
    +--   
    +--   >>> n
    +--   Right 3
    +--   
    +--   >>> :type s
    +--   s :: Either String Int
    +--   
    +--   >>> :type n
    +--   n :: Either String Int
    +--   
    +-- +-- The fmap from our Functor instance will ignore +-- Left values, but will apply the supplied function to values +-- contained in a Right: +-- +--
    +--   >>> let s = Left "foo" :: Either String Int
    +--   
    +--   >>> let n = Right 3 :: Either String Int
    +--   
    +--   >>> fmap (*2) s
    +--   Left "foo"
    +--   
    +--   >>> fmap (*2) n
    +--   Right 6
    +--   
    +-- +-- The Monad instance for Either allows us to chain +-- together multiple actions which may fail, and fail overall if any of +-- the individual steps failed. First we'll write a function that can +-- either parse an Int from a Char, or fail. +-- +--
    +--   >>> import Data.Char ( digitToInt, isDigit )
    +--   
    +--   >>> :{
    +--       let parseEither :: Char -> Either String Int
    +--           parseEither c
    +--             | isDigit c = Right (digitToInt c)
    +--             | otherwise = Left "parse error"
    +--   
    +--   >>> :}
    +--   
    +-- +-- The following should work, since both '1' and '2' +-- can be parsed as Ints. +-- +--
    +--   >>> :{
    +--       let parseMultiple :: Either String Int
    +--           parseMultiple = do
    +--             x <- parseEither '1'
    +--             y <- parseEither '2'
    +--             return (x + y)
    +--   
    +--   >>> :}
    +--   
    +-- +--
    +--   >>> parseMultiple
    +--   Right 3
    +--   
    +-- +-- But the following should fail overall, since the first operation where +-- we attempt to parse 'm' as an Int will fail: +-- +--
    +--   >>> :{
    +--       let parseMultiple :: Either String Int
    +--           parseMultiple = do
    +--             x <- parseEither 'm'
    +--             y <- parseEither '2'
    +--             return (x + y)
    +--   
    +--   >>> :}
    +--   
    +-- +--
    +--   >>> parseMultiple
    +--   Left "parse error"
    +--   
    +data Either a b :: * -> * -> * +Left :: a -> Either a b +Right :: b -> Either a b + +-- | A space-efficient representation of a Word8 vector, supporting +-- many efficient operations. +-- +-- A ByteString contains 8-bit bytes, or by using the operations +-- from Data.ByteString.Char8 it can be interpreted as containing +-- 8-bit characters. +data ByteString :: * + +-- | A space efficient, packed, unboxed Unicode text type. +data Text :: * + +-- | A Map from keys k to values a. +data Map k a :: * -> * -> * + +-- | A map from keys to values. A map cannot contain duplicate keys; each +-- key can map to at most one value. +data HashMap k v :: * -> * -> * + +-- | A map of integers to values a. +data IntMap a :: * -> * + +-- | A set of values a. +data Set a :: * -> * + +-- | A set of values. A set cannot contain duplicate values. +data HashSet a :: * -> * + +-- | A set of integers. +data IntSet :: * + +-- | General-purpose finite sequences. +data Seq a :: * -> * + +-- | Identity functor and monad. (a non-strict monad) +newtype Identity a :: * -> * +Identity :: a -> Identity a +[runIdentity] :: Identity a -> a + +-- | The SomeException type is the root of the exception type +-- hierarchy. When an exception of type e is thrown, behind the +-- scenes it is encapsulated in a SomeException. +data SomeException :: * +[SomeException] :: SomeException + +-- | Superclass for asynchronous exceptions. +data SomeAsyncException :: * +[SomeAsyncException] :: SomeAsyncException + +-- | A String is a list of characters. String constants in Haskell +-- are values of type String. +type String = [Char] + +-- | File and directory names are values of type String, whose +-- precise meaning is operating system dependent. Files can be opened, +-- yielding a handle which can then be used to operate on the contents of +-- that file. +type FilePath = String + +-- | A Word is an unsigned integral type, with the same size as +-- Int. +data Word :: * + +-- | 8-bit unsigned integer type +data Word8 :: * + +-- | 16-bit unsigned integer type +data Word16 :: * + +-- | 32-bit unsigned integer type +data Word32 :: * + +-- | 64-bit unsigned integer type +data Word64 :: * + +-- | A fixed-precision integer type with at least the range [-2^29 .. +-- 2^29-1]. The exact range for a given implementation can be +-- determined by using minBound and maxBound from the +-- Bounded class. +data Int :: * + +-- | 8-bit signed integer type +data Int8 :: * + +-- | 16-bit signed integer type +data Int16 :: * + +-- | 32-bit signed integer type +data Int32 :: * + +-- | 64-bit signed integer type +data Int64 :: * + +-- | Invariant: Jn# and Jp# are used iff value doesn't fit in +-- S# +-- +-- Useful properties resulting from the invariants: +-- +-- +data Integer :: * + +-- | Arbitrary-precision rational numbers, represented as a ratio of two +-- Integer values. A rational number may be constructed using the +-- % operator. +type Rational = Ratio Integer + +-- | Single-precision floating point numbers. It is desirable that this +-- type be at least equal in range and precision to the IEEE +-- single-precision type. +data Float :: * + +-- | Double-precision floating point numbers. It is desirable that this +-- type be at least equal in range and precision to the IEEE +-- double-precision type. +data Double :: * + +-- | A concrete, poly-kinded proxy type +data Proxy k (t :: k) :: forall k. k -> * +Proxy :: Proxy k + +-- | The Ord class is used for totally ordered datatypes. +-- +-- Instances of Ord can be derived for any user-defined datatype +-- whose constituent types are in Ord. The declared order of the +-- constructors in the data declaration determines the ordering in +-- derived Ord instances. The Ordering datatype allows a +-- single comparison to determine the precise ordering of two objects. +-- +-- Minimal complete definition: either compare or <=. +-- Using compare can be more efficient for complex types. +class Eq a => Ord a +compare :: a -> a -> Ordering +(<) :: a -> a -> Bool +(<=) :: a -> a -> Bool +(>) :: a -> a -> Bool +(>=) :: a -> a -> Bool +max :: a -> a -> a +min :: a -> a -> a + +-- | The Eq class defines equality (==) and inequality +-- (/=). All the basic datatypes exported by the Prelude +-- are instances of Eq, and Eq may be derived for any +-- datatype whose constituents are also instances of Eq. +-- +-- Minimal complete definition: either == or /=. +class Eq a +(==) :: a -> a -> Bool +(/=) :: a -> a -> Bool + +-- | The Bounded class is used to name the upper and lower limits of +-- a type. Ord is not a superclass of Bounded since types +-- that are not totally ordered may also have upper and lower bounds. +-- +-- The Bounded class may be derived for any enumeration type; +-- minBound is the first constructor listed in the data +-- declaration and maxBound is the last. Bounded may also +-- be derived for single-constructor datatypes whose constituent types +-- are in Bounded. +class Bounded a +minBound :: a +maxBound :: a + +-- | Conversion of values to readable Strings. +-- +-- Derived instances of Show have the following properties, which +-- are compatible with derived instances of Read: +-- +-- +-- +-- For example, given the declarations +-- +--
    +--   infixr 5 :^:
    +--   data Tree a =  Leaf a  |  Tree a :^: Tree a
    +--   
    +-- +-- the derived instance of Show is equivalent to +-- +--
    +--   instance (Show a) => Show (Tree a) where
    +--   
    +--          showsPrec d (Leaf m) = showParen (d > app_prec) $
    +--               showString "Leaf " . showsPrec (app_prec+1) m
    +--            where app_prec = 10
    +--   
    +--          showsPrec d (u :^: v) = showParen (d > up_prec) $
    +--               showsPrec (up_prec+1) u .
    +--               showString " :^: "      .
    +--               showsPrec (up_prec+1) v
    +--            where up_prec = 5
    +--   
    +-- +-- Note that right-associativity of :^: is ignored. For example, +-- +-- +class Show a + +-- | Convert a value to a readable String. +-- +-- showsPrec should satisfy the law +-- +--
    +--   showsPrec d x r ++ s  ==  showsPrec d x (r ++ s)
    +--   
    +-- +-- Derived instances of Read and Show satisfy the +-- following: +-- +-- +-- +-- That is, readsPrec parses the string produced by +-- showsPrec, and delivers the value that showsPrec started +-- with. +showsPrec :: Int -> a -> ShowS + +-- | A specialised variant of showsPrec, using precedence context +-- zero, and returning an ordinary String. +show :: a -> String + +-- | The method showList is provided to allow the programmer to give +-- a specialised way of showing lists of values. For example, this is +-- used by the predefined Show instance of the Char type, +-- where values of type String should be shown in double quotes, +-- rather than between square brackets. +showList :: [a] -> ShowS + +-- | Parsing of Strings, producing values. +-- +-- Derived instances of Read make the following assumptions, which +-- derived instances of Show obey: +-- +-- +-- +-- For example, given the declarations +-- +--
    +--   infixr 5 :^:
    +--   data Tree a =  Leaf a  |  Tree a :^: Tree a
    +--   
    +-- +-- the derived instance of Read in Haskell 2010 is equivalent to +-- +--
    +--   instance (Read a) => Read (Tree a) where
    +--   
    +--           readsPrec d r =  readParen (d > app_prec)
    +--                            (\r -> [(Leaf m,t) |
    +--                                    ("Leaf",s) <- lex r,
    +--                                    (m,t) <- readsPrec (app_prec+1) s]) r
    +--   
    +--                         ++ readParen (d > up_prec)
    +--                            (\r -> [(u:^:v,w) |
    +--                                    (u,s) <- readsPrec (up_prec+1) r,
    +--                                    (":^:",t) <- lex s,
    +--                                    (v,w) <- readsPrec (up_prec+1) t]) r
    +--   
    +--             where app_prec = 10
    +--                   up_prec = 5
    +--   
    +-- +-- Note that right-associativity of :^: is unused. +-- +-- The derived instance in GHC is equivalent to +-- +--
    +--   instance (Read a) => Read (Tree a) where
    +--   
    +--           readPrec = parens $ (prec app_prec $ do
    +--                                    Ident "Leaf" <- lexP
    +--                                    m <- step readPrec
    +--                                    return (Leaf m))
    +--   
    +--                        +++ (prec up_prec $ do
    +--                                    u <- step readPrec
    +--                                    Symbol ":^:" <- lexP
    +--                                    v <- step readPrec
    +--                                    return (u :^: v))
    +--   
    +--             where app_prec = 10
    +--                   up_prec = 5
    +--   
    +--           readListPrec = readListPrecDefault
    +--   
    +class Read a + +-- | attempts to parse a value from the front of the string, returning a +-- list of (parsed value, remaining string) pairs. If there is no +-- successful parse, the returned list is empty. +-- +-- Derived instances of Read and Show satisfy the +-- following: +-- +-- +-- +-- That is, readsPrec parses the string produced by +-- showsPrec, and delivers the value that showsPrec started +-- with. +readsPrec :: Int -> ReadS a + +-- | The method readList is provided to allow the programmer to give +-- a specialised way of parsing lists of values. For example, this is +-- used by the predefined Read instance of the Char type, +-- where values of type String should be are expected to use +-- double quotes, rather than square brackets. +readList :: ReadS [a] + +-- | Proposed replacement for readsPrec using new-style parsers (GHC +-- only). +readPrec :: ReadPrec a + +-- | Proposed replacement for readList using new-style parsers (GHC +-- only). The default definition uses readList. Instances that +-- define readPrec should also define readListPrec as +-- readListPrecDefault. +readListPrec :: ReadPrec [a] + +-- | The Functor class is used for types that can be mapped over. +-- Instances of Functor should satisfy the following laws: +-- +--
    +--   fmap id  ==  id
    +--   fmap (f . g)  ==  fmap f . fmap g
    +--   
    +-- +-- The instances of Functor for lists, Maybe and IO +-- satisfy these laws. +class Functor (f :: * -> *) +fmap :: (a -> b) -> f a -> f b + +-- | Replace all locations in the input with the same value. The default +-- definition is fmap . const, but this may be +-- overridden with a more efficient version. +(<$) :: a -> f b -> f a + +-- | A functor with application, providing operations to +-- +-- +-- +-- A minimal complete definition must include implementations of these +-- functions satisfying the following laws: +-- +-- +-- +-- The other methods have the following default definitions, which may be +-- overridden with equivalent specialized implementations: +-- +-- +-- +-- As a consequence of these laws, the Functor instance for +-- f will satisfy +-- +-- +-- +-- If f is also a Monad, it should satisfy +-- +-- +-- +-- (which implies that pure and <*> satisfy the +-- applicative functor laws). +class Functor f => Applicative (f :: * -> *) + +-- | Lift a value. +pure :: a -> f a + +-- | Sequential application. +(<*>) :: f (a -> b) -> f a -> f b + +-- | Sequence actions, discarding the value of the first argument. +(*>) :: f a -> f b -> f b + +-- | Sequence actions, discarding the value of the second argument. +(<*) :: f a -> f b -> f a + +-- | A monoid on applicative functors. +-- +-- If defined, some and many should be the least solutions +-- of the equations: +-- +-- +class Applicative f => Alternative (f :: * -> *) + +-- | The identity of <|> +empty :: f a + +-- | An associative binary operation +(<|>) :: f a -> f a -> f a + +-- | One or more. +some :: f a -> f [a] + +-- | Zero or more. +many :: f a -> f [a] + +-- | The Monad class defines the basic operations over a +-- monad, a concept from a branch of mathematics known as +-- category theory. From the perspective of a Haskell programmer, +-- however, it is best to think of a monad as an abstract datatype +-- of actions. Haskell's do expressions provide a convenient +-- syntax for writing monadic expressions. +-- +-- Instances of Monad should satisfy the following laws: +-- +-- +-- +-- Furthermore, the Monad and Applicative operations should +-- relate as follows: +-- +-- +-- +-- The above laws imply: +-- +-- +-- +-- and that pure and (<*>) satisfy the applicative +-- functor laws. +-- +-- The instances of Monad for lists, Maybe and IO +-- defined in the Prelude satisfy these laws. +class Applicative m => Monad (m :: * -> *) + +-- | Sequentially compose two actions, passing any value produced by the +-- first as an argument to the second. +(>>=) :: m a -> (a -> m b) -> m b + +-- | Sequentially compose two actions, discarding any value produced by the +-- first, like sequencing operators (such as the semicolon) in imperative +-- languages. +(>>) :: m a -> m b -> m b + +-- | Inject a value into the monadic type. +return :: a -> m a + +-- | Fail with a message. This operation is not part of the mathematical +-- definition of a monad, but is invoked on pattern-match failure in a +-- do expression. +-- +-- As part of the MonadFail proposal (MFP), this function is moved to its +-- own class MonadFail (see Control.Monad.Fail for more +-- details). The definition here will be removed in a future release. +fail :: String -> m a + +-- | Monads in which IO computations may be embedded. Any monad +-- built by applying a sequence of monad transformers to the IO +-- monad will be an instance of this class. +-- +-- Instances should satisfy the following laws, which state that +-- liftIO is a transformer of monads: +-- +-- +class Monad m => MonadIO (m :: * -> *) + +-- | Lift a computation from the IO monad. +liftIO :: IO a -> m a + +-- | The class of monad transformers. Instances should satisfy the +-- following laws, which state that lift is a monad +-- transformation: +-- +-- +class MonadTrans (t :: (* -> *) -> * -> *) + +-- | Lift a computation from the argument monad to the constructed monad. +lift :: Monad m => m a -> t m a + +-- | See examples in Control.Monad.Reader. Note, the partially +-- applied function type (->) r is a simple reader monad. See +-- the instance declaration below. +class Monad m => MonadReader r (m :: * -> *) | m -> r + +-- | Retrieves the monad environment. +ask :: m r + +-- | Executes a computation in a modified environment. +local :: (r -> r) -> m a -> m a + +-- | Retrieves a function of the current environment. +reader :: (r -> a) -> m a + +-- | A class for monads in which exceptions may be thrown. +-- +-- Instances should obey the following law: +-- +--
    +--   throwM e >> x = throwM e
    +--   
    +-- +-- In other words, throwing an exception short-circuits the rest of the +-- monadic computation. +class Monad m => MonadThrow (m :: * -> *) + +-- | Any type that you wish to throw or catch as an exception must be an +-- instance of the Exception class. The simplest case is a new +-- exception type directly below the root: +-- +--
    +--   data MyException = ThisException | ThatException
    +--       deriving (Show, Typeable)
    +--   
    +--   instance Exception MyException
    +--   
    +-- +-- The default method definitions in the Exception class do what +-- we need in this case. You can now throw and catch +-- ThisException and ThatException as exceptions: +-- +--
    +--   *Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException))
    +--   Caught ThisException
    +--   
    +-- +-- In more complicated examples, you may wish to define a whole hierarchy +-- of exceptions: +-- +--
    +--   ---------------------------------------------------------------------
    +--   -- Make the root exception type for all the exceptions in a compiler
    +--   
    +--   data SomeCompilerException = forall e . Exception e => SomeCompilerException e
    +--       deriving Typeable
    +--   
    +--   instance Show SomeCompilerException where
    +--       show (SomeCompilerException e) = show e
    +--   
    +--   instance Exception SomeCompilerException
    +--   
    +--   compilerExceptionToException :: Exception e => e -> SomeException
    +--   compilerExceptionToException = toException . SomeCompilerException
    +--   
    +--   compilerExceptionFromException :: Exception e => SomeException -> Maybe e
    +--   compilerExceptionFromException x = do
    +--       SomeCompilerException a <- fromException x
    +--       cast a
    +--   
    +--   ---------------------------------------------------------------------
    +--   -- Make a subhierarchy for exceptions in the frontend of the compiler
    +--   
    +--   data SomeFrontendException = forall e . Exception e => SomeFrontendException e
    +--       deriving Typeable
    +--   
    +--   instance Show SomeFrontendException where
    +--       show (SomeFrontendException e) = show e
    +--   
    +--   instance Exception SomeFrontendException where
    +--       toException = compilerExceptionToException
    +--       fromException = compilerExceptionFromException
    +--   
    +--   frontendExceptionToException :: Exception e => e -> SomeException
    +--   frontendExceptionToException = toException . SomeFrontendException
    +--   
    +--   frontendExceptionFromException :: Exception e => SomeException -> Maybe e
    +--   frontendExceptionFromException x = do
    +--       SomeFrontendException a <- fromException x
    +--       cast a
    +--   
    +--   ---------------------------------------------------------------------
    +--   -- Make an exception type for a particular frontend compiler exception
    +--   
    +--   data MismatchedParentheses = MismatchedParentheses
    +--       deriving (Typeable, Show)
    +--   
    +--   instance Exception MismatchedParentheses where
    +--       toException   = frontendExceptionToException
    +--       fromException = frontendExceptionFromException
    +--   
    +-- +-- We can now catch a MismatchedParentheses exception as +-- MismatchedParentheses, SomeFrontendException or +-- SomeCompilerException, but not other types, e.g. +-- IOException: +-- +--
    +--   *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses))
    +--   Caught MismatchedParentheses
    +--   *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException))
    +--   Caught MismatchedParentheses
    +--   *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException))
    +--   Caught MismatchedParentheses
    +--   *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: IOException))
    +--   *** Exception: MismatchedParentheses
    +--   
    +class (Typeable * e, Show e) => Exception e +toException :: e -> SomeException +fromException :: SomeException -> Maybe e + +-- | Render this exception value in a human-friendly manner. +-- +-- Default implementation: show. +displayException :: e -> String + +-- | A class for monads which allow exceptions to be caught, in particular +-- exceptions which were thrown by throwM. +-- +-- Instances should obey the following law: +-- +--
    +--   catch (throwM e) f = f e
    +--   
    +-- +-- Note that the ability to catch an exception does not guarantee +-- that we can deal with all possible exit points from a computation. +-- Some monads, such as continuation-based stacks, allow for more than +-- just a success/failure strategy, and therefore catch +-- cannot be used by those monads to properly implement a function +-- such as finally. For more information, see MonadMask. +class MonadThrow m => MonadCatch (m :: * -> *) + +-- | A class for monads which provide for the ability to account for all +-- possible exit points from a computation, and to mask asynchronous +-- exceptions. Continuation-based monads, and stacks such as ErrorT e +-- IO which provide for multiple failure modes, are invalid +-- instances of this class. +-- +-- Note that this package does provide a MonadMask +-- instance for CatchT. This instance is only valid if +-- the base monad provides no ability to provide multiple exit. For +-- example, IO or Either would be invalid base monads, +-- but Reader or State would be acceptable. +-- +-- Instances should ensure that, in the following code: +-- +--
    +--   f `finally` g
    +--   
    +-- +-- The action g is called regardless of what occurs within +-- f, including async exceptions. +class MonadCatch m => MonadMask (m :: * -> *) + +-- | Data structures that can be folded. +-- +-- For example, given a data type +-- +--
    +--   data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
    +--   
    +-- +-- a suitable instance would be +-- +--
    +--   instance Foldable Tree where
    +--      foldMap f Empty = mempty
    +--      foldMap f (Leaf x) = f x
    +--      foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend` foldMap f r
    +--   
    +-- +-- This is suitable even for abstract types, as the monoid is assumed to +-- satisfy the monoid laws. Alternatively, one could define +-- foldr: +-- +--
    +--   instance Foldable Tree where
    +--      foldr f z Empty = z
    +--      foldr f z (Leaf x) = f x z
    +--      foldr f z (Node l k r) = foldr f (f k (foldr f z r)) l
    +--   
    +-- +-- Foldable instances are expected to satisfy the following +-- laws: +-- +--
    +--   foldr f z t = appEndo (foldMap (Endo . f) t ) z
    +--   
    +-- +--
    +--   foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z
    +--   
    +-- +--
    +--   fold = foldMap id
    +--   
    +-- +-- sum, product, maximum, and minimum +-- should all be essentially equivalent to foldMap forms, such +-- as +-- +--
    +--   sum = getSum . foldMap Sum
    +--   
    +-- +-- but may be less defined. +-- +-- If the type is also a Functor instance, it should satisfy +-- +--
    +--   foldMap f = fold . fmap f
    +--   
    +-- +-- which implies that +-- +--
    +--   foldMap f . fmap g = foldMap (f . g)
    +--   
    +class Foldable (t :: * -> *) + +-- | Combine the elements of a structure using a monoid. +fold :: Monoid m => t m -> m + +-- | Map each element of the structure to a monoid, and combine the +-- results. +foldMap :: Monoid m => (a -> m) -> t a -> m + +-- | Right-associative fold of a structure. +-- +-- In the case of lists, foldr, when applied to a binary operator, +-- a starting value (typically the right-identity of the operator), and a +-- list, reduces the list using the binary operator, from right to left: +-- +--
    +--   foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)
    +--   
    +-- +-- Note that, since the head of the resulting expression is produced by +-- an application of the operator to the first element of the list, +-- foldr can produce a terminating expression from an infinite +-- list. +-- +-- For a general Foldable structure this should be semantically +-- identical to, +-- +--
    +--   foldr f z = foldr f z . toList
    +--   
    +foldr :: (a -> b -> b) -> b -> t a -> b + +-- | Right-associative fold of a structure, but with strict application of +-- the operator. +foldr' :: (a -> b -> b) -> b -> t a -> b + +-- | Left-associative fold of a structure. +-- +-- In the case of lists, foldl, when applied to a binary operator, +-- a starting value (typically the left-identity of the operator), and a +-- list, reduces the list using the binary operator, from left to right: +-- +--
    +--   foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn
    +--   
    +-- +-- Note that to produce the outermost application of the operator the +-- entire input list must be traversed. This means that foldl' +-- will diverge if given an infinite list. +-- +-- Also note that if you want an efficient left-fold, you probably want +-- to use foldl' instead of foldl. The reason for this is +-- that latter does not force the "inner" results (e.g. z f +-- x1 in the above example) before applying them to the operator +-- (e.g. to (f x2)). This results in a thunk chain +-- O(n) elements long, which then must be evaluated from the +-- outside-in. +-- +-- For a general Foldable structure this should be semantically +-- identical to, +-- +--
    +--   foldl f z = foldl f z . toList
    +--   
    +foldl :: (b -> a -> b) -> b -> t a -> b + +-- | Left-associative fold of a structure but with strict application of +-- the operator. +-- +-- This ensures that each step of the fold is forced to weak head normal +-- form before being applied, avoiding the collection of thunks that +-- would otherwise occur. This is often what you want to strictly reduce +-- a finite list to a single, monolithic result (e.g. length). +-- +-- For a general Foldable structure this should be semantically +-- identical to, +-- +--
    +--   foldl f z = foldl' f z . toList
    +--   
    +foldl' :: (b -> a -> b) -> b -> t a -> b + +-- | List of elements of a structure, from left to right. +toList :: t a -> [a] + +-- | Test whether the structure is empty. The default implementation is +-- optimized for structures that are similar to cons-lists, because there +-- is no general way to do better. +null :: t a -> Bool + +-- | Returns the size/length of a finite structure as an Int. The +-- default implementation is optimized for structures that are similar to +-- cons-lists, because there is no general way to do better. +length :: t a -> Int + +-- | Does the element occur in the structure? +elem :: Eq a => a -> t a -> Bool + +-- | List of elements of a structure, from left to right. +toList :: Foldable t => forall a. t a -> [a] + +-- | Test whether the structure is empty. The default implementation is +-- optimized for structures that are similar to cons-lists, because there +-- is no general way to do better. +null :: Foldable t => forall a. t a -> Bool + +-- | Returns the size/length of a finite structure as an Int. The +-- default implementation is optimized for structures that are similar to +-- cons-lists, because there is no general way to do better. +length :: Foldable t => forall a. t a -> Int + +-- | Does the element occur in the structure? +elem :: Foldable t => forall a. Eq a => a -> t a -> Bool + +-- | Functors representing data structures that can be traversed from left +-- to right. +-- +-- A definition of traverse must satisfy the following laws: +-- +-- +-- +-- A definition of sequenceA must satisfy the following laws: +-- +-- +-- +-- where an applicative transformation is a function +-- +--
    +--   t :: (Applicative f, Applicative g) => f a -> g a
    +--   
    +-- +-- preserving the Applicative operations, i.e. +-- +-- +-- +-- and the identity functor Identity and composition of functors +-- Compose are defined as +-- +--
    +--   newtype Identity a = Identity a
    +--   
    +--   instance Functor Identity where
    +--     fmap f (Identity x) = Identity (f x)
    +--   
    +--   instance Applicative Identity where
    +--     pure x = Identity x
    +--     Identity f <*> Identity x = Identity (f x)
    +--   
    +--   newtype Compose f g a = Compose (f (g a))
    +--   
    +--   instance (Functor f, Functor g) => Functor (Compose f g) where
    +--     fmap f (Compose x) = Compose (fmap (fmap f) x)
    +--   
    +--   instance (Applicative f, Applicative g) => Applicative (Compose f g) where
    +--     pure x = Compose (pure (pure x))
    +--     Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)
    +--   
    +-- +-- (The naturality law is implied by parametricity.) +-- +-- Instances are similar to Functor, e.g. given a data type +-- +--
    +--   data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
    +--   
    +-- +-- a suitable instance would be +-- +--
    +--   instance Traversable Tree where
    +--      traverse f Empty = pure Empty
    +--      traverse f (Leaf x) = Leaf <$> f x
    +--      traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r
    +--   
    +-- +-- This is suitable even for abstract types, as the laws for +-- <*> imply a form of associativity. +-- +-- The superclass instances should satisfy the following: +-- +-- +class (Functor t, Foldable t) => Traversable (t :: * -> *) + +-- | Map each element of a structure to an action, evaluate these actions +-- from left to right, and collect the results. For a version that +-- ignores the results see traverse_. +traverse :: Applicative f => (a -> f b) -> t a -> f (t b) + +-- | Evaluate each action in the structure from left to right, and and +-- collect the results. For a version that ignores the results see +-- sequenceA_. +sequenceA :: Applicative f => t (f a) -> f (t a) + +-- | The class Typeable allows a concrete representation of a type +-- to be calculated. +class Typeable k (a :: k) + +-- | Class for string-like datastructures; used by the overloaded string +-- extension (-XOverloadedStrings in GHC). +class IsString a +fromString :: String -> a + +-- | The class of types that can be converted to a hash value. +-- +-- Minimal implementation: hashWithSalt. +class Hashable a + +-- | Return a hash value for the argument, using the given salt. +-- +-- The general contract of hashWithSalt is: +-- +-- +hashWithSalt :: Int -> a -> Int + +-- | Like hashWithSalt, but no salt is used. The default +-- implementation uses hashWithSalt with some default salt. +-- Instances might want to implement this method to provide a more +-- efficient implementation than the default implementation. +hash :: a -> Int + +-- | The class of semigroups (types with an associative binary operation). +class Semigroup a + +-- | An associative operation. +-- +--
    +--   (a <> b) <> c = a <> (b <> c)
    +--   
    +-- +-- If a is also a Monoid we further require +-- +--
    +--   (<>) = mappend
    +--   
    +(<>) :: a -> a -> a + +-- | Reduce a non-empty list with <> +-- +-- The default definition should be sufficient, but this can be +-- overridden for efficiency. +sconcat :: NonEmpty a -> a + +-- | Repeat a value n times. +-- +-- Given that this works on a Semigroup it is allowed to fail if +-- you request 0 or fewer repetitions, and the default definition will do +-- so. +-- +-- By making this a member of the class, idempotent semigroups and +-- monoids can upgrade this to execute in O(1) by picking +-- stimes = stimesIdempotent or stimes = +-- stimesIdempotentMonoid respectively. +stimes :: Integral b => b -> a -> a + +-- | The class of monoids (types with an associative binary operation that +-- has an identity). Instances should satisfy the following laws: +-- +-- +-- +-- The method names refer to the monoid of lists under concatenation, but +-- there are many other instances. +-- +-- Some types can be viewed as a monoid in more than one way, e.g. both +-- addition and multiplication on numbers. In such cases we often define +-- newtypes and make those instances of Monoid, e.g. +-- Sum and Product. +class Monoid a + +-- | Identity of mappend +mempty :: a + +-- | An associative operation +mappend :: a -> a -> a + +-- | Fold a list using the monoid. For most types, the default definition +-- for mconcat will be used, but the function is included in the +-- class definition so that an optimized version can be provided for +-- specific types. +mconcat :: [a] -> a + +-- | Basic numeric class. +class Num a +(+) :: a -> a -> a +(-) :: a -> a -> a +(*) :: a -> a -> a + +-- | Unary negation. +negate :: a -> a + +-- | Absolute value. +abs :: a -> a + +-- | Sign of a number. The functions abs and signum should +-- satisfy the law: +-- +--
    +--   abs x * signum x == x
    +--   
    +-- +-- For real numbers, the signum is either -1 (negative), +-- 0 (zero) or 1 (positive). +signum :: a -> a + +-- | Conversion from an Integer. An integer literal represents the +-- application of the function fromInteger to the appropriate +-- value of type Integer, so such literals have type +-- (Num a) => a. +fromInteger :: Integer -> a +class (Num a, Ord a) => Real a + +-- | the rational equivalent of its real argument with full precision +toRational :: a -> Rational + +-- | Integral numbers, supporting integer division. +class (Real a, Enum a) => Integral a + +-- | integer division truncated toward zero +quot :: a -> a -> a + +-- | integer remainder, satisfying +-- +--
    +--   (x `quot` y)*y + (x `rem` y) == x
    +--   
    +rem :: a -> a -> a + +-- | integer division truncated toward negative infinity +div :: a -> a -> a + +-- | integer modulus, satisfying +-- +--
    +--   (x `div` y)*y + (x `mod` y) == x
    +--   
    +mod :: a -> a -> a + +-- | simultaneous quot and rem +quotRem :: a -> a -> (a, a) + +-- | simultaneous div and mod +divMod :: a -> a -> (a, a) + +-- | conversion to Integer +toInteger :: a -> Integer + +-- | Fractional numbers, supporting real division. +class Num a => Fractional a + +-- | fractional division +(/) :: a -> a -> a + +-- | reciprocal fraction +recip :: a -> a + +-- | Conversion from a Rational (that is Ratio +-- Integer). A floating literal stands for an application of +-- fromRational to a value of type Rational, so such +-- literals have type (Fractional a) => a. +fromRational :: Rational -> a + +-- | Trigonometric and hyperbolic functions and related functions. +class Fractional a => Floating a +pi :: a +exp :: a -> a +log :: a -> a +sqrt :: a -> a +(**) :: a -> a -> a +logBase :: a -> a -> a +sin :: a -> a +cos :: a -> a +tan :: a -> a +asin :: a -> a +acos :: a -> a +atan :: a -> a +sinh :: a -> a +cosh :: a -> a +tanh :: a -> a +asinh :: a -> a +acosh :: a -> a +atanh :: a -> a + +-- | Extracting components of fractions. +class (Real a, Fractional a) => RealFrac a + +-- | The function properFraction takes a real fractional number +-- x and returns a pair (n,f) such that x = +-- n+f, and: +-- +-- +-- +-- The default definitions of the ceiling, floor, +-- truncate and round functions are in terms of +-- properFraction. +properFraction :: Integral b => a -> (b, a) + +-- | truncate x returns the integer nearest x +-- between zero and x +truncate :: Integral b => a -> b + +-- | round x returns the nearest integer to x; the +-- even integer if x is equidistant between two integers +round :: Integral b => a -> b + +-- | ceiling x returns the least integer not less than +-- x +ceiling :: Integral b => a -> b + +-- | floor x returns the greatest integer not greater than +-- x +floor :: Integral b => a -> b + +-- | Efficient, machine-independent access to the components of a +-- floating-point number. +class (RealFrac a, Floating a) => RealFloat a + +-- | a constant function, returning the radix of the representation (often +-- 2) +floatRadix :: a -> Integer + +-- | a constant function, returning the number of digits of +-- floatRadix in the significand +floatDigits :: a -> Int + +-- | a constant function, returning the lowest and highest values the +-- exponent may assume +floatRange :: a -> (Int, Int) + +-- | The function decodeFloat applied to a real floating-point +-- number returns the significand expressed as an Integer and an +-- appropriately scaled exponent (an Int). If +-- decodeFloat x yields (m,n), then x +-- is equal in value to m*b^^n, where b is the +-- floating-point radix, and furthermore, either m and +-- n are both zero or else b^(d-1) <= abs m < +-- b^d, where d is the value of floatDigits +-- x. In particular, decodeFloat 0 = (0,0). If the +-- type contains a negative zero, also decodeFloat (-0.0) = +-- (0,0). The result of decodeFloat x is +-- unspecified if either of isNaN x or +-- isInfinite x is True. +decodeFloat :: a -> (Integer, Int) + +-- | encodeFloat performs the inverse of decodeFloat in the +-- sense that for finite x with the exception of -0.0, +-- uncurry encodeFloat (decodeFloat x) = +-- x. encodeFloat m n is one of the two closest +-- representable floating-point numbers to m*b^^n (or +-- ±Infinity if overflow occurs); usually the closer, but if +-- m contains too many bits, the result may be rounded in the +-- wrong direction. +encodeFloat :: Integer -> Int -> a + +-- | exponent corresponds to the second component of +-- decodeFloat. exponent 0 = 0 and for finite +-- nonzero x, exponent x = snd (decodeFloat x) +-- + floatDigits x. If x is a finite floating-point +-- number, it is equal in value to significand x * b ^^ +-- exponent x, where b is the floating-point radix. +-- The behaviour is unspecified on infinite or NaN values. +exponent :: a -> Int + +-- | The first component of decodeFloat, scaled to lie in the open +-- interval (-1,1), either 0.0 or of absolute +-- value >= 1/b, where b is the floating-point +-- radix. The behaviour is unspecified on infinite or NaN +-- values. +significand :: a -> a + +-- | multiplies a floating-point number by an integer power of the radix +scaleFloat :: Int -> a -> a + +-- | True if the argument is an IEEE "not-a-number" (NaN) value +isNaN :: a -> Bool + +-- | True if the argument is an IEEE infinity or negative infinity +isInfinite :: a -> Bool + +-- | True if the argument is too small to be represented in +-- normalized format +isDenormalized :: a -> Bool + +-- | True if the argument is an IEEE negative zero +isNegativeZero :: a -> Bool + +-- | True if the argument is an IEEE floating point number +isIEEE :: a -> Bool + +-- | a version of arctangent taking two real floating-point arguments. For +-- real floating x and y, atan2 y x +-- computes the angle (from the positive x-axis) of the vector from the +-- origin to the point (x,y). atan2 y x returns +-- a value in the range [-pi, pi]. It follows the +-- Common Lisp semantics for the origin when signed zeroes are supported. +-- atan2 y 1, with y in a type that is +-- RealFloat, should return the same value as atan +-- y. A default definition of atan2 is provided, but +-- implementors can provide a more accurate implementation. +atan2 :: a -> a -> a + +-- | Application operator. This operator is redundant, since ordinary +-- application (f x) means the same as (f $ x). +-- However, $ has low, right-associative binding precedence, so it +-- sometimes allows parentheses to be omitted; for example: +-- +--
    +--   f $ g $ h x  =  f (g (h x))
    +--   
    +-- +-- It is also useful in higher-order situations, such as map +-- ($ 0) xs, or zipWith ($) fs xs. +($) :: (a -> b) -> a -> b +infixr 0 $ + +-- | & is a reverse application operator. This provides +-- notational convenience. Its precedence is one higher than that of the +-- forward application operator $, which allows & to be +-- nested in $. +(&) :: a -> (a -> b) -> b +infixl 1 & + +-- | Strict (call-by-value) application operator. It takes a function and +-- an argument, evaluates the argument to weak head normal form (WHNF), +-- then calls the function with that value. +($!) :: (a -> b) -> a -> b +infixr 0 $! + +-- | Boolean "and" +(&&) :: Bool -> Bool -> Bool +infixr 3 && + +-- | Boolean "or" +(||) :: Bool -> Bool -> Bool +infixr 2 || + +-- | Function composition. +(.) :: (b -> c) -> (a -> b) -> a -> c +infixr 9 . + +-- | Boolean "not" +not :: Bool -> Bool + +-- | otherwise is defined as the value True. It helps to make +-- guards more readable. eg. +-- +--
    +--   f x | x < 0     = ...
    +--       | otherwise = ...
    +--   
    +otherwise :: Bool + +-- | Extract the first component of a pair. +fst :: (a, b) -> a + +-- | Extract the second component of a pair. +snd :: (a, b) -> b + +-- | Identity function. +id :: a -> a + +-- | The maybe function takes a default value, a function, and a +-- Maybe value. If the Maybe value is Nothing, the +-- function returns the default value. Otherwise, it applies the function +-- to the value inside the Just and returns the result. +-- +--

    Examples

    +-- +-- Basic usage: +-- +--
    +--   >>> maybe False odd (Just 3)
    +--   True
    +--   
    +-- +--
    +--   >>> maybe False odd Nothing
    +--   False
    +--   
    +-- +-- Read an integer from a string using readMaybe. If we succeed, +-- return twice the integer; that is, apply (*2) to it. If +-- instead we fail to parse an integer, return 0 by default: +-- +--
    +--   >>> import Text.Read ( readMaybe )
    +--   
    +--   >>> maybe 0 (*2) (readMaybe "5")
    +--   10
    +--   
    +--   >>> maybe 0 (*2) (readMaybe "")
    +--   0
    +--   
    +-- +-- Apply show to a Maybe Int. If we have Just +-- n, we want to show the underlying Int n. But if +-- we have Nothing, we return the empty string instead of (for +-- example) "Nothing": +-- +--
    +--   >>> maybe "" show (Just 5)
    +--   "5"
    +--   
    +--   >>> maybe "" show Nothing
    +--   ""
    +--   
    +maybe :: b -> (a -> b) -> Maybe a -> b + +-- | Case analysis for the Either type. If the value is +-- Left a, apply the first function to a; if it +-- is Right b, apply the second function to b. +-- +--

    Examples

    +-- +-- We create two values of type Either String +-- Int, one using the Left constructor and another +-- using the Right constructor. Then we apply "either" the +-- length function (if we have a String) or the +-- "times-two" function (if we have an Int): +-- +--
    +--   >>> let s = Left "foo" :: Either String Int
    +--   
    +--   >>> let n = Right 3 :: Either String Int
    +--   
    +--   >>> either length (*2) s
    +--   3
    +--   
    +--   >>> either length (*2) n
    +--   6
    +--   
    +either :: (a -> c) -> (b -> c) -> Either a b -> c + +-- | flip f takes its (first) two arguments in the reverse +-- order of f. +flip :: (a -> b -> c) -> b -> a -> c + +-- | const x is a unary function which evaluates to x for +-- all inputs. +-- +-- For instance, +-- +--
    +--   >>> map (const 42) [0..3]
    +--   [42,42,42,42]
    +--   
    +const :: a -> b -> a +odd :: Integral a => a -> Bool +even :: Integral a => a -> Bool + +-- | uncurry converts a curried function to a function on pairs. +uncurry :: (a -> b -> c) -> (a, b) -> c + +-- | curry converts an uncurried function to a curried function. +curry :: ((a, b) -> c) -> a -> b -> c + +-- | asTypeOf is a type-restricted version of const. It is +-- usually used as an infix operator, and its typing forces its first +-- argument (which is usually overloaded) to have the same type as the +-- second. +asTypeOf :: a -> a -> a + +-- | The value of seq a b is bottom if a is bottom, and +-- otherwise equal to b. seq is usually introduced to +-- improve performance by avoiding unneeded laziness. +-- +-- A note on evaluation order: the expression seq a b does +-- not guarantee that a will be evaluated before +-- b. The only guarantee given by seq is that the both +-- a and b will be evaluated before seq +-- returns a value. In particular, this means that b may be +-- evaluated before a. If you need to guarantee a specific order +-- of evaluation, you must use the function pseq from the +-- "parallel" package. +seq :: a -> b -> b + +-- | fix f is the least fixed point of the function +-- f, i.e. the least defined x such that f x = +-- x. +fix :: (a -> a) -> a + +-- | raise a number to a non-negative integral power +(^) :: (Num a, Integral b) => a -> b -> a +infixr 8 ^ + +-- | raise a number to an integral power +(^^) :: (Fractional a, Integral b) => a -> b -> a +infixr 8 ^^ + +-- | the same as flip (-). +-- +-- Because - is treated specially in the Haskell grammar, +-- (- e) is not a section, but an application of +-- prefix negation. However, (subtract +-- exp) is equivalent to the disallowed section. +subtract :: Num a => a -> a -> a + +-- | general coercion from integral types +fromIntegral :: (Integral a, Num b) => a -> b + +-- | general coercion to fractional types +realToFrac :: (Real a, Fractional b) => a -> b + +-- | Get the sum of the elements in a Foldable. +-- +-- This is not the same as the function from Foldable; instead, +-- this function uses a strict left fold. +sum :: (Foldable f, Num a) => f a -> a + +-- | Get the product of the elements in a Foldable. +-- +-- This is not the same as the function from Foldable; instead, +-- this function uses a strict left fold. +product :: (Foldable f, Num a) => f a -> a + +-- | Monadic fold over the elements of a structure, associating to the +-- right, i.e. from right to left. +foldrM :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m b + +-- | Monadic fold over the elements of a structure, associating to the +-- left, i.e. from left to right. +foldlM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b + +-- | Map each element of a structure to an action, evaluate these actions +-- from left to right, and ignore the results. For a version that doesn't +-- ignore the results see traverse. +traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f () + +-- | for_ is traverse_ with its arguments flipped. For a +-- version that doesn't ignore the results see for. +-- +--
    +--   >>> for_ [1..4] print
    +--   1
    +--   2
    +--   3
    +--   4
    +--   
    +for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f () + +-- | Evaluate each action in the structure from left to right, and ignore +-- the results. For a version that doesn't ignore the results see +-- sequenceA. +sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f () + +-- | The sum of a collection of actions, generalizing concat. +asum :: (Foldable t, Alternative f) => t (f a) -> f a + +-- | Synonym for traverse_; different from base to generalize to +-- Applicative. +mapM_ :: (Applicative m, Foldable f) => (a -> m b) -> f a -> m () + +-- | Flipped version of mapM_. +forM_ :: (Applicative m, Foldable f) => f a -> (a -> m b) -> m () + +-- | Synonym for sequence_; different from base to generalize to +-- Applicative. +sequence_ :: (Applicative m, Foldable f) => f (m a) -> m () + +-- | The sum of a collection of actions, generalizing concat. As of +-- base 4.8.0.0, msum is just asum, specialized to +-- MonadPlus. +msum :: (Foldable t, MonadPlus m) => t (m a) -> m a + +-- | The concatenation of all the elements of a container of lists. +concat :: Foldable t => t [a] -> [a] + +-- | Map a function over all the elements of a container and concatenate +-- the resulting lists. +concatMap :: Foldable t => (a -> [b]) -> t a -> [b] + +-- | and returns the conjunction of a container of Bools. For the +-- result to be True, the container must be finite; False, +-- however, results from a False value finitely far from the left +-- end. +and :: Foldable t => t Bool -> Bool + +-- | or returns the disjunction of a container of Bools. For the +-- result to be False, the container must be finite; True, +-- however, results from a True value finitely far from the left +-- end. +or :: Foldable t => t Bool -> Bool + +-- | Determines whether any element of the structure satisfies the +-- predicate. +any :: Foldable t => (a -> Bool) -> t a -> Bool + +-- | Determines whether all elements of the structure satisfy the +-- predicate. +all :: Foldable t => (a -> Bool) -> t a -> Bool + +-- | notElem is the negation of elem. +notElem :: (Foldable t, Eq a) => a -> t a -> Bool +infix 4 `notElem` + +-- | The find function takes a predicate and a structure and returns +-- the leftmost element of the structure matching the predicate, or +-- Nothing if there is no such element. +find :: Foldable t => (a -> Bool) -> t a -> Maybe a + +-- | Synonym for traverse; different from base to generalize to +-- Applicative. +mapM :: (Applicative m, Traversable t) => (a -> m b) -> t a -> m (t b) + +-- | Synonym for sequenceA; different from base to generalize to +-- Applicative. +sequence :: (Applicative m, Traversable t) => t (m a) -> m (t a) + +-- | for is traverse with its arguments flipped. For a +-- version that ignores the results see for_. +for :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b) + +-- | Flipped version of mapM. +forM :: (Applicative m, Traversable t) => t a -> (a -> m b) -> m (t b) + +-- | The mapAccumL function behaves like a combination of +-- fmap and foldl; it applies a function to each element +-- of a structure, passing an accumulating parameter from left to right, +-- and returning a final value of this accumulator together with the new +-- structure. +mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) + +-- | The mapAccumR function behaves like a combination of +-- fmap and foldr; it applies a function to each element +-- of a structure, passing an accumulating parameter from right to left, +-- and returning a final value of this accumulator together with the new +-- structure. +mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) + +-- | Flipped version of <$. +-- +--

    Examples

    +-- +-- Replace the contents of a Maybe Int with a +-- constant String: +-- +--
    +--   >>> Nothing $> "foo"
    +--   Nothing
    +--   
    +--   >>> Just 90210 $> "foo"
    +--   Just "foo"
    +--   
    +-- +-- Replace the contents of an Either Int +-- Int with a constant String, resulting in an +-- Either Int String: +-- +--
    +--   >>> Left 8675309 $> "foo"
    +--   Left 8675309
    +--   
    +--   >>> Right 8675309 $> "foo"
    +--   Right "foo"
    +--   
    +-- +-- Replace each element of a list with a constant String: +-- +--
    +--   >>> [1,2,3] $> "foo"
    +--   ["foo","foo","foo"]
    +--   
    +-- +-- Replace the second element of a pair with a constant String: +-- +--
    +--   >>> (1,2) $> "foo"
    +--   (1,"foo")
    +--   
    +($>) :: Functor f => f a -> b -> f b +infixl 4 $> + +-- | An infix synonym for fmap. +-- +-- The name of this operator is an allusion to $. Note the +-- similarities between their types: +-- +--
    +--    ($)  ::              (a -> b) ->   a ->   b
    +--   (<$>) :: Functor f => (a -> b) -> f a -> f b
    +--   
    +-- +-- Whereas $ is function application, <$> is +-- function application lifted over a Functor. +-- +--

    Examples

    +-- +-- Convert from a Maybe Int to a +-- Maybe String using show: +-- +--
    +--   >>> show <$> Nothing
    +--   Nothing
    +--   
    +--   >>> show <$> Just 3
    +--   Just "3"
    +--   
    +-- +-- Convert from an Either Int Int to +-- an Either Int String using +-- show: +-- +--
    +--   >>> show <$> Left 17
    +--   Left 17
    +--   
    +--   >>> show <$> Right 17
    +--   Right "17"
    +--   
    +-- +-- Double each element of a list: +-- +--
    +--   >>> (*2) <$> [1,2,3]
    +--   [2,4,6]
    +--   
    +-- +-- Apply even to the second element of a pair: +-- +--
    +--   >>> even <$> (2,2)
    +--   (2,True)
    +--   
    +(<$>) :: Functor f => (a -> b) -> f a -> f b +infixl 4 <$> + +-- | void value discards or ignores the result of +-- evaluation, such as the return value of an IO action. +-- +--

    Examples

    +-- +-- Replace the contents of a Maybe Int with +-- unit: +-- +--
    +--   >>> void Nothing
    +--   Nothing
    +--   
    +--   >>> void (Just 3)
    +--   Just ()
    +--   
    +-- +-- Replace the contents of an Either Int +-- Int with unit, resulting in an Either +-- Int '()': +-- +--
    +--   >>> void (Left 8675309)
    +--   Left 8675309
    +--   
    +--   >>> void (Right 8675309)
    +--   Right ()
    +--   
    +-- +-- Replace every element of a list with unit: +-- +--
    +--   >>> void [1,2,3]
    +--   [(),(),()]
    +--   
    +-- +-- Replace the second element of a pair with unit: +-- +--
    +--   >>> void (1,2)
    +--   (1,())
    +--   
    +-- +-- Discard the result of an IO action: +-- +--
    +--   >>> mapM print [1,2]
    +--   1
    +--   2
    +--   [(),()]
    +--   
    +--   >>> void $ mapM print [1,2]
    +--   1
    +--   2
    +--   
    +void :: Functor f => f a -> f () + +-- | Lift a function to actions. This function may be used as a value for +-- fmap in a Functor instance. +liftA :: Applicative f => (a -> b) -> f a -> f b + +-- | Lift a binary function to actions. +liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c + +-- | Lift a ternary function to actions. +liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d + +-- | One or none. +optional :: Alternative f => f a -> f (Maybe a) + +-- | Same as >>=, but with the arguments interchanged. +(=<<) :: Monad m => (a -> m b) -> m a -> m b +infixr 1 =<< + +-- | Left-to-right Kleisli composition of monads. +(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c +infixr 1 >=> + +-- | Right-to-left Kleisli composition of monads. +-- (>=>), with the arguments flipped. +-- +-- Note how this operator resembles function composition +-- (.): +-- +--
    +--   (.)   ::            (b ->   c) -> (a ->   b) -> a ->   c
    +--   (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c
    +--   
    +(<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c +infixr 1 <=< + +-- | forever act repeats the action infinitely. +forever :: Applicative f => f a -> f b + +-- | The join function is the conventional monad join operator. It +-- is used to remove one level of monadic structure, projecting its bound +-- argument into the outer level. +join :: Monad m => m (m a) -> m a + +-- | The foldM function is analogous to foldl, except that +-- its result is encapsulated in a monad. Note that foldM works +-- from left-to-right over the list arguments. This could be an issue +-- where (>>) and the `folded function' are not +-- commutative. +-- +--
    +--   foldM f a1 [x1, x2, ..., xm]
    +--   
    +-- +-- == +-- +--
    +--   do
    +--     a2 <- f a1 x1
    +--     a3 <- f a2 x2
    +--     ...
    +--     f am xm
    +--   
    +-- +-- If right-to-left evaluation is required, the input list should be +-- reversed. +-- +-- Note: foldM is the same as foldlM +foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b + +-- | Like foldM, but discards the result. +foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m () + +-- | Like replicateM, but discards the result. +replicateM_ :: Applicative m => Int -> m a -> m () + +-- | guard b is pure () if b is +-- True, and empty if b is False. +guard :: Alternative f => Bool -> f () + +-- | Conditional execution of Applicative expressions. For example, +-- +--
    +--   when debug (putStrLn "Debugging")
    +--   
    +-- +-- will output the string Debugging if the Boolean value +-- debug is True, and otherwise do nothing. +when :: Applicative f => Bool -> f () -> f () + +-- | The reverse of when. +unless :: Applicative f => Bool -> f () -> f () + +-- | Promote a function to a monad. +liftM :: Monad m => (a1 -> r) -> m a1 -> m r + +-- | In many situations, the liftM operations can be replaced by +-- uses of ap, which promotes function application. +-- +--
    +--   return f `ap` x1 `ap` ... `ap` xn
    +--   
    +-- +-- is equivalent to +-- +--
    +--   liftMn f x1 x2 ... xn
    +--   
    +ap :: Monad m => m (a -> b) -> m a -> m b + +-- | Strict version of <$>. +(<$!>) :: Monad m => (a -> b) -> m a -> m b +infixl 4 <$!> + +-- | Suspends the current thread for a given number of microseconds (GHC +-- only). +-- +-- There is no guarantee that the thread will be rescheduled promptly +-- when the delay has expired, but the thread will never continue to run +-- earlier than specified. +threadDelay :: Int -> IO () + +-- | An MVar (pronounced "em-var") is a synchronising variable, used +-- for communication between concurrent threads. It can be thought of as +-- a a box, which may be empty or full. +data MVar a :: * -> * + +-- | Create an MVar which is initially empty. +newEmptyMVar :: IO (MVar a) + +-- | Create an MVar which contains the supplied value. +newMVar :: a -> IO (MVar a) + +-- | Return the contents of the MVar. If the MVar is +-- currently empty, takeMVar will wait until it is full. After a +-- takeMVar, the MVar is left empty. +-- +-- There are two further important properties of takeMVar: +-- +-- +takeMVar :: MVar a -> IO a + +-- | Put a value into an MVar. If the MVar is currently full, +-- putMVar will wait until it becomes empty. +-- +-- There are two further important properties of putMVar: +-- +-- +putMVar :: MVar a -> a -> IO () + +-- | Atomically read the contents of an MVar. If the MVar is +-- currently empty, readMVar will wait until its full. +-- readMVar is guaranteed to receive the next putMVar. +-- +-- readMVar is multiple-wakeup, so when multiple readers are +-- blocked on an MVar, all of them are woken up at the same time. +-- +-- Compatibility note: Prior to base 4.7, readMVar was a +-- combination of takeMVar and putMVar. This mean that in +-- the presence of other threads attempting to putMVar, +-- readMVar could block. Furthermore, readMVar would not +-- receive the next putMVar if there was already a pending thread +-- blocked on takeMVar. The old behavior can be recovered by +-- implementing 'readMVar as follows: +-- +--
    +--   readMVar :: MVar a -> IO a
    +--   readMVar m =
    +--     mask_ $ do
    +--       a <- takeMVar m
    +--       putMVar m a
    +--       return a
    +--   
    +readMVar :: MVar a -> IO a + +-- | Take a value from an MVar, put a new value into the MVar +-- and return the value taken. This function is atomic only if there are +-- no other producers for this MVar. +swapMVar :: MVar a -> a -> IO a + +-- | A non-blocking version of takeMVar. The tryTakeMVar +-- function returns immediately, with Nothing if the MVar +-- was empty, or Just a if the MVar was full with +-- contents a. After tryTakeMVar, the MVar is left +-- empty. +tryTakeMVar :: MVar a -> IO (Maybe a) + +-- | A non-blocking version of putMVar. The tryPutMVar +-- function attempts to put the value a into the MVar, +-- returning True if it was successful, or False otherwise. +tryPutMVar :: MVar a -> a -> IO Bool + +-- | Check whether a given MVar is empty. +-- +-- Notice that the boolean value returned is just a snapshot of the state +-- of the MVar. By the time you get to react on its result, the MVar may +-- have been filled (or emptied) - so be extremely careful when using +-- this operation. Use tryTakeMVar instead if possible. +isEmptyMVar :: MVar a -> IO Bool + +-- | withMVar is an exception-safe wrapper for operating on the +-- contents of an MVar. This operation is exception-safe: it will +-- replace the original contents of the MVar if an exception is +-- raised (see Control.Exception). However, it is only atomic if +-- there are no other producers for this MVar. +withMVar :: MVar a -> (a -> IO b) -> IO b + +-- | Like withMVar, but the IO action in the second +-- argument is executed with asynchronous exceptions masked. +withMVarMasked :: MVar a -> (a -> IO b) -> IO b + +-- | An exception-safe wrapper for modifying the contents of an +-- MVar. Like withMVar, modifyMVar will replace the +-- original contents of the MVar if an exception is raised during +-- the operation. This function is only atomic if there are no other +-- producers for this MVar. +modifyMVar_ :: MVar a -> (a -> IO a) -> IO () + +-- | A slight variation on modifyMVar_ that allows a value to be +-- returned (b) in addition to the modified value of the +-- MVar. +modifyMVar :: MVar a -> (a -> IO (a, b)) -> IO b + +-- | Like modifyMVar_, but the IO action in the second +-- argument is executed with asynchronous exceptions masked. +modifyMVarMasked_ :: MVar a -> (a -> IO a) -> IO () + +-- | Like modifyMVar, but the IO action in the second +-- argument is executed with asynchronous exceptions masked. +modifyMVarMasked :: MVar a -> (a -> IO (a, b)) -> IO b + +-- | A non-blocking version of readMVar. The tryReadMVar +-- function returns immediately, with Nothing if the MVar +-- was empty, or Just a if the MVar was full with +-- contents a. +tryReadMVar :: MVar a -> IO (Maybe a) + +-- | Make a Weak pointer to an MVar, using the second +-- argument as a finalizer to run when MVar is garbage-collected +mkWeakMVar :: MVar a -> IO () -> IO (Weak (MVar a)) + +-- | Chan is an abstract type representing an unbounded FIFO +-- channel. +data Chan a :: * -> * + +-- | Build and returns a new instance of Chan. +newChan :: IO (Chan a) + +-- | Write a value to a Chan. +writeChan :: Chan a -> a -> IO () + +-- | Read the next value from the Chan. +readChan :: Chan a -> IO a + +-- | Duplicate a Chan: the duplicate channel begins empty, but data +-- written to either channel from then on will be available from both. +-- Hence this creates a kind of broadcast channel, where data written by +-- anyone is seen by everyone else. +-- +-- (Note that a duplicated channel is not equal to its original. So: +-- fmap (c /=) $ dupChan c returns True for all +-- c.) +dupChan :: Chan a -> IO (Chan a) + +-- | Retrieves a function of the current environment. +asks :: MonadReader r m => (r -> a) -> m a + +-- | Synonym for throw +throwIO :: (MonadThrow m, Exception e) => e -> m a + +-- | Synonym for throw +throwM :: (MonadThrow m, Exception e) => e -> m a + +-- | Throw an asynchronous exception to another thread +-- +-- It's usually a better idea to use the async package, see +-- https://github.com/fpco/safe-exceptions#quickstart +throwTo :: (Exception e, MonadIO m) => ThreadId -> e -> m () + +-- | Same as upstream catch, but will not catch asynchronous +-- exceptions +catch :: (MonadCatch m, Exception e) => m a -> (e -> m a) -> m a + +-- | catch specialized to only catching IOExceptions +catchIO :: MonadCatch m => m a -> (IOException -> m a) -> m a + +-- | catch specialized to catch all synchronous exception +catchAny :: MonadCatch m => m a -> (SomeException -> m a) -> m a + +-- | Same as catch, but fully force evaluation of the result value +-- to find all impure exceptions. +catchDeep :: (MonadCatch m, MonadIO m, Exception e, NFData a) => m a -> (e -> m a) -> m a + +-- | catchDeep specialized to catch all synchronous exception +catchAnyDeep :: (MonadCatch m, MonadIO m, NFData a) => m a -> (SomeException -> m a) -> m a + +-- | Flipped version of catch +handle :: (MonadCatch m, Exception e) => (e -> m a) -> m a -> m a + +-- | handle specialized to only catching IOExceptions +handleIO :: MonadCatch m => (IOException -> m a) -> m a -> m a + +-- | Flipped version of catchAny +handleAny :: MonadCatch m => (SomeException -> m a) -> m a -> m a + +-- | Flipped version of catchDeep +handleDeep :: (MonadCatch m, Exception e, MonadIO m, NFData a) => (e -> m a) -> m a -> m a + +-- | Flipped version of catchAnyDeep +handleAnyDeep :: (MonadCatch m, MonadIO m, NFData a) => (SomeException -> m a) -> m a -> m a + +-- | Same as upstream try, but will not catch asynchronous +-- exceptions +try :: (MonadCatch m, Exception e) => m a -> m (Either e a) + +-- | try specialized to only catching IOExceptions +tryIO :: MonadCatch m => m a -> m (Either IOException a) + +-- | try specialized to catch all synchronous exceptions +tryAny :: MonadCatch m => m a -> m (Either SomeException a) + +-- | Same as try, but fully force evaluation of the result value to +-- find all impure exceptions. +tryDeep :: (MonadCatch m, MonadIO m, Exception e, NFData a) => m a -> m (Either e a) + +-- | tryDeep specialized to catch all synchronous exceptions +tryAnyDeep :: (MonadCatch m, MonadIO m, NFData a) => m a -> m (Either SomeException a) + +-- | Async safe version of onException +onException :: MonadMask m => m a -> m b -> m a + +-- | Async safe version of bracket +bracket :: MonadMask m => m a -> (a -> m b) -> (a -> m c) -> m c + +-- | Async safe version of bracket_ +bracket_ :: MonadMask m => m a -> m b -> m c -> m c + +-- | Async safe version of finally +finally :: MonadMask m => m a -> m b -> m a + +-- | Like onException, but provides the handler the thrown +-- exception. +withException :: (MonadMask m, Exception e) => m a -> (e -> m b) -> m a + +-- | Async safe version of bracketOnError +bracketOnError :: MonadMask m => m a -> (a -> m b) -> (a -> m c) -> m c + +-- | Async safe version of bracketOnError_ +bracketOnError_ :: MonadMask m => m a -> m b -> m c -> m c + +-- | Render this exception value in a human-friendly manner. +-- +-- Default implementation: show. +displayException :: Exception e => e -> String + +-- | Fanout: send the input to both argument arrows and combine their +-- output. +-- +-- The default definition may be overridden with a more efficient version +-- if desired. +(&&&) :: Arrow a => forall b c c'. a b c -> a b c' -> a b (c, c') + +-- | Split the input between the two argument arrows and combine their +-- output. Note that this is in general not a functor. +-- +-- The default definition may be overridden with a more efficient version +-- if desired. +(***) :: Arrow a => forall b c b' c'. a b c -> a b' c' -> a (b, b') (c, c') + +-- | The mapMaybe function is a version of map which can +-- throw out elements. In particular, the functional argument returns +-- something of type Maybe b. If this is Nothing, +-- no element is added on to the result list. If it is Just +-- b, then b is included in the result list. +-- +--

    Examples

    +-- +-- Using mapMaybe f x is a shortcut for +-- catMaybes $ map f x in most cases: +-- +--
    +--   >>> import Text.Read ( readMaybe )
    +--   
    +--   >>> let readMaybeInt = readMaybe :: String -> Maybe Int
    +--   
    +--   >>> mapMaybe readMaybeInt ["1", "Foo", "3"]
    +--   [1,3]
    +--   
    +--   >>> catMaybes $ map readMaybeInt ["1", "Foo", "3"]
    +--   [1,3]
    +--   
    +-- +-- If we map the Just constructor, the entire list should be +-- returned: +-- +--
    +--   >>> mapMaybe Just [1,2,3]
    +--   [1,2,3]
    +--   
    +mapMaybe :: (a -> Maybe b) -> [a] -> [b] + +-- | The catMaybes function takes a list of Maybes and +-- returns a list of all the Just values. +-- +--

    Examples

    +-- +-- Basic usage: +-- +--
    +--   >>> catMaybes [Just 1, Nothing, Just 3]
    +--   [1,3]
    +--   
    +-- +-- When constructing a list of Maybe values, catMaybes can +-- be used to return all of the "success" results (if the list is the +-- result of a map, then mapMaybe would be more +-- appropriate): +-- +--
    +--   >>> import Text.Read ( readMaybe )
    +--   
    +--   >>> [readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ]
    +--   [Just 1,Nothing,Just 3]
    +--   
    +--   >>> catMaybes $ [readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ]
    +--   [1,3]
    +--   
    +catMaybes :: [Maybe a] -> [a] + +-- | The fromMaybe function takes a default value and and +-- Maybe value. If the Maybe is Nothing, it returns +-- the default values; otherwise, it returns the value contained in the +-- Maybe. +-- +--

    Examples

    +-- +-- Basic usage: +-- +--
    +--   >>> fromMaybe "" (Just "Hello, World!")
    +--   "Hello, World!"
    +--   
    +-- +--
    +--   >>> fromMaybe "" Nothing
    +--   ""
    +--   
    +-- +-- Read an integer from a string using readMaybe. If we fail to +-- parse an integer, we want to return 0 by default: +-- +--
    +--   >>> import Text.Read ( readMaybe )
    +--   
    +--   >>> fromMaybe 0 (readMaybe "5")
    +--   5
    +--   
    +--   >>> fromMaybe 0 (readMaybe "")
    +--   0
    +--   
    +fromMaybe :: a -> Maybe a -> a + +-- | The isJust function returns True iff its argument is of +-- the form Just _. +-- +--

    Examples

    +-- +-- Basic usage: +-- +--
    +--   >>> isJust (Just 3)
    +--   True
    +--   
    +-- +--
    +--   >>> isJust (Just ())
    +--   True
    +--   
    +-- +--
    +--   >>> isJust Nothing
    +--   False
    +--   
    +-- +-- Only the outer constructor is taken into consideration: +-- +--
    +--   >>> isJust (Just Nothing)
    +--   True
    +--   
    +isJust :: Maybe a -> Bool + +-- | The isNothing function returns True iff its argument is +-- Nothing. +-- +--

    Examples

    +-- +-- Basic usage: +-- +--
    +--   >>> isNothing (Just 3)
    +--   False
    +--   
    +-- +--
    +--   >>> isNothing (Just ())
    +--   False
    +--   
    +-- +--
    +--   >>> isNothing Nothing
    +--   True
    +--   
    +-- +-- Only the outer constructor is taken into consideration: +-- +--
    +--   >>> isNothing (Just Nothing)
    +--   False
    +--   
    +isNothing :: Maybe a -> Bool + +-- | The listToMaybe function returns Nothing on an empty +-- list or Just a where a is the first element +-- of the list. +-- +--

    Examples

    +-- +-- Basic usage: +-- +--
    +--   >>> listToMaybe []
    +--   Nothing
    +--   
    +-- +--
    +--   >>> listToMaybe [9]
    +--   Just 9
    +--   
    +-- +--
    +--   >>> listToMaybe [1,2,3]
    +--   Just 1
    +--   
    +-- +-- Composing maybeToList with listToMaybe should be the +-- identity on singleton/empty lists: +-- +--
    +--   >>> maybeToList $ listToMaybe [5]
    +--   [5]
    +--   
    +--   >>> maybeToList $ listToMaybe []
    +--   []
    +--   
    +-- +-- But not on lists with more than one element: +-- +--
    +--   >>> maybeToList $ listToMaybe [1,2,3]
    +--   [1]
    +--   
    +listToMaybe :: [a] -> Maybe a + +-- | 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. +-- +--

    Examples

    +-- +-- Basic usage: +-- +--
    +--   >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
    +--   
    +--   >>> partitionEithers list
    +--   (["foo","bar","baz"],[3,7])
    +--   
    +-- +-- The pair returned by partitionEithers x should be the +-- same pair as (lefts x, rights x): +-- +--
    +--   >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
    +--   
    +--   >>> partitionEithers list == (lefts list, rights list)
    +--   True
    +--   
    +partitionEithers :: [Either a b] -> ([a], [b]) + +-- | Extracts from a list of Either all the Left elements. +-- All the Left elements are extracted in order. +-- +--

    Examples

    +-- +-- Basic usage: +-- +--
    +--   >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
    +--   
    +--   >>> lefts list
    +--   ["foo","bar","baz"]
    +--   
    +lefts :: [Either a b] -> [a] + +-- | Extracts from a list of Either all the Right elements. +-- All the Right elements are extracted in order. +-- +--

    Examples

    +-- +-- Basic usage: +-- +--
    +--   >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
    +--   
    +--   >>> rights list
    +--   [3,7]
    +--   
    +rights :: [Either a b] -> [b] + +-- | (*) `on` f = \x y -> f x * f y. +-- +-- Typical usage: sortBy (compare `on` +-- fst). +-- +-- Algebraic properties: +-- +-- +on :: (b -> b -> c) -> (a -> b) -> a -> a -> c +infixl 0 `on` + +-- |
    +--   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) ...
    +--   
    +comparing :: Ord a => (b -> a) -> b -> b -> Ordering + +-- | Send a Text to standard output, appending a newline, and +-- chunking the data. By default, the chunk size is 2048 characters, so +-- any messages below that size will be sent as one contiguous unit. If +-- larger messages are used, it is possible for interleaving with other +-- threads to occur. +say :: MonadIO m => Text -> m () + +-- | Same as say, but operates on a String. Note that this +-- will force the entire String into memory at once, and will +-- fail for infinite Strings. +sayString :: MonadIO m => String -> m () + +-- | Same as say, but for instances of Show. +-- +-- If your Show instance generates infinite output, this will +-- fail. However, an infinite result for show would generally be +-- considered an invalid instance anyway. +sayShow :: (MonadIO m, Show a) => a -> m () + +-- | Same as say, but data is sent to standard error. +sayErr :: MonadIO m => Text -> m () + +-- | Same as sayString, but data is sent to standard error. +sayErrString :: MonadIO m => String -> m () + +-- | Same as sayShow, but data is sent to standard error. +sayErrShow :: (MonadIO m, Show a) => a -> m () + +-- | Same as say, but data is sent to the provided Handle. +hSay :: MonadIO m => Handle -> Text -> m () + +-- | Same as sayString, but data is sent to the provided +-- Handle. +hSayString :: MonadIO m => Handle -> String -> m () + +-- | Same as sayShow, but data is sent to the provided +-- Handle. +hSayShow :: (MonadIO m, Show a) => Handle -> a -> m () + +-- | A mutable variable in the IO monad +data IORef a :: * -> * + +-- | Build a new IORef +newIORef :: a -> IO (IORef a) + +-- | Read the value of an IORef +readIORef :: IORef a -> IO a + +-- | Write a new value into an IORef +writeIORef :: IORef a -> a -> IO () + +-- | Mutate the contents of an IORef. +-- +-- Be warned that modifyIORef does not apply the function +-- strictly. This means if the program calls modifyIORef many +-- times, but seldomly uses the value, thunks will pile up in memory +-- resulting in a space leak. This is a common mistake made when using an +-- IORef as a counter. For example, the following will likely produce a +-- stack overflow: +-- +--
    +--   ref <- newIORef 0
    +--   replicateM_ 1000000 $ modifyIORef ref (+1)
    +--   readIORef ref >>= print
    +--   
    +-- +-- To avoid this problem, use modifyIORef' instead. +modifyIORef :: IORef a -> (a -> a) -> IO () + +-- | Strict version of modifyIORef +modifyIORef' :: IORef a -> (a -> a) -> IO () + +-- | Atomically modifies the contents of an IORef. +-- +-- This function is useful for using IORef in a safe way in a +-- multithreaded program. If you only have one IORef, then using +-- atomicModifyIORef to access and modify it will prevent race +-- conditions. +-- +-- Extending the atomicity to multiple IORefs is problematic, so +-- it is recommended that if you need to do anything more complicated +-- then using MVar instead is a good idea. +-- +-- atomicModifyIORef does not apply the function strictly. This is +-- important to know even if all you are doing is replacing the value. +-- For example, this will leak memory: +-- +--
    +--   ref <- newIORef '1'
    +--   forever $ atomicModifyIORef ref (\_ -> ('2', ()))
    +--   
    +-- +-- Use atomicModifyIORef' or atomicWriteIORef to avoid this +-- problem. +atomicModifyIORef :: IORef a -> (a -> (a, b)) -> IO b + +-- | Strict version of atomicModifyIORef. This forces both the value +-- stored in the IORef as well as the value returned. +atomicModifyIORef' :: IORef a -> (a -> (a, b)) -> IO b + +-- | Variant of writeIORef with the "barrier to reordering" property +-- that atomicModifyIORef has. +atomicWriteIORef :: IORef a -> a -> IO () + +-- | Make a Weak pointer to an IORef, using the second +-- argument as a finalizer to run when IORef is garbage-collected +mkWeakIORef :: IORef a -> IO () -> IO (Weak (IORef a)) + +-- | 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: +-- +-- +-- +-- 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. +data Handle :: * + +-- | See openFile +data IOMode :: * +ReadMode :: IOMode +WriteMode :: IOMode +AppendMode :: IOMode +ReadWriteMode :: IOMode + +-- | A handle managing input from the Haskell program's standard input +-- channel. +stdin :: Handle + +-- | A handle managing output to the Haskell program's standard output +-- channel. +stdout :: Handle + +-- | A handle managing output to the Haskell program's standard error +-- channel. +stderr :: Handle + +-- | Computation hClose hdl makes handle hdl +-- closed. Before the computation finishes, if hdl is writable +-- its buffer is flushed as for hFlush. Performing hClose +-- on a handle that has already been closed has no effect; doing so is +-- not an error. All other operations on a closed handle will fail. If +-- hClose fails for any reason, any further operations (apart from +-- hClose) on the handle will still fail as if hdl had +-- been successfully closed. +hClose :: Handle -> IO () + +-- | withBinaryFile name mode act opens a file using +-- openBinaryFile and passes the resulting handle to the +-- computation act. The handle will be closed on exit from +-- withBinaryFile, whether by normal termination or by raising an +-- exception. +withBinaryFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r + +-- | Read an entire file strictly into a ByteString. +readFile :: FilePath -> IO ByteString + +-- | Write a ByteString to a file. +writeFile :: FilePath -> ByteString -> IO () + +-- | Read a file assuming a UTF-8 character encoding. +-- +-- This leverages decodeUtf8, so in the event of a character +-- encoding issue, replacement characters will be used. +readFileUtf8 :: MonadIO m => FilePath -> m Text + +-- | Write a file using a UTF-8 character encoding. +writeFileUtf8 :: MonadIO m => FilePath -> Text -> m () + +-- | Encode text using UTF-8 encoding. +encodeUtf8 :: Text -> ByteString + +-- | A total function for decoding a ByteString into Text +-- using a UTF-8 character encoding. This uses lenientDecode in +-- the case of any encoding errors. +decodeUtf8 :: ByteString -> Text + +-- | A class of types that can be fully evaluated. +class NFData a + +-- | rnf should reduce its argument to normal form (that is, fully +-- evaluate all sub-components), and then return '()'. +-- +--

    Generic NFData deriving

    +-- +-- Starting with GHC 7.2, you can automatically derive instances for +-- types possessing a Generic instance. +-- +--
    +--   {-# LANGUAGE DeriveGeneric #-}
    +--   
    +--   import GHC.Generics (Generic)
    +--   import Control.DeepSeq
    +--   
    +--   data Foo a = Foo a String
    +--                deriving (Eq, Generic)
    +--   
    +--   instance NFData a => NFData (Foo a)
    +--   
    +--   data Colour = Red | Green | Blue
    +--                 deriving Generic
    +--   
    +--   instance NFData Colour
    +--   
    +-- +-- Starting with GHC 7.10, the example above can be written more +-- concisely by enabling the new DeriveAnyClass extension: +-- +--
    +--   {-# LANGUAGE DeriveGeneric, DeriveAnyClass #-}
    +--   
    +--   import GHC.Generics (Generic)
    +--   import Control.DeepSeq
    +--   
    +--   data Foo a = Foo a String
    +--                deriving (Eq, Generic, NFData)
    +--   
    +--   data Colour = Red | Green | Blue
    +--                 deriving (Generic, NFData)
    +--   
    +-- +--

    Compatibility with previous deepseq versions

    +-- +-- Prior to version 1.4.0.0, the default implementation of the rnf +-- method was defined as +-- +--
    +--   rnf a = seq a ()
    +--   
    +-- +-- However, starting with deepseq-1.4.0.0, the default +-- implementation is based on DefaultSignatures allowing for +-- more accurate auto-derived NFData instances. If you need the +-- previously used exact default rnf method implementation +-- semantics, use +-- +--
    +--   instance NFData Colour where rnf x = seq x ()
    +--   
    +-- +-- or alternatively +-- +--
    +--   {-# LANGUAGE BangPatterns #-}
    +--   instance NFData Colour where rnf !_ = ()
    +--   
    +rnf :: a -> () + +-- | deepseq: fully evaluates the first argument, before returning +-- the second. +-- +-- The name deepseq is used to illustrate the relationship to +-- seq: where seq is shallow in the sense that it only +-- evaluates the top level of its argument, deepseq traverses the +-- entire data structure evaluating it completely. +-- +-- deepseq can be useful for forcing pending exceptions, +-- eradicating space leaks, or forcing lazy I/O to happen. It is also +-- useful in conjunction with parallel Strategies (see the +-- parallel package). +-- +-- There is no guarantee about the ordering of evaluation. The +-- implementation may evaluate the components of the structure in any +-- order or in parallel. To impose an actual order on evaluation, use +-- pseq from Control.Parallel in the parallel +-- package. +deepseq :: NFData a => a -> b -> b + +-- | the deep analogue of $!. In the expression f $!! x, +-- x is fully evaluated before the function f is +-- applied to it. +($!!) :: NFData a => (a -> b) -> a -> b +infixr 0 $!! + +-- | a variant of deepseq that is useful in some circumstances: +-- +--
    +--   force x = x `deepseq` x
    +--   
    +-- +-- force x fully evaluates x, and then returns it. Note +-- that force x only performs evaluation when the value of +-- force x itself is demanded, so essentially it turns shallow +-- evaluation into deep evaluation. +-- +-- force can be conveniently used in combination with +-- ViewPatterns: +-- +--
    +--   {-# LANGUAGE BangPatterns, ViewPatterns #-}
    +--   import Control.DeepSeq
    +--   
    +--   someFun :: ComplexData -> SomeResult
    +--   someFun (force -> !arg) = {- 'arg' will be fully evaluated -}
    +--   
    +-- +-- Another useful application is to combine force with +-- evaluate in order to force deep evaluation relative to other +-- IO operations: +-- +--
    +--   import Control.Exception (evaluate)
    +--   import Control.DeepSeq
    +--   
    +--   main = do
    +--     result <- evaluate $ force $ pureComputation
    +--     {- 'result' will be fully evaluated at this point -}
    +--     return ()
    +--   
    +force :: NFData a => a -> a + +-- | Operator version of mappend. +-- +-- In base, this operator is known as <>. However, this is +-- the name of the operator for Semigroup as well. Once +-- Semigroup is a superclass of Monoid, this historical +-- accident will be unimportant. In the meanwhile, SafePrelude +-- deals with this situation by making <> the +-- Semigroup operator, and ++ the Monoid operator. +(++) :: Monoid m => m -> m -> m +infixr 5 ++ + +-- | Parse a string using the Read instance. Succeeds if there is +-- exactly one valid result. +readMaybe :: Read a => String -> Maybe a + +-- | Parse a string using the Read instance. Succeeds if there is +-- exactly one valid result. A Left value indicates a parse error. +readEither :: Read a => String -> Either String a diff --git a/static/safe-prelude/src/SafePrelude.html b/static/safe-prelude/src/SafePrelude.html new file mode 100644 index 0000000..524fd48 --- /dev/null +++ b/static/safe-prelude/src/SafePrelude.html @@ -0,0 +1,451 @@ +
    {-# LANGUAGE CPP #-}
    +-- TODO Consider replacing all IO-specific functions being reexported
    +-- to MonadIO
    +module SafePrelude
    +    ( -- * Types
    +      Prelude.Maybe (..)
    +    , Prelude.Ordering (..)
    +    , Bool (..)
    +    , Char
    +    , IO
    +    , Prelude.Either (..)
    +    , ByteString
    +    , Text
    +    , Map
    +    , HashMap
    +    , IntMap
    +    , Set
    +    , HashSet
    +    , IntSet
    +    , Seq
    +    , Identity (..)
    +    , SomeException (..)
    +    , SomeAsyncException (..)
    +    -- very grudgingly
    +    , String
    +    , IO.FilePath
    +      -- ** Numbers
    +    , Word
    +    , Word8
    +    , Word16
    +    , Word32
    +    , Word64
    +    , Int
    +    , Int8
    +    , Int16
    +    , Int32
    +    , Int64
    +    , Integer
    +    , Rational
    +    , Float
    +    , Double
    +    , Proxy (..)
    +      -- * Type classes
    +    , Prelude.Ord (..)
    +    , Eq (..)
    +    , Bounded (..)
    +    , Show (..)
    +    , Prelude.Read (..)
    +    , Functor (fmap, (<$))
    +    , Applicative (pure, (<*>), (*>), (<*))
    +    , Alternative (empty, (<|>), some, many)
    +    , Monad ((>>=), (>>), return, fail)
    +    , MonadIO (liftIO)
    +    , MonadTrans (lift)
    +    , MonadReader (ask, local, reader)
    +    , MonadThrow
    +    , Exception (toException, fromException)
    +    , MonadCatch
    +    , MonadMask
    +    , Foldable (fold, foldMap, foldr, foldr', foldl, foldl')
    +    -- separate from the type class in earlier bases
    +    , toList, null, length, elem
    +    , Traversable (traverse, sequenceA)
    +    , Typeable
    +    , IsString (..)
    +    , Hashable (..)
    +    , Semigroup (..)
    +    , Monoid (..)
    +      -- ** Numeric
    +    , Num (..)
    +    , Real (..)
    +    , Integral (..)
    +    , Fractional (..)
    +    , Floating (..)
    +    , RealFrac (..)
    +    , RealFloat (..)
    +      -- * Functions
    +    , (Prelude.$)
    +    , (&)
    +    , (Prelude.$!)
    +    , (Prelude.&&)
    +    , (Prelude.||)
    +    , (Prelude..)
    +    , Prelude.not
    +    , Prelude.otherwise
    +    , Prelude.fst
    +    , Prelude.snd
    +    , Prelude.id
    +    , Prelude.maybe
    +    , Prelude.either
    +    , Prelude.flip
    +    , Prelude.const
    +    , Prelude.odd
    +    , Prelude.even
    +    , Prelude.uncurry
    +    , Prelude.curry
    +    , Prelude.asTypeOf
    +    , Prelude.seq
    +    , fix
    +      -- ** Numeric
    +    , (^)
    +    , (^^)
    +    , subtract
    +    , fromIntegral
    +    , realToFrac
    +      -- ** Foldable
    +    , sum
    +    , product
    +    , foldrM
    +    , foldlM
    +    , traverse_
    +    , for_
    +    , sequenceA_
    +    , asum
    +    , SafePrelude.mapM_
    +    , SafePrelude.forM_
    +    , SafePrelude.sequence_
    +    , msum
    +    , concat
    +    , concatMap
    +    , and
    +    , or
    +    , any
    +    , all
    +    , notElem
    +    , find
    +      -- ** Traversable
    +    , SafePrelude.mapM
    +    , SafePrelude.sequence
    +    , for
    +    , SafePrelude.forM
    +    , mapAccumL
    +    , mapAccumR
    +      -- ** Functor
    +    , ($>)
    +    , (<$>)
    +    , void
    +      -- ** Applicative
    +    , liftA
    +    , liftA2
    +    , liftA3
    +      -- ** Alternative
    +    , optional
    +      -- ** Monad
    +    , (=<<)
    +    , (>=>)
    +    , (<=<)
    +    , forever
    +    , join
    +    , foldM
    +    , foldM_
    +    , replicateM_
    +    , guard
    +    , when
    +    , unless
    +    , liftM
    +    , ap
    +    , (<$!>)
    +      -- ** Concurrent
    +    , threadDelay
    +    , MVar
    +    , newEmptyMVar
    +    , newMVar
    +    , takeMVar
    +    , putMVar
    +    , readMVar
    +    , swapMVar
    +    , tryTakeMVar
    +    , tryPutMVar
    +    , isEmptyMVar
    +    , withMVar
    +    , withMVarMasked
    +    , modifyMVar_
    +    , modifyMVar
    +    , modifyMVarMasked_
    +    , modifyMVarMasked
    +    , tryReadMVar
    +    , mkWeakMVar
    +    , Chan
    +    , newChan
    +    , writeChan
    +    , readChan
    +    , dupChan
    +      -- ** Reader
    +    , asks
    +      -- ** Exceptions
    +    , throwIO
    +    , throwM
    +    , throwTo
    +    , catch
    +    , catchIO
    +    , catchAny
    +    , catchDeep
    +    , catchAnyDeep
    +    , handle
    +    , handleIO
    +    , handleAny
    +    , handleDeep
    +    , handleAnyDeep
    +    , try
    +    , tryIO
    +    , tryAny
    +    , tryDeep
    +    , tryAnyDeep
    +    , onException
    +    , bracket
    +    , bracket_
    +    , finally
    +    , withException
    +    , bracketOnError
    +    , bracketOnError_
    +    , displayException
    +      -- ** Arrow
    +    , (&&&)
    +    , (***)
    +      -- ** Maybe
    +    , mapMaybe
    +    , catMaybes
    +    , fromMaybe
    +    , isJust
    +    , isNothing
    +    , listToMaybe
    +      -- ** Either
    +    , partitionEithers
    +    , lefts
    +    , rights
    +      -- ** Ord
    +    , on
    +    , comparing
    +      -- ** Say
    +    , say
    +    , sayString
    +    , sayShow
    +    , sayErr
    +    , sayErrString
    +    , sayErrShow
    +    , hSay
    +    , hSayString
    +    , hSayShow
    +      -- ** IORef
    +    , IORef
    +    , newIORef
    +    , readIORef
    +    , writeIORef
    +    , modifyIORef
    +    , modifyIORef'
    +    , atomicModifyIORef
    +    , atomicModifyIORef'
    +    , atomicWriteIORef
    +    , mkWeakIORef
    +      -- ** IO
    +    , IO.Handle
    +    , IO.IOMode (..)
    +    , IO.stdin
    +    , IO.stdout
    +    , IO.stderr
    +    , IO.hClose
    +    , IO.withBinaryFile
    +    , readFile
    +    , writeFile
    +    , readFileUtf8
    +    , writeFileUtf8
    +      -- ** Character encoding
    +    , encodeUtf8
    +    , decodeUtf8
    +      -- ** deepseq
    +    , NFData (rnf)
    +    , deepseq
    +    , ($!!)
    +    , force
    +      -- ** Monoids
    +    , (++)
    +      -- ** Read
    +    , readMaybe
    +    , readEither
    +    ) where
    +
    +import Control.Exception.Safe
    +import Data.Maybe
    +import Data.Function
    +import Data.Ord
    +import Data.Either
    +import Control.Arrow
    +import Data.ByteString (ByteString, readFile, writeFile)
    +import Data.Text (Text)
    +import Data.Foldable hiding (sum, product, mapM_, forM_, sequence_, msum)
    +import Data.Traversable hiding (mapM, sequence)
    +import Data.String
    +import Data.Int
    +import Data.Word
    +import Prelude (Bool (..), Char, IO, Integer, Rational, Float, Double, Eq (..), Bounded (..), Show (..), Num (..), Real (..), Integral (..), Fractional (..), Floating (..), RealFrac (..), RealFloat (..), (^), (^^), subtract, fromIntegral, realToFrac)
    +import Data.Map (Map)
    +import Data.IntMap (IntMap)
    +import Data.HashMap.Strict (HashMap)
    +import Data.Set (Set)
    +import Data.IntSet (IntSet)
    +import Data.HashSet (HashSet)
    +import Data.Sequence (Seq)
    +import Control.Applicative
    +import Control.Monad
    +import Data.Functor
    +import Control.Concurrent hiding (throwTo)
    +import Control.Monad.IO.Class
    +import Control.Monad.Trans.Class
    +import Control.Monad.Reader
    +import Data.Functor.Identity
    +import Data.Hashable
    +import qualified Prelude
    +import Data.Monoid hiding ((<>))
    +import Say
    +import Data.Semigroup
    +import Text.Read
    +import Data.Typeable
    +import Data.IORef
    +import qualified System.IO as IO
    +import Data.Text.Encoding (encodeUtf8, decodeUtf8With)
    +import Data.Text.Encoding.Error (lenientDecode)
    +import Control.DeepSeq
    +
    +-- | Get the sum of the elements in a 'Foldable'.
    +--
    +-- This is not the same as the function from 'Data.Foldable'; instead,
    +-- this function uses a strict left fold.
    +--
    +-- @since 0.1.0.0
    +sum :: (Foldable f, Num a) => f a -> a
    +sum = foldl' (+) 0
    +
    +-- | Get the product of the elements in a 'Foldable'.
    +--
    +-- This is not the same as the function from 'Data.Foldable'; instead,
    +-- this function uses a strict left fold.
    +--
    +-- @since 0.1.0.0
    +product :: (Foldable f, Num a) => f a -> a
    +product = foldl' (*) 1
    +
    +-- | Operator version of 'mappend'.
    +--
    +-- In base, this operator is known as '<>'. However, this is the name
    +-- of the operator for 'Semigroup' as well. Once 'Semigroup' is a
    +-- superclass of 'Monoid', this historical accident will be
    +-- unimportant. In the meanwhile, 'SafePrelude' deals with this
    +-- situation by making '<>' the 'Semigroup' operator, and '++' the
    +-- 'Monoid' operator.
    +--
    +-- @since 0.1.0.0
    +(++) :: Monoid m => m -> m -> m
    +(++) = mappend
    +{-# INLINE (++) #-}
    +infixr 5  ++
    +
    +-- | A total function for decoding a 'ByteString' into 'Text' using a
    +-- UTF-8 character encoding. This uses 'lenientDecode' in the case of
    +-- any encoding errors.
    +--
    +-- @since 0.1.0.0
    +decodeUtf8 :: ByteString -> Text
    +decodeUtf8 = decodeUtf8With lenientDecode
    +
    +-- | Read a file assuming a UTF-8 character encoding.
    +--
    +-- This leverages 'decodeUtf8', so in the event of a character
    +-- encoding issue, replacement characters will be used.
    +--
    +-- @since 0.1.0.0
    +readFileUtf8 :: MonadIO m => IO.FilePath -> m Text
    +readFileUtf8 = liftIO . fmap decodeUtf8 . readFile
    +
    +-- | Write a file using a UTF-8 character encoding.
    +--
    +-- @since 0.1.0.0
    +writeFileUtf8 :: MonadIO m => IO.FilePath -> Text -> m ()
    +writeFileUtf8 fp = liftIO . writeFile fp . encodeUtf8
    +
    +-- | Synonym for 'traverse_'; different from base to generalize to
    +-- 'Applicative'.
    +--
    +-- @since 0.1.0.0
    +mapM_ :: (Applicative m, Foldable f) => (a -> m b) -> f a -> m ()
    +mapM_ = traverse_
    +
    +
    +-- | Flipped version of 'mapM_'.
    +--
    +-- @since 0.1.0.0
    +forM_ :: (Applicative m, Foldable f) => f a -> (a -> m b) -> m ()
    +forM_ = for_
    +
    +-- | Synonym for 'sequence_'; different from base to generalize to
    +-- 'Applicative'.
    +--
    +-- @since 0.1.0.0
    +sequence_ :: (Applicative m, Foldable f) => f (m a) -> m ()
    +sequence_ = sequenceA_
    +
    +-- | Synonym for 'traverse'; different from base to generalize to
    +-- 'Applicative'.
    +--
    +-- @since 0.1.0.0
    +mapM :: (Applicative m, Traversable t) => (a -> m b) -> t a -> m (t b)
    +mapM = traverse
    +
    +-- | Flipped version of 'mapM'.
    +--
    +-- @since 0.1.0.0
    +forM :: (Applicative m, Traversable t) => t a -> (a -> m b) -> m (t b)
    +forM = for
    +
    +-- | Synonym for 'sequenceA'; different from base to generalize to
    +-- 'Applicative'.
    +--
    +-- @since 0.1.0.0
    +sequence :: (Applicative m, Traversable t) => t (m a) -> m (t a)
    +sequence = sequenceA
    +
    +#if !MIN_VERSION_base(4, 8, 0)
    +-- Copied straight from base
    +
    +-- | Test whether the structure is empty. The default implementation is
    +-- optimized for structures that are similar to cons-lists, because there
    +-- is no general way to do better.
    +null :: Foldable t => t a -> Bool
    +null = foldr (\_ _ -> False) True
    +
    +-- | Returns the size/length of a finite structure as an 'Int'.  The
    +-- default implementation is optimized for structures that are similar to
    +-- cons-lists, because there is no general way to do better.
    +length :: Foldable t => t a -> Int
    +length = foldl' (\c _ -> c+1) 0
    +
    +-- | '&' is a reverse application operator.  This provides notational
    +-- convenience.  Its precedence is one higher than that of the forward
    +-- application operator '$', which allows '&' to be nested in '$'.
    +--
    +-- @since 4.8.0.0
    +(&) :: a -> (a -> b) -> b
    +x & f = f x
    +
    +
    +-- | Strict version of 'Data.Functor.<$>'.
    +--
    +-- @since 4.8.0.0
    +(<$!>) :: Monad m => (a -> b) -> m a -> m b
    +{-# INLINE (<$!>) #-}
    +f <$!> m = do
    +  x <- m
    +  let z = f x
    +  z `Prelude.seq` return z
    +#endif
    +
    \ No newline at end of file diff --git a/static/safe-prelude/src/highlight.js b/static/safe-prelude/src/highlight.js new file mode 100644 index 0000000..1e903bd --- /dev/null +++ b/static/safe-prelude/src/highlight.js @@ -0,0 +1,27 @@ + +var highlight = function (on) { + return function () { + var links = document.getElementsByTagName('a'); + for (var i = 0; i < links.length; i++) { + var that = links[i]; + + if (this.href != that.href) { + continue; + } + + if (on) { + that.classList.add("hover-highlight"); + } else { + that.classList.remove("hover-highlight"); + } + } + } +}; + +window.onload = function () { + var links = document.getElementsByTagName('a'); + for (var i = 0; i < links.length; i++) { + links[i].onmouseover = highlight(true); + links[i].onmouseout = highlight(false); + } +}; diff --git a/static/safe-prelude/src/style.css b/static/safe-prelude/src/style.css new file mode 100644 index 0000000..e83dc5e --- /dev/null +++ b/static/safe-prelude/src/style.css @@ -0,0 +1,55 @@ +body { + background-color: #fdf6e3; +} + +.hs-identifier { + color: #073642; +} + +.hs-identifier.hs-var { +} + +.hs-identifier.hs-type { + color: #5f5faf; +} + +.hs-keyword { + color: #af005f; +} + +.hs-string, .hs-char { + color: #cb4b16; +} + +.hs-number { + color: #268bd2; +} + +.hs-operator { + color: #d33682; +} + +.hs-glyph, .hs-special { + color: #dc322f; +} + +.hs-comment { + color: #8a8a8a; +} + +.hs-pragma { + color: #2aa198; +} + +.hs-cpp { + color: #859900; +} + +a:link, a:visited { + text-decoration: none; + border-bottom: 1px solid #eee8d5; +} + +a:hover, a.hover-highlight { + background-color: #eee8d5; +} diff --git a/static/safe-prelude/synopsis.png b/static/safe-prelude/synopsis.png new file mode 100644 index 0000000..85fb86e Binary files /dev/null and b/static/safe-prelude/synopsis.png differ