hydrogen-prelude-0.20: Hydrogen Prelude

Safe HaskellNone
LanguageHaskell2010

Hydrogen.Prelude

Synopsis

Documentation

module Prelude

module Data.Array

module Data.Bits

module Data.Bool

module Data.Char

module Data.Fixed

module Data.Int

module Data.Ix

module Data.List

module Data.Maybe

module Data.Ord

module Data.Ratio

module Data.Time

module Data.Tuple

module Data.Word

module Numeric

(.&) :: (a -> Bool) -> (a -> Bool) -> a -> Bool Source

(.|) :: (a -> Bool) -> (a -> Bool) -> a -> Bool Source

(.^) :: (a -> Bool) -> (a -> Bool) -> a -> Bool Source

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

(|>) :: a -> (a -> b) -> b Source

flip ($)

($$) :: (a -> b -> z) -> (a, b) -> z infixr 0 Source

($$$) :: (a -> b -> c -> z) -> (a, b, c) -> z infixr 0 Source

($$$$) :: (a -> b -> c -> d -> z) -> (a, b, c, d) -> z infixr 0 Source

($$$$$) :: (a -> b -> c -> d -> e -> z) -> (a, b, c, d, e) -> z infixr 0 Source

(<$$>) :: Functor f => (a -> b -> z) -> f (a, b) -> f z infixl 4 Source

(<$$$>) :: Functor f => (a -> b -> c -> z) -> f (a, b, c) -> f z infixl 4 Source

(<$$$$>) :: Functor f => (a -> b -> c -> d -> z) -> f (a, b, c, d) -> f z infixl 4 Source

(<$$$$$>) :: Functor f => (a -> b -> c -> d -> e -> z) -> f (a, b, c, d, e) -> f z infixl 4 Source

randomUUID :: IO UUID Source

Produces a random V4 UUID (alias for nextRandom).

safeHead Source

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

firstJust :: [a -> Maybe b] -> a -> Maybe b Source

Applies a bunch of functions on a given value, returns the first result that is not Nothing (or Nothing if no Just value was produced).

uncurry3 :: (a -> b -> c -> z) -> (a, b, c) -> z Source

uncurry4 :: (a -> b -> c -> d -> z) -> (a, b, c, d) -> z Source

uncurry5 :: (a -> b -> c -> d -> e -> z) -> (a, b, c, d, e) -> z Source

map :: Functor f => (a -> b) -> f a -> f b Source

map as it should be: fmap.

data UUID :: *

The UUID type. A Random instance is provided which produces version 4 UUIDs as specified in RFC 4122. The Storable and Binary instances are compatible with RFC 4122, storing the fields in network order as 16 bytes.

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.

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 Generic clause to your datatype and declare a Serialize instance for it without giving a definition for put and get.

Instances

Serialize Bool 
Serialize Char 
Serialize Double 
Serialize Float 
Serialize Int 
Serialize Int8 
Serialize Int16 
Serialize Int32 
Serialize Int64 
Serialize Integer 
Serialize Ordering 
Serialize Word 
Serialize Word8 
Serialize Word16 
Serialize Word32 
Serialize Word64 
Serialize () 
Serialize All 
Serialize Any 
Serialize ByteString 
Serialize ByteString 
Serialize IntSet 
Serialize Version 
Serialize LocalTime 
Serialize ZonedTime 
Serialize TimeOfDay 
Serialize TimeZone 
Serialize Day 
Serialize UniversalTime 
Serialize UUID 
Serialize a => Serialize [a] 
(Serialize a, Integral a) => Serialize (Ratio a) 
Serialize (Fixed E12) 
Serialize a => Serialize (Dual a) 
Serialize a => Serialize (Sum a) 
Serialize a => Serialize (Product a) 
Serialize a => Serialize (First a) 
Serialize a => Serialize (Last a) 
Serialize a => Serialize (Maybe a) 
Serialize e => Serialize (IntMap e) 
(Ord a, Serialize a) => Serialize (Set a) 
Serialize e => Serialize (Tree e) 
Serialize e => Serialize (Seq e) 
(Serialize a, Serialize b) => Serialize (Either a b) 
(Serialize a, Serialize b) => Serialize (a, b) 
(Serialize i, Ix i, Serialize e, IArray UArray e) => Serialize (UArray i e) 
(Serialize i, Ix i, Serialize e) => Serialize (Array i e) 
(Ord k, Serialize k, Serialize e) => Serialize (Map k e) 
(Serialize a, Serialize b, Serialize c) => Serialize (a, b, c) 
(Serialize a, Serialize b, Serialize c, Serialize d) => Serialize (a, b, c, d) 
(Serialize a, Serialize b, Serialize c, Serialize d, Serialize e) => Serialize (a, b, c, d, e) 
(Serialize a, Serialize b, Serialize c, Serialize d, Serialize e, Serialize f) => Serialize (a, b, c, d, e, f) 
(Serialize a, Serialize b, Serialize c, Serialize d, Serialize e, Serialize f, Serialize g) => Serialize (a, b, c, d, e, f, g) 
(Serialize a, Serialize b, Serialize c, Serialize d, Serialize e, Serialize f, Serialize g, Serialize h) => Serialize (a, b, c, d, e, f, g, h) 
(Serialize a, Serialize b, Serialize c, Serialize d, Serialize e, Serialize f, Serialize g, Serialize h, Serialize i) => Serialize (a, b, c, d, e, f, g, h, i) 
(Serialize a, Serialize b, Serialize c, Serialize d, Serialize e, Serialize f, Serialize g, Serialize h, Serialize i, Serialize j) => Serialize (a, b, c, d, e, f, g, h, i, j) 

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

