hydrogen-prelude-0.10: 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 ($)

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).

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.

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) 
(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) 
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) 
(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.