| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Hydrogen.Prelude
- module Prelude
- module Control.Applicative
- module Control.Arrow
- module Control.Monad
- module Data.Array
- module Data.Bits
- module Data.Bool
- module Data.Char
- module Data.Complex
- module Data.Dynamic
- module Data.Either
- module Data.Fixed
- module Data.Function
- module Data.Functor.Identity
- module Data.Functor.Reverse
- module Data.Hashable
- module Data.Foldable
- module Data.Int
- module Data.Ix
- module Data.List
- module Data.Maybe
- module Data.Ord
- module Data.Ratio
- module Data.String
- module Data.Time
- module Data.Time.Calendar.OrdinalDate
- module Data.Traversable
- module Data.Tuple
- module Data.Typeable
- module Data.Word
- module Hydrogen.Version
- module Numeric
- module Text.Printf
- (.&) :: (a -> Bool) -> (a -> Bool) -> a -> Bool
- (.|) :: (a -> Bool) -> (a -> Bool) -> a -> Bool
- (.^) :: (a -> Bool) -> (a -> Bool) -> a -> Bool
- (=~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext Regex source1 target) => source1 -> source -> target
- (=~~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext Regex source1 target, Monad m) => source1 -> source -> m target
- (|>) :: a -> (a -> b) -> b
- ($$) :: (a -> b -> z) -> (a, b) -> z
- ($$$) :: (a -> b -> c -> z) -> (a, b, c) -> z
- ($$$$) :: (a -> b -> c -> d -> z) -> (a, b, c, d) -> z
- ($$$$$) :: (a -> b -> c -> d -> e -> z) -> (a, b, c, d, e) -> z
- (<$$>) :: Functor f => (a -> b -> z) -> f (a, b) -> f z
- (<$$$>) :: Functor f => (a -> b -> c -> z) -> f (a, b, c) -> f z
- (<$$$$>) :: Functor f => (a -> b -> c -> d -> z) -> f (a, b, c, d) -> f z
- (<$$$$$>) :: Functor f => (a -> b -> c -> d -> e -> z) -> f (a, b, c, d, e) -> f z
- uuidFromString :: String -> Maybe UUID
- randomUUID :: IO UUID
- safeHead :: a -> [a] -> a
- safeHeadAndTail :: a -> [a] -> (a, [a])
- safeHeadAndTail2 :: a -> a -> [a] -> (a, a, [a])
- firstJust :: [a -> Maybe b] -> a -> Maybe b
- uncurry3 :: (a -> b -> c -> z) -> (a, b, c) -> z
- uncurry4 :: (a -> b -> c -> d -> z) -> (a, b, c, d) -> z
- uncurry5 :: (a -> b -> c -> d -> e -> z) -> (a, b, c, d, e) -> z
- map :: Functor f => (a -> b) -> f a -> f b
- data UUID :: *
- data ByteString :: *
- type LazyByteString = ByteString
- class Serialize t
- encode :: Serialize a => a -> ByteString
- encodeLazy :: Serialize a => a -> LazyByteString
- decode :: Serialize a => ByteString -> Either String a
- decodeLazy :: Serialize a => LazyByteString -> Either String a
- class Binary t
- binaryEncode :: Binary a => a -> LazyByteString
- binaryDecode :: Binary a => LazyByteString -> a
- binaryEncodeFile :: Binary a => FilePath -> a -> IO ()
- binaryDecodeFile :: Binary a => FilePath -> IO a
- class Generic a
- type List a = [a]
- data Map k a :: * -> * -> *
- data MultiMap k v :: * -> * -> *
- data Seq a :: * -> *
- data Set a :: * -> *
- data ShowBox
- class TMap a where
- class Has a where
- class Container a where
- class Default a where
- def :: a
- __ :: a
Documentation
module Prelude
module Control.Applicative
module Control.Arrow
module Control.Monad
module Data.Array
module Data.Bits
module Data.Bool
module Data.Char
module Data.Complex
module Data.Dynamic
module Data.Either
module Data.Fixed
module Data.Function
module Data.Functor.Identity
module Data.Functor.Reverse
module Data.Hashable
module Data.Foldable
module Data.Int
module Data.Ix
module Data.List
module Data.Maybe
module Data.Ord
module Data.Ratio
module Data.String
module Data.Time
module Data.Traversable
module Data.Tuple
module Data.Typeable
module Data.Word
module Hydrogen.Version
module Numeric
module Text.Printf
(=~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext Regex source1 target) => source1 -> source -> target
This is the pure functional matching operator. If the target
cannot be produced then some empty result will be returned. If
there is an error in processing, then error will be called.
(=~~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext Regex source1 target, Monad m) => source1 -> source -> m target
This is the monadic matching operator. If a single match fails,
then fail will be called.
uuidFromString :: String -> Maybe UUID Source
randomUUID :: IO UUID Source
Produces a random V4 UUID (alias for nextRandom).
Arguments
| :: a | The default value for the case of the empty list. |
| -> [a] | The list. |
| -> a |
Returns the head of the list or the default value.
safeHeadAndTail :: a -> [a] -> (a, [a]) Source
safeHeadAndTail2 :: a -> a -> [a] -> (a, a, [a]) Source
data UUID :: *
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
type LazyByteString = ByteString Source
class Serialize t
If your compiler has support for the DeriveGeneric and
DefaultSignatures language extensions (ghc >= 7.2.1), the put and get
methods will have default generic implementations.
To use this option, simply add a deriving clause to your datatype
and declare a GenericSerialize instance for it without giving a definition for
put and get.
Instances
encode :: Serialize a => a -> ByteString Source
Encode a value using binary serialization to a strict ByteString.
encodeLazy :: Serialize a => a -> LazyByteString Source
Encode a value using binary serialization to a lazy ByteString.
decode :: Serialize a => ByteString -> Either String a Source
Decode a value from a strict ByteString, reconstructing the original structure.
decodeLazy :: Serialize a => LazyByteString -> Either String a Source
Decode a value from a lazy ByteString, reconstructing the original structure.
class Binary t
The Binary class provides put and get, methods to encode and
decode a Haskell value to a lazy ByteString. It mirrors the Read and
Show classes for textual representation of Haskell types, and is
suitable for serialising Haskell values to disk, over the network.
For decoding and generating simple external binary formats (e.g. C
structures), Binary may be used, but in general is not suitable
for complex protocols. Instead use the Put and Get primitives
directly.
Instances of Binary should satisfy the following property:
decode . encode == id
That is, the get and put methods should be the inverse of each
other. A range of instances are provided for basic Haskell types.
Instances
binaryEncode :: Binary a => a -> LazyByteString Source
Encode a value using binary serialisation to a lazy ByteString.
binaryDecode :: Binary a => LazyByteString -> a Source
Decode a value from a lazy ByteString, reconstructing the original structure.
binaryEncodeFile :: Binary a => FilePath -> a -> IO () Source
Lazily serialise a value to a file.
binaryDecodeFile :: Binary a => FilePath -> IO a Source
Decode a value from a file. In case of errors, error will be called with the error message.
class Generic a
Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.
Instances
| Generic Bool | |
| Generic Char | |
| Generic Double | |
| Generic Float | |
| Generic Int | |
| Generic Ordering | |
| Generic () | |
| Generic All | |
| Generic Any | |
| Generic Arity | |
| Generic Fixity | |
| Generic Associativity | |
| Generic Version | |
| Generic LocalTime | |
| Generic ZonedTime | |
| Generic TimeOfDay | |
| Generic TimeZone | |
| Generic Day | |
| Generic UniversalTime | |
| Generic [a] | |
| Generic (U1 p) | |
| Generic (Par1 p) | |
| Generic (ZipList a) | |
| Generic (Dual a) | |
| Generic (Endo a) | |
| Generic (Sum a) | |
| Generic (Product a) | |
| Generic (First a) | |
| Generic (Last a) | |
| Generic (Maybe a) | |
| Generic (Either a b) | |
| Generic (Rec1 f p) | |
| Generic (a, b) | |
| Generic (Const a b) | |
| Generic (WrappedMonad m a) | |
| Generic (Proxy * t) | |
| Generic (MultiMap k v) | |
| Generic (K1 i c p) | |
| Generic ((:+:) f g p) | |
| Generic ((:*:) f g p) | |
| Generic ((:.:) f g p) | |
| Generic (a, b, c) | |
| Generic (WrappedArrow a b c) | |
| Generic (M1 i c f p) | |
| Generic (a, b, c, d) | |
| Generic (a, b, c, d, e) | |
| Generic (a, b, c, d, e, f) | |
| Generic (a, b, c, d, e, f, g) |
data Map k a :: * -> * -> *
A Map from keys k to values a.
Instances
| Functor (Map k) | |
| Foldable (Map k) | |
| Traversable (Map k) | |
| (Eq k, Eq a) => Eq (Map k a) | |
| (Data k, Data a, Ord k) => Data (Map k a) | |
| (Ord k, Ord v) => Ord (Map k v) | |
| (Ord k, Read k, Read e) => Read (Map k e) | |
| (Show k, Show a) => Show (Map k a) | |
| Ord k => Monoid (Map k v) | |
| (Binary k, Binary e) => Binary (Map k e) | |
| (Ord k, Serialize k, Serialize e) => Serialize (Map k e) | |
| (NFData k, NFData a) => NFData (Map k a) | |
| Ord k => Container (Map k v) | |
| Ord k => Has (Map k v) | |
| TMap (Map k v) | |
| Typeable (* -> * -> *) Map | |
| type Contained (Map k v) = k | |
| type HasKey (Map k v) = k | |
| type HasValue (Map k v) = v | |
| type Component (Map k v) = v | |
| type Transform ((v -> w) -> Map k v) = Map k w |
data MultiMap k v :: * -> * -> *
Instances
| Functor (MultiMap k) | |
| Foldable (MultiMap k) | |
| Traversable (MultiMap k) | |
| (Eq k, Eq v) => Eq (MultiMap k v) | |
| (Ord k, Ord v) => Ord (MultiMap k v) | |
| (Show k, Show v) => Show (MultiMap k v) | |
| Generic (MultiMap k v) | |
| Ord k => Container (MultiMap k v) | |
| Ord k => Has (MultiMap k v) | |
| TMap (MultiMap k v) | |
| Typeable (* -> * -> *) MultiMap | |
| type Rep (MultiMap k v) = D1 D1MultiMap (C1 C1_0MultiMap ((:*:) (S1 NoSelector (Rec0 (Map k [v]))) (S1 NoSelector (Rec0 Int)))) | |
| type Contained (MultiMap k v) = k | |
| type HasKey (MultiMap k v) = k | |
| type HasValue (MultiMap k v) = [v] | |
| type Component (MultiMap k v) = v | |
| type Transform ((v -> w) -> MultiMap k v) = MultiMap k w |
data Seq a :: * -> *
General-purpose finite sequences.
Instances
| Alternative Seq | |
| Monad Seq | |
| Functor Seq | |
| MonadPlus Seq | |
| Applicative Seq | |
| Foldable Seq | |
| Traversable Seq | |
| RegexMaker Regex CompOption ExecOption (Seq Char) | |
| RegexLike Regex (Seq Char) | |
| RegexContext Regex (Seq Char) (Seq Char) | |
| Eq a => Eq (Seq a) | |
| Data a => Data (Seq a) | |
| Ord a => Ord (Seq a) | |
| Read a => Read (Seq a) | |
| Show a => Show (Seq a) | |
| Monoid (Seq a) | |
| Binary e => Binary (Seq e) | |
| Serialize e => Serialize (Seq e) | |
| NFData a => NFData (Seq a) | |
| Extract (Seq a) | |
| Eq a => Container (Seq a) | |
| TMap (Seq a) | |
| Typeable (* -> *) Seq | |
| type Contained (Seq a) = a | |
| type Component (Seq a) = a | |
| type Transform ((a -> b) -> Seq a) = Seq b |
data Set a :: * -> *
A set of values a.
Instances
| Foldable Set | |
| Eq a => Eq (Set a) | |
| (Data a, Ord a) => Data (Set a) | |
| Ord a => Ord (Set a) | |
| (Read a, Ord a) => Read (Set a) | |
| Show a => Show (Set a) | |
| Ord a => Monoid (Set a) | |
| Binary a => Binary (Set a) | |
| (Ord a, Serialize a) => Serialize (Set a) | |
| NFData a => NFData (Set a) | |
| Ord a => Container (Set a) | |
| Typeable (* -> *) Set | |
| type Contained (Set a) = a |