Binary Bool 
Binary Char 
Binary Double 
Binary Float 
Binary Int 
Binary Int8 
Binary Int16 
Binary Int32 
Binary Int64 
Binary Integer 
Binary Ordering 
Binary Word 
Binary Word8 
Binary Word16 
Binary Word32 
Binary Word64 
Binary () 
Binary ByteString 
Binary ByteString 
Binary IntSet 
Binary Version 
Binary LocalTime 
Binary ZonedTime 
Binary TimeOfDay 
Binary TimeZone 
Binary Day 
Binary UniversalTime 
Binary UUID 
Binary a => Binary [a] 
(Binary a, Integral a) => Binary (Ratio a) 
Binary (Fixed E12) 
Binary a => Binary (Maybe a) 
Binary e => Binary (IntMap e) 
Binary a => Binary (Set a) 
Binary e => Binary (Tree e) 
Binary e => Binary (Seq e) 
(Binary a, Binary b) => Binary (Either a b) 
(Binary a, Binary b) => Binary (a, b) 
(Binary i, Ix i, Binary e, IArray UArray e) => Binary (UArray i e) 
(Binary i, Ix i, Binary e) => Binary (Array i e) 
(Binary k, Binary e) => Binary (Map k e) 
(Binary a, Binary b, Binary c) => Binary (a, b, c) 
(Binary a, Binary b, Binary c, Binary d) => Binary (a, b, c, d) 
(Binary a, Binary b, Binary c, Binary d, Binary e) => Binary (a, b, c, d, e) 
(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f) => Binary (a, b, c, d, e, f) 
(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g) => Binary (a, b, c, d, e, f, g) 
(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g, Binary h) => Binary (a, b, c, d, e, f, g, h) 
(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g, Binary h, Binary i) => Binary (a, b, c, d, e, f, g, h, i) 
(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g, Binary h, Binary i, Binary j) => Binary (a, b, c, d, e, f, g, h, i, j) 

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.

Minimal complete definition

from, to

type List a = [a] Source

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 

data ShowBox Source

Instances

class TMap a where Source

Associated Types

type Component x Source

type Transform x Source

Methods

tmap :: (Component a -> b) -> a -> Transform ((Component a -> b) -> a) Source

Instances

TMap [a] 
TMap (Seq a) 
TMap (a, a) 
TMap (Map k v) 
TMap (MultiMap k v) 
TMap (a, a, a) 
TMap (a, a, a, a) 

class Has a where Source

Associated Types

type HasKey a Source

type HasValue a Source

Methods

(!) :: a -> HasKey a -> HasValue a Source

Instances

Eq k => Has [(k, v)] 
Ix i => Has (Array i e) 
Ord k => Has (Map k v) 
Ord k => Has (MultiMap k v) 

class Container a where Source

Associated Types

type Contained a Source

Methods

(?) :: a -> Contained a -> Bool Source

Instances

Eq a => Container [a] 
Ord a => Container (Set a) 
Eq a => Container (Seq a) 
Ord k => Container (Map k v) 
Ord k => Container (MultiMap k v) 

__ :: a Source

A shorthand for undefined.