praglude-0.1.1.0: A pragmatic Prelude

Safe HaskellNone
LanguageHaskell2010

Praglude

Contents

Synopsis

The Original Prelude

module Prelude

Monoids

concat :: Monoid a => [a] -> a Source #

append :: Monoid a => a -> a -> a Source #

empty :: Monoid a => a Source #

Maybe

module Data.Maybe

Applicative

(<|>) :: Alternative f => forall a. f a -> f a -> f a #

An associative binary operation

Monads

Arrows

Mutable Variables In IO

module Data.IORef

Default

Lens

State monads

Painless String Types

s :: (ToString a, FromString b) => a -> b #

class ToString a where #

Defines how a given type should be converted to String. If at all possible, the conversion should be loss-less, and if encodings are involved, UTF-8 should be the default.

Minimal complete definition

toString

Methods

toString :: a -> String #

class FromString a #

Minimal complete definition

fromString

class IsString a where #

Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).

Minimal complete definition

fromString

Methods

fromString :: String -> a #

Instances

IsString ByteString 
IsString ByteString 
IsString Value 

Methods

fromString :: String -> Value #

IsString ShortByteString 
(~) * 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 #

(~) * a Char => IsString (DList a) 

Methods

fromString :: String -> DList a #

IsString a => IsString (Const * a b) 

Methods

fromString :: String -> Const * a b #

IsString a => IsString (Tagged k s a) 

Methods

fromString :: String -> Tagged k s a #

type Text = Text Source #

Generalized String Operations

trim :: (FromString a, ToString a) => a -> a Source #

ltrim :: (FromString a, ToString a) => a -> a Source #

rtrim :: (FromString a, ToString a) => a -> a Source #

words :: (FromString a, ToString a) => a -> [a] Source #

lines :: (FromString a, ToString a) => a -> [a] Source #

module Data.Char

String Case Conversions

kebab :: String -> String #

Directly convert to kebab-case through fromAny

snake :: String -> String #

Directly convert to snake_Case through fromAny

pascal :: String -> String #

Directly convert to PascalCase through fromAny

I/O

stderr :: Handle #

A handle managing output to the Haskell program's standard error channel.

stdout :: Handle #

A handle managing output to the Haskell program's standard output channel.

stdin :: Handle #

A handle managing input from the Haskell program's standard input channel.

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 

Environment

Generalized I/O

class StringIO a where Source #

Types that can be written to / read from file descriptors.

Minimal complete definition

putStr, hPutStr, readFile, writeFile, getContents, hGetContents

Methods

putStr :: a -> IO () Source #

putStrLn :: a -> IO () Source #

hPutStr :: Handle -> a -> IO () Source #

hPutStrLn :: Handle -> a -> IO () Source #

readFile :: FilePath -> IO a Source #

writeFile :: FilePath -> a -> IO () Source #

getContents :: IO a Source #

hGetContents :: Handle -> IO a Source #

Instances

StringIO String Source # 
StringIO LByteString Source # 
StringIO ByteString Source # 
StringIO LText Source # 
StringIO Text Source # 

Printf

Filename And File System Manipulation

Type Forcers

Container Types With Unified Interfaces

newtype AList k v Source #

Constructors

AList 

Fields

Instances

Eq k => DictLike AList k Source # 

Methods

insert :: k -> v -> AList k v -> AList k v Source #

delete :: k -> AList k v -> AList k v Source #

update :: k -> (v -> Maybe v) -> AList k v -> AList k v Source #

pairs :: AList k v -> [(k, v)] Source #

fromPairs :: [(k, v)] -> AList k v Source #

keys :: AList k v -> [k] Source #

elems :: AList k v -> [v] Source #

singletonMap :: k -> v -> AList k v Source #

member :: k -> AList k v -> Bool Source #

Functor (AList k) Source # 

Methods

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

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

Eq k => Lookup (AList k) k Source # 

Methods

lookup :: k -> AList k v -> Maybe v Source #

lookupDef :: v -> k -> AList k v -> v Source #

(Eq v, Eq k) => Eq (AList k v) Source # 

Methods

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

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

(Ord v, Ord k) => Ord (AList k v) Source # 

Methods

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

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

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

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

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

max :: AList k v -> AList k v -> AList k v #

min :: AList k v -> AList k v -> AList k v #

(Read v, Read k) => Read (AList k v) Source # 
(Show v, Show k) => Show (AList k v) Source # 

Methods

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

show :: AList k v -> String #

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

Generic (AList k v) Source # 

Associated Types

type Rep (AList k v) :: * -> * #

Methods

from :: AList k v -> Rep (AList k v) x #

to :: Rep (AList k v) x -> AList k v #

type Rep (AList k v) Source # 
type Rep (AList k v) = D1 (MetaData "AList" "Praglude" "praglude-0.1.1.0-GKXm4qTmMG94uj6a7hnJH5" True) (C1 (MetaCons "AList" PrefixI True) (S1 (MetaSel (Just Symbol "unAList") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(k, v)])))

data LHashMap k v Source #

A lazy hash map. Because HashMap is actually the exact same type as HashMap, we wrap it in a newtype so that we can tie laziness into the type itself (similar to how it works for Text and ByteString).

Instances

(Eq k, Hashable k) => DictLike LHashMap k Source # 

Methods

insert :: k -> v -> LHashMap k v -> LHashMap k v Source #

delete :: k -> LHashMap k v -> LHashMap k v Source #

update :: k -> (v -> Maybe v) -> LHashMap k v -> LHashMap k v Source #

pairs :: LHashMap k v -> [(k, v)] Source #

fromPairs :: [(k, v)] -> LHashMap k v Source #

keys :: LHashMap k v -> [k] Source #

elems :: LHashMap k v -> [v] Source #

singletonMap :: k -> v -> LHashMap k v Source #

member :: k -> LHashMap k v -> Bool Source #

Functor (LHashMap k) Source # 

Methods

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

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

Foldable (LHashMap k) Source # 

Methods

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

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

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

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

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

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

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

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

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

null :: LHashMap k a -> Bool #

length :: LHashMap k a -> Int #

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

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

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

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

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

Traversable (LHashMap k) Source # 

Methods

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

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

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

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

Filterable (LHashMap k) Source # 

Methods

filter :: (v -> Bool) -> LHashMap k v -> LHashMap k v Source #

(Eq k, Hashable k) => Lookup (LHashMap k) k Source # 

Methods

lookup :: k -> LHashMap k v -> Maybe v Source #

lookupDef :: v -> k -> LHashMap k v -> v Source #

(Eq v, Eq k) => Eq (LHashMap k v) Source # 

Methods

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

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

(Hashable k, Eq k, Data v, Data k) => Data (LHashMap k v) Source # 

Methods

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

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

toConstr :: LHashMap k v -> Constr #

dataTypeOf :: LHashMap k v -> DataType #

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

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

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

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

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

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

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

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

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

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

(Read v, Read k, Hashable k, Eq k) => Read (LHashMap k v) Source # 
(Show v, Show k) => Show (LHashMap k v) Source # 

Methods

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

show :: LHashMap k v -> String #

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

Generic (LHashMap k v) Source # 

Associated Types

type Rep (LHashMap k v) :: * -> * #

Methods

from :: LHashMap k v -> Rep (LHashMap k v) x #

to :: Rep (LHashMap k v) x -> LHashMap k v #

(Hashable k, Eq k) => Semigroup (LHashMap k v) Source # 

Methods

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

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

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

(Hashable k, Eq k) => Monoid (LHashMap k v) Source # 

Methods

mempty :: LHashMap k v #

mappend :: LHashMap k v -> LHashMap k v -> LHashMap k v #

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

(Hashable v, Hashable k) => Hashable (LHashMap k v) Source # 

Methods

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

hash :: LHashMap k v -> Int #

(NFData v, NFData k) => NFData (LHashMap k v) Source # 

Methods

rnf :: LHashMap k v -> () #

(Eq k, Hashable k) => SetLike (LHashMap k v) (k, v) Source # 

Methods

conj :: (k, v) -> LHashMap k v -> LHashMap k v Source #

remove :: (k, v) -> LHashMap k v -> LHashMap k v Source #

elem :: (k, v) -> LHashMap k v -> Bool Source #

null :: LHashMap k v -> Bool Source #

items :: LHashMap k v -> [(k, v)] Source #

fromItems :: [(k, v)] -> LHashMap k v Source #

singleton :: (k, v) -> LHashMap k v Source #

size :: LHashMap k v -> Int Source #

type Rep (LHashMap k v) Source # 
type Rep (LHashMap k v) = D1 (MetaData "LHashMap" "Praglude" "praglude-0.1.1.0-GKXm4qTmMG94uj6a7hnJH5" True) (C1 (MetaCons "LHashMap" PrefixI True) (S1 (MetaSel (Just Symbol "unLHashMap") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap k v))))

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

A Map from keys k to values a.

Instances

(Eq k, Ord k) => DictLike Map k Source # 

Methods

insert :: k -> v -> Map k v -> Map k v Source #

delete :: k -> Map k v -> Map k v Source #

update :: k -> (v -> Maybe v) -> Map k v -> Map k v Source #

pairs :: Map k v -> [(k, v)] Source #

fromPairs :: [(k, v)] -> Map k v Source #

keys :: Map k v -> [k] Source #

elems :: Map k v -> [v] Source #

singletonMap :: k -> v -> Map k v Source #

member :: k -> Map k v -> Bool Source #

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

ToJSONKey k => ToJSON1 (Map k) 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Map k a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Map k a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Map k a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Map k a] -> Encoding #

(FromJSONKey k, Ord k) => FromJSON1 (Map k) 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Map k a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Map k a] #

Filterable (Map k) Source # 

Methods

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

(Eq k, Ord k) => Lookup (Map k) k Source # 

Methods

lookup :: k -> Map k v -> Maybe v Source #

lookupDef :: v -> k -> Map k v -> v Source #

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 #

(ToJSON v, ToJSONKey k) => ToJSON (Map k v) 

Methods

toJSON :: Map k v -> Value #

toEncoding :: Map k v -> Encoding #

toJSONList :: [Map k v] -> Value #

toEncodingList :: [Map k v] -> Encoding #

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

Methods

parseJSON :: Value -> Parser (Map k v) #

parseJSONList :: Value -> Parser [Map k v] #

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

Methods

rnf :: Map k a -> () #

Ord k => Ixed (Map k a) 

Methods

ix :: Index (Map k a) -> Traversal' (Map k a) (IxValue (Map k a)) #

Ord k => At (Map k a) 

Methods

at :: Index (Map k a) -> Lens' (Map k a) (Maybe (IxValue (Map k a))) #

Ord k => Wrapped (Map k a) 

Associated Types

type Unwrapped (Map k a) :: * #

Methods

_Wrapped' :: Iso' (Map k a) (Unwrapped (Map k a)) #

((~) * t (Map k' a'), Ord k) => Rewrapped (Map k a) t

Use wrapping fromList. unwrapping returns a sorted list.

(Eq k, Ord k) => SetLike (Map k v) (k, v) Source # 

Methods

conj :: (k, v) -> Map k v -> Map k v Source #

remove :: (k, v) -> Map k v -> Map k v Source #

elem :: (k, v) -> Map k v -> Bool Source #

null :: Map k v -> Bool Source #

items :: Map k v -> [(k, v)] Source #

fromItems :: [(k, v)] -> Map k v Source #

singleton :: (k, v) -> Map k v Source #

size :: Map k v -> Int Source #

type Item (Map k v) 
type Item (Map k v) = (k, v)
type Index (Map k a) 
type Index (Map k a) = k
type IxValue (Map k a) 
type IxValue (Map k a) = a
type Unwrapped (Map k a) 
type Unwrapped (Map k a) = [(k, 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 #

ToJSON1 Set 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Set a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Set a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Set a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Set a] -> Encoding #

Filterable Set Source # 

Methods

filter :: (v -> Bool) -> Set v -> Set v Source #

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 #

ToJSON a => ToJSON (Set a) 

Methods

toJSON :: Set a -> Value #

toEncoding :: Set a -> Encoding #

toJSONList :: [Set a] -> Value #

toEncodingList :: [Set a] -> Encoding #

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

Methods

parseJSON :: Value -> Parser (Set a) #

parseJSONList :: Value -> Parser [Set a] #

NFData a => NFData (Set a) 

Methods

rnf :: Set a -> () #

Ord a => Contains (Set a) 

Methods

contains :: Index (Set a) -> Lens' (Set a) Bool #

Ord k => Ixed (Set k) 

Methods

ix :: Index (Set k) -> Traversal' (Set k) (IxValue (Set k)) #

Ord k => At (Set k) 

Methods

at :: Index (Set k) -> Lens' (Set k) (Maybe (IxValue (Set k))) #

Ord a => Wrapped (Set a) 

Associated Types

type Unwrapped (Set a) :: * #

Methods

_Wrapped' :: Iso' (Set a) (Unwrapped (Set a)) #

((~) * t (Set a'), Ord a) => Rewrapped (Set a) t

Use wrapping fromList. unwrapping returns a sorted list.

(Eq v, Ord v) => SetLike (Set v) v Source # 

Methods

conj :: v -> Set v -> Set v Source #

remove :: v -> Set v -> Set v Source #

elem :: v -> Set v -> Bool Source #

null :: Set v -> Bool Source #

items :: Set v -> [v] Source #

fromItems :: [v] -> Set v Source #

singleton :: v -> Set v Source #

size :: Set v -> Int Source #

type Item (Set a) 
type Item (Set a) = a
type Index (Set a) 
type Index (Set a) = a
type IxValue (Set k) 
type IxValue (Set k) = ()
type Unwrapped (Set a) 
type Unwrapped (Set a) = [a]

data Vector a :: * -> * #

Boxed vectors, supporting efficient slicing.

Instances

Monad Vector 

Methods

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

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

return :: a -> Vector a #

fail :: String -> Vector a #

Functor Vector 

Methods

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

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

Applicative Vector 

Methods

pure :: a -> Vector a #

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

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

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

Foldable Vector 

Methods

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

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

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

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

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

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

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

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

toList :: Vector a -> [a] #

null :: Vector a -> Bool #

length :: Vector a -> Int #

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

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

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

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

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

Traversable Vector 

Methods

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

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

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

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

ToJSON1 Vector 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Vector a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Vector a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Vector a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Vector a] -> Encoding #

FromJSON1 Vector 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Vector a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Vector a] #

Alternative Vector 

Methods

empty :: Vector a #

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

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

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

MonadPlus Vector 

Methods

mzero :: Vector a #

mplus :: Vector a -> Vector a -> Vector a #

Filterable Vector Source # 

Methods

filter :: (v -> Bool) -> Vector v -> Vector v Source #

Vector Vector a 

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) a -> m (Vector a) #

basicUnsafeThaw :: PrimMonad m => Vector a -> m (Mutable Vector (PrimState m) a) #

basicLength :: Vector a -> Int #

basicUnsafeSlice :: Int -> Int -> Vector a -> Vector a #

basicUnsafeIndexM :: Monad m => Vector a -> Int -> m a #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) a -> Vector a -> m () #

elemseq :: Vector a -> a -> b -> b #

Lookup Vector Int Source # 

Methods

lookup :: Int -> Vector v -> Maybe v Source #

lookupDef :: v -> Int -> Vector v -> v Source #

IsList (Vector a) 

Associated Types

type Item (Vector a) :: * #

Methods

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

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

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

Eq a => Eq (Vector a) 

Methods

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

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

Data a => Data (Vector a) 

Methods

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

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

toConstr :: Vector a -> Constr #

dataTypeOf :: Vector a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (Vector a) 

Methods

compare :: Vector a -> Vector a -> Ordering #

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

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

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

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

max :: Vector a -> Vector a -> Vector a #

min :: Vector a -> Vector a -> Vector a #

Read a => Read (Vector a) 
Show a => Show (Vector a) 

Methods

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

show :: Vector a -> String #

showList :: [Vector a] -> ShowS #

Monoid (Vector a) 

Methods

mempty :: Vector a #

mappend :: Vector a -> Vector a -> Vector a #

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

ToJSON a => ToJSON (Vector a) 
FromJSON a => FromJSON (Vector a) 
NFData a => NFData (Vector a) 

Methods

rnf :: Vector a -> () #

Ixed (Vector a) 

Methods

ix :: Index (Vector a) -> Traversal' (Vector a) (IxValue (Vector a)) #

Wrapped (Vector a) 

Associated Types

type Unwrapped (Vector a) :: * #

Methods

_Wrapped' :: Iso' (Vector a) (Unwrapped (Vector a)) #

(~) * t (Vector a') => Rewrapped (Vector a) t 
Eq a => SetLike (Vector a) a Source # 

Methods

conj :: a -> Vector a -> Vector a Source #

remove :: a -> Vector a -> Vector a Source #

elem :: a -> Vector a -> Bool Source #

null :: Vector a -> Bool Source #

items :: Vector a -> [a] Source #

fromItems :: [a] -> Vector a Source #

singleton :: a -> Vector a Source #

size :: Vector a -> Int Source #

ListLike (Vector a) a Source # 

Methods

intersperse :: a -> Vector a -> Vector a Source #

take :: Int -> Vector a -> Vector a Source #

takeEnd :: Int -> Vector a -> Vector a Source #

drop :: Int -> Vector a -> Vector a Source #

dropEnd :: Int -> Vector a -> Vector a Source #

slice :: Int -> Int -> Vector a -> Vector a Source #

length :: Vector a -> Int Source #

type Mutable Vector 
type Item (Vector a) 
type Item (Vector a) = a
type Index (Vector a) 
type Index (Vector a) = Int
type IxValue (Vector a) 
type IxValue (Vector a) = a
type Unwrapped (Vector a) 
type Unwrapped (Vector a) = [a]

class Hashable a where #

The class of types that can be converted to a hash value.

Minimal implementation: hashWithSalt.

Methods

hashWithSalt :: Int -> a -> Int infixl 0 #

Return a hash value for the argument, using the given salt.

The general contract of hashWithSalt is:

  • If two values are equal according to the == method, then applying the hashWithSalt method on each of the two values must produce the same integer result if the same salt is used in each case.
  • It is not required that if two values are unequal according to the == method, then applying the hashWithSalt method on each of the two values must produce distinct integer results. However, the programmer should be aware that producing distinct integer results for unequal values may improve the performance of hashing-based data structures.
  • This method can be used to compute different hash values for the same input by providing a different salt in each application of the method. This implies that any instance that defines hashWithSalt must make use of the salt in its implementation.

hash :: 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.

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 ByteString 
Hashable ByteString 
Hashable Scientific 
Hashable Text 

Methods

hashWithSalt :: Int -> Text -> Int #

hash :: Text -> Int #

Hashable Value 

Methods

hashWithSalt :: Int -> Value -> Int #

hash :: Value -> Int #

Hashable Text 

Methods

hashWithSalt :: Int -> Text -> Int #

hash :: Text -> 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 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 k, Hashable v) => Hashable (HashMap k v) 

Methods

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

hash :: HashMap k v -> Int #

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

Methods

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

hash :: Arg a b -> Int #

(Hashable v, Hashable k) => Hashable (LHashMap k v) # 

Methods

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

hash :: LHashMap 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 Lookup m k | m -> k where Source #

Things that support keyed element lookup.

Minimal complete definition

lookup

Methods

lookup :: k -> m v -> Maybe v Source #

lookupDef :: v -> k -> m v -> v Source #

Instances

Lookup [] Int Source # 

Methods

lookup :: Int -> [v] -> Maybe v Source #

lookupDef :: v -> Int -> [v] -> v Source #

Lookup Vector Int Source # 

Methods

lookup :: Int -> Vector v -> Maybe v Source #

lookupDef :: v -> Int -> Vector v -> v Source #

(Eq k, Hashable k) => Lookup (HashMap k) k Source # 

Methods

lookup :: k -> HashMap k v -> Maybe v Source #

lookupDef :: v -> k -> HashMap k v -> v Source #

(Eq k, Ord k) => Lookup (Map k) k Source # 

Methods

lookup :: k -> Map k v -> Maybe v Source #

lookupDef :: v -> k -> Map k v -> v Source #

Eq k => Lookup (AList k) k Source # 

Methods

lookup :: k -> AList k v -> Maybe v Source #

lookupDef :: v -> k -> AList k v -> v Source #

(Eq k, Hashable k) => Lookup (LHashMap k) k Source # 

Methods

lookup :: k -> LHashMap k v -> Maybe v Source #

lookupDef :: v -> k -> LHashMap k v -> v Source #

class ListLike m a | m -> a where Source #

Minimal complete definition

intersperse, take, drop, length

Methods

intersperse :: a -> m -> m Source #

take :: Int -> m -> m Source #

takeEnd :: Int -> m -> m Source #

drop :: Int -> m -> m Source #

dropEnd :: Int -> m -> m Source #

slice :: Int -> Int -> m -> m Source #

length :: m -> Int Source #

Instances

ListLike LText Char Source # 
ListLike Text Char Source # 
ListLike [a] a Source # 

Methods

intersperse :: a -> [a] -> [a] Source #

take :: Int -> [a] -> [a] Source #

takeEnd :: Int -> [a] -> [a] Source #

drop :: Int -> [a] -> [a] Source #

dropEnd :: Int -> [a] -> [a] Source #

slice :: Int -> Int -> [a] -> [a] Source #

length :: [a] -> Int Source #

ListLike (Vector a) a Source # 

Methods

intersperse :: a -> Vector a -> Vector a Source #

take :: Int -> Vector a -> Vector a Source #

takeEnd :: Int -> Vector a -> Vector a Source #

drop :: Int -> Vector a -> Vector a Source #

dropEnd :: Int -> Vector a -> Vector a Source #

slice :: Int -> Int -> Vector a -> Vector a Source #

length :: Vector a -> Int Source #

class DictLike m k where Source #

Things that behave like key-value dictionaries.

Minimal complete definition

insert, delete, update, pairs, fromPairs, singletonMap, member

Methods

insert :: k -> v -> m k v -> m k v Source #

Add or overwrite an element at a key.

delete :: k -> m k v -> m k v Source #

Delete by key

update :: k -> (v -> Maybe v) -> m k v -> m k v Source #

Modify an element at a key

pairs :: m k v -> [(k, v)] Source #

Convert to an association list (list of key/value pairs)

fromPairs :: [(k, v)] -> m k v Source #

Convert from an association list (list of key/value pairs)

keys :: m k v -> [k] Source #

Get the keys, discard the values

elems :: m k v -> [v] Source #

Get the values, discard the keys

singletonMap :: k -> v -> m k v Source #

Create a singleton dictionary (just one key-value pair)

member :: k -> m k v -> Bool Source #

Test whether the dictionary contains a given key

Instances

(Eq k, Hashable k) => DictLike HashMap k Source # 

Methods

insert :: k -> v -> HashMap k v -> HashMap k v Source #

delete :: k -> HashMap k v -> HashMap k v Source #

update :: k -> (v -> Maybe v) -> HashMap k v -> HashMap k v Source #

pairs :: HashMap k v -> [(k, v)] Source #

fromPairs :: [(k, v)] -> HashMap k v Source #

keys :: HashMap k v -> [k] Source #

elems :: HashMap k v -> [v] Source #

singletonMap :: k -> v -> HashMap k v Source #

member :: k -> HashMap k v -> Bool Source #

(Eq k, Ord k) => DictLike Map k Source # 

Methods

insert :: k -> v -> Map k v -> Map k v Source #

delete :: k -> Map k v -> Map k v Source #

update :: k -> (v -> Maybe v) -> Map k v -> Map k v Source #

pairs :: Map k v -> [(k, v)] Source #

fromPairs :: [(k, v)] -> Map k v Source #

keys :: Map k v -> [k] Source #

elems :: Map k v -> [v] Source #

singletonMap :: k -> v -> Map k v Source #

member :: k -> Map k v -> Bool Source #

Eq k => DictLike AList k Source # 

Methods

insert :: k -> v -> AList k v -> AList k v Source #

delete :: k -> AList k v -> AList k v Source #

update :: k -> (v -> Maybe v) -> AList k v -> AList k v Source #

pairs :: AList k v -> [(k, v)] Source #

fromPairs :: [(k, v)] -> AList k v Source #

keys :: AList k v -> [k] Source #

elems :: AList k v -> [v] Source #

singletonMap :: k -> v -> AList k v Source #

member :: k -> AList k v -> Bool Source #

(Eq k, Hashable k) => DictLike LHashMap k Source # 

Methods

insert :: k -> v -> LHashMap k v -> LHashMap k v Source #

delete :: k -> LHashMap k v -> LHashMap k v Source #

update :: k -> (v -> Maybe v) -> LHashMap k v -> LHashMap k v Source #

pairs :: LHashMap k v -> [(k, v)] Source #

fromPairs :: [(k, v)] -> LHashMap k v Source #

keys :: LHashMap k v -> [k] Source #

elems :: LHashMap k v -> [v] Source #

singletonMap :: k -> v -> LHashMap k v Source #

member :: k -> LHashMap k v -> Bool Source #

class SetLike m v | m -> v where Source #

Things that behave like sets.

Minimal complete definition

conj, remove, elem, items, fromItems, singleton

Methods

conj :: v -> m -> m Source #

Conjoin: add an element to a set. For ordered sets, the end at which the new element is inserted is unspecified.

remove :: v -> m -> m Source #

Remove all occurrences of the element from the set.

elem :: v -> m -> Bool Source #

Test if the element is in the set.

null :: m -> Bool Source #

Test if the set is empty.

items :: m -> [v] Source #

Convert the set to a list of elements. The ordering is unspecified.

fromItems :: [v] -> m Source #

Create a set from a list of elements. Duplicate list elements may be skipped at the implementation's discretion.

singleton :: v -> m Source #

Create a singleton (one-element) set.

size :: m -> Int Source #

Get the number of elements in the set.

Instances

Eq a => SetLike [a] a Source # 

Methods

conj :: a -> [a] -> [a] Source #

remove :: a -> [a] -> [a] Source #

elem :: a -> [a] -> Bool Source #

null :: [a] -> Bool Source #

items :: [a] -> [a] Source #

fromItems :: [a] -> [a] Source #

singleton :: a -> [a] Source #

size :: [a] -> Int Source #

(Eq v, Ord v) => SetLike (Set v) v Source # 

Methods

conj :: v -> Set v -> Set v Source #

remove :: v -> Set v -> Set v Source #

elem :: v -> Set v -> Bool Source #

null :: Set v -> Bool Source #

items :: Set v -> [v] Source #

fromItems :: [v] -> Set v Source #

singleton :: v -> Set v Source #

size :: Set v -> Int Source #

Eq a => SetLike (Vector a) a Source # 

Methods

conj :: a -> Vector a -> Vector a Source #

remove :: a -> Vector a -> Vector a Source #

elem :: a -> Vector a -> Bool Source #

null :: Vector a -> Bool Source #

items :: Vector a -> [a] Source #

fromItems :: [a] -> Vector a Source #

singleton :: a -> Vector a Source #

size :: Vector a -> Int Source #

(Eq v, Hashable v) => SetLike (HashSet v) v Source # 

Methods

conj :: v -> HashSet v -> HashSet v Source #

remove :: v -> HashSet v -> HashSet v Source #

elem :: v -> HashSet v -> Bool Source #

null :: HashSet v -> Bool Source #

items :: HashSet v -> [v] Source #

fromItems :: [v] -> HashSet v Source #

singleton :: v -> HashSet v Source #

size :: HashSet v -> Int Source #

(Eq k, Ord k) => SetLike (Map k v) (k, v) Source # 

Methods

conj :: (k, v) -> Map k v -> Map k v Source #

remove :: (k, v) -> Map k v -> Map k v Source #

elem :: (k, v) -> Map k v -> Bool Source #

null :: Map k v -> Bool Source #

items :: Map k v -> [(k, v)] Source #

fromItems :: [(k, v)] -> Map k v Source #

singleton :: (k, v) -> Map k v Source #

size :: Map k v -> Int Source #

(Eq k, Hashable k) => SetLike (LHashMap k v) (k, v) Source # 

Methods

conj :: (k, v) -> LHashMap k v -> LHashMap k v Source #

remove :: (k, v) -> LHashMap k v -> LHashMap k v Source #

elem :: (k, v) -> LHashMap k v -> Bool Source #

null :: LHashMap k v -> Bool Source #

items :: LHashMap k v -> [(k, v)] Source #

fromItems :: [(k, v)] -> LHashMap k v Source #

singleton :: (k, v) -> LHashMap k v Source #

size :: LHashMap k v -> Int Source #

(Eq k, Hashable k) => SetLike (HashMap k v) (k, v) Source # 

Methods

conj :: (k, v) -> HashMap k v -> HashMap k v Source #

remove :: (k, v) -> HashMap k v -> HashMap k v Source #

elem :: (k, v) -> HashMap k v -> Bool Source #

null :: HashMap k v -> Bool Source #

items :: HashMap k v -> [(k, v)] Source #

fromItems :: [(k, v)] -> HashMap k v Source #

singleton :: (k, v) -> HashMap k v Source #

size :: HashMap k v -> Int Source #

class Filterable m where Source #

Things that can be filtered

Minimal complete definition

filter

Methods

filter :: (v -> Bool) -> m v -> m v Source #

Filter the set to retain only the elements that match the predicate.

Instances

Filterable [] Source # 

Methods

filter :: (v -> Bool) -> [v] -> [v] Source #

Filterable Set Source # 

Methods

filter :: (v -> Bool) -> Set v -> Set v Source #

Filterable Vector Source # 

Methods

filter :: (v -> Bool) -> Vector v -> Vector v Source #

Filterable HashSet Source # 

Methods

filter :: (v -> Bool) -> HashSet v -> HashSet v Source #

Filterable (Map k) Source # 

Methods

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

Filterable (LHashMap k) Source # 

Methods

filter :: (v -> Bool) -> LHashMap k v -> LHashMap k v Source #

Filterable (HashMap k) Source # 

Methods

filter :: (v -> Bool) -> HashMap k v -> HashMap k v Source #

cull :: Filterable m => (v -> Bool) -> m v -> m v Source #

startsWith :: (Eq a, ListLike a e) => a -> a -> Bool Source #

endsWith :: (Eq a, ListLike a e) => a -> a -> Bool Source #

intercalate :: (Monoid a, Foldable m, ListLike (m a) a) => a -> m a -> a Source #

JSON

class ToJSON a where #

A type that can be converted to JSON.

An example type and instance:

-- Allow ourselves to write Text literals.
{-# LANGUAGE OverloadedStrings #-}

data Coord = Coord { x :: Double, y :: Double }

instance ToJSON Coord where
  toJSON (Coord x y) = object ["x" .= x, "y" .= y]

  toEncoding (Coord x y) = pairs ("x" .= x <> "y" .= y)

Instead of manually writing your ToJSON instance, there are two options to do it automatically:

  • Data.Aeson.TH provides Template Haskell functions which will derive an instance at compile time. The generated instance is optimized for your type so will probably be more efficient than the following two options:
  • The compiler can provide a default generic implementation for toJSON.

To use the second, simply add a deriving Generic clause to your datatype and declare a ToJSON instance for your datatype without giving definitions for toJSON or toEncoding.

For example, the previous example can be simplified to a more minimal instance:

{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics

data Coord = Coord { x :: Double, y :: Double } deriving Generic

instance ToJSON Coord where
    toEncoding = genericToEncoding defaultOptions

Why do we provide an implementation for toEncoding here? The toEncoding function is a relatively new addition to this class. To allow users of older versions of this library to upgrade without having to edit all of their instances or encounter surprising incompatibilities, the default implementation of toEncoding uses toJSON. This produces correct results, but since it performs an intermediate conversion to a Value, it will be less efficient than directly emitting an Encoding. Our one-liner definition of toEncoding above bypasses the intermediate Value.

If DefaultSignatures doesn't give exactly the results you want, you can customize the generic encoding with only a tiny amount of effort, using genericToJSON and genericToEncoding with your preferred Options:

instance ToJSON Coord where
    toJSON     = genericToJSON defaultOptions
    toEncoding = genericToEncoding defaultOptions

Methods

toJSON :: a -> Value #

Convert a Haskell value to a JSON-friendly intermediate type.

toEncoding :: a -> Encoding #

Encode a Haskell value as JSON.

The default implementation of this method creates an intermediate Value using toJSON. This provides source-level compatibility for people upgrading from older versions of this library, but obviously offers no performance advantage.

To benefit from direct encoding, you must provide an implementation for this method. The easiest way to do so is by having your types implement Generic using the DeriveGeneric extension, and then have GHC generate a method body as follows.

instance ToJSON Coord where
    toEncoding = genericToEncoding defaultOptions

toJSONList :: [a] -> Value #

toEncodingList :: [a] -> Encoding #

Instances

ToJSON Bool 
ToJSON Char 
ToJSON Double 
ToJSON Float 
ToJSON Int 
ToJSON Int8 
ToJSON Int16 
ToJSON Int32 
ToJSON Int64 
ToJSON Integer 
ToJSON Ordering 
ToJSON Word 
ToJSON Word8 
ToJSON Word16 
ToJSON Word32 
ToJSON Word64 
ToJSON () 

Methods

toJSON :: () -> Value #

toEncoding :: () -> Encoding #

toJSONList :: [()] -> Value #

toEncodingList :: [()] -> Encoding #

ToJSON Scientific 
ToJSON Number 
ToJSON Text 
ToJSON UTCTime 
ToJSON Value 
ToJSON DotNetTime 
ToJSON Text 
ToJSON Natural 
ToJSON Version 
ToJSON IntSet 
ToJSON LocalTime 
ToJSON ZonedTime 
ToJSON TimeOfDay 
ToJSON NominalDiffTime 
ToJSON Day 
ToJSON a => ToJSON [a] 

Methods

toJSON :: [a] -> Value #

toEncoding :: [a] -> Encoding #

toJSONList :: [[a]] -> Value #

toEncodingList :: [[a]] -> Encoding #

ToJSON a => ToJSON (Maybe a) 
(ToJSON a, Integral a) => ToJSON (Ratio a) 
ToJSON a => ToJSON (Identity a) 
ToJSON a => ToJSON (Min a) 

Methods

toJSON :: Min a -> Value #

toEncoding :: Min a -> Encoding #

toJSONList :: [Min a] -> Value #

toEncodingList :: [Min a] -> Encoding #

ToJSON a => ToJSON (Max a) 

Methods

toJSON :: Max a -> Value #

toEncoding :: Max a -> Encoding #

toJSONList :: [Max a] -> Value #

toEncodingList :: [Max a] -> Encoding #

ToJSON a => ToJSON (First a) 
ToJSON a => ToJSON (Last a) 
ToJSON a => ToJSON (WrappedMonoid a) 
ToJSON a => ToJSON (Option a) 
ToJSON a => ToJSON (NonEmpty a) 
HasResolution a => ToJSON (Fixed a) 
ToJSON a => ToJSON (Dual a) 
ToJSON a => ToJSON (First a) 
ToJSON a => ToJSON (Last a) 
ToJSON a => ToJSON (IntMap a) 
ToJSON v => ToJSON (Tree v) 
ToJSON a => ToJSON (Seq a) 

Methods

toJSON :: Seq a -> Value #

toEncoding :: Seq a -> Encoding #

toJSONList :: [Seq a] -> Value #

toEncodingList :: [Seq a] -> Encoding #

ToJSON a => ToJSON (Set a) 

Methods

toJSON :: Set a -> Value #

toEncoding :: Set a -> Encoding #

toJSONList :: [Set a] -> Value #

toEncodingList :: [Set a] -> Encoding #

ToJSON a => ToJSON (DList a) 
ToJSON a => ToJSON (Vector a) 
(Prim a, ToJSON a) => ToJSON (Vector a) 
(Storable a, ToJSON a) => ToJSON (Vector a) 
(Vector Vector a, ToJSON a) => ToJSON (Vector a) 
ToJSON a => ToJSON (HashSet a) 
(ToJSON a, ToJSON b) => ToJSON (Either a b) 

Methods

toJSON :: Either a b -> Value #

toEncoding :: Either a b -> Encoding #

toJSONList :: [Either a b] -> Value #

toEncodingList :: [Either a b] -> Encoding #

(ToJSON a, ToJSON b) => ToJSON (a, b) 

Methods

toJSON :: (a, b) -> Value #

toEncoding :: (a, b) -> Encoding #

toJSONList :: [(a, b)] -> Value #

toEncodingList :: [(a, b)] -> Encoding #

(ToJSON v, ToJSONKey k) => ToJSON (HashMap k v) 
(ToJSON v, ToJSONKey k) => ToJSON (Map k v) 

Methods

toJSON :: Map k v -> Value #

toEncoding :: Map k v -> Encoding #

toJSONList :: [Map k v] -> Value #

toEncodingList :: [Map k v] -> Encoding #

ToJSON (Proxy k a) 

Methods

toJSON :: Proxy k a -> Value #

toEncoding :: Proxy k a -> Encoding #

toJSONList :: [Proxy k a] -> Value #

toEncodingList :: [Proxy k a] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c) => ToJSON (a, b, c) 

Methods

toJSON :: (a, b, c) -> Value #

toEncoding :: (a, b, c) -> Encoding #

toJSONList :: [(a, b, c)] -> Value #

toEncodingList :: [(a, b, c)] -> Encoding #

ToJSON a => ToJSON (Const k a b) 

Methods

toJSON :: Const k a b -> Value #

toEncoding :: Const k a b -> Encoding #

toJSONList :: [Const k a b] -> Value #

toEncodingList :: [Const k a b] -> Encoding #

ToJSON b => ToJSON (Tagged k a b) 

Methods

toJSON :: Tagged k a b -> Value #

toEncoding :: Tagged k a b -> Encoding #

toJSONList :: [Tagged k a b] -> Value #

toEncodingList :: [Tagged k a b] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d) => ToJSON (a, b, c, d) 

Methods

toJSON :: (a, b, c, d) -> Value #

toEncoding :: (a, b, c, d) -> Encoding #

toJSONList :: [(a, b, c, d)] -> Value #

toEncodingList :: [(a, b, c, d)] -> Encoding #

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Sum * f g a) 

Methods

toJSON :: Sum * f g a -> Value #

toEncoding :: Sum * f g a -> Encoding #

toJSONList :: [Sum * f g a] -> Value #

toEncodingList :: [Sum * f g a] -> Encoding #

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Product * f g a) 

Methods

toJSON :: Product * f g a -> Value #

toEncoding :: Product * f g a -> Encoding #

toJSONList :: [Product * f g a] -> Value #

toEncodingList :: [Product * f g a] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e) => ToJSON (a, b, c, d, e) 

Methods

toJSON :: (a, b, c, d, e) -> Value #

toEncoding :: (a, b, c, d, e) -> Encoding #

toJSONList :: [(a, b, c, d, e)] -> Value #

toEncodingList :: [(a, b, c, d, e)] -> Encoding #

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Compose * * f g a) 

Methods

toJSON :: Compose * * f g a -> Value #

toEncoding :: Compose * * f g a -> Encoding #

toJSONList :: [Compose * * f g a] -> Value #

toEncodingList :: [Compose * * f g a] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f) => ToJSON (a, b, c, d, e, f) 

Methods

toJSON :: (a, b, c, d, e, f) -> Value #

toEncoding :: (a, b, c, d, e, f) -> Encoding #

toJSONList :: [(a, b, c, d, e, f)] -> Value #

toEncodingList :: [(a, b, c, d, e, f)] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g) => ToJSON (a, b, c, d, e, f, g) 

Methods

toJSON :: (a, b, c, d, e, f, g) -> Value #

toEncoding :: (a, b, c, d, e, f, g) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g)] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h) => ToJSON (a, b, c, d, e, f, g, h) 

Methods

toJSON :: (a, b, c, d, e, f, g, h) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h)] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i) => ToJSON (a, b, c, d, e, f, g, h, i) 

Methods

toJSON :: (a, b, c, d, e, f, g, h, i) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i)] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j) => ToJSON (a, b, c, d, e, f, g, h, i, j) 

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j)] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k) => ToJSON (a, b, c, d, e, f, g, h, i, j, k) 

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l) 

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m) 

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n, ToJSON o) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> Encoding #

class FromJSON a where #

A type that can be converted from JSON, with the possibility of failure.

In many cases, you can get the compiler to generate parsing code for you (see below). To begin, let's cover writing an instance by hand.

There are various reasons a conversion could fail. For example, an Object could be missing a required key, an Array could be of the wrong size, or a value could be of an incompatible type.

The basic ways to signal a failed conversion are as follows:

  • empty and mzero work, but are terse and uninformative
  • fail yields a custom error message
  • typeMismatch produces an informative message for cases when the value encountered is not of the expected type

An example type and instance:

-- Allow ourselves to write Text literals.
{-# LANGUAGE OverloadedStrings #-}

data Coord = Coord { x :: Double, y :: Double }

instance FromJSON Coord where
  parseJSON (Object v) = Coord    <$>
                         v .: "x" <*>
                         v .: "y"

  -- We do not expect a non-Object value here.
  -- We could use mzero to fail, but typeMismatch
  -- gives a much more informative error message.
  parseJSON invalid    = typeMismatch "Coord" invalid

Instead of manually writing your FromJSON instance, there are two options to do it automatically:

  • Data.Aeson.TH provides Template Haskell functions which will derive an instance at compile time. The generated instance is optimized for your type so will probably be more efficient than the following two options:
  • The compiler can provide a default generic implementation for parseJSON.

To use the second, simply add a deriving Generic clause to your datatype and declare a FromJSON instance for your datatype without giving a definition for parseJSON.

For example, the previous example can be simplified to just:

{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics

data Coord = Coord { x :: Double, y :: Double } deriving Generic

instance FromJSON Coord

If DefaultSignatures doesn't give exactly the results you want, you can customize the generic decoding with only a tiny amount of effort, using genericParseJSON with your preferred Options:

instance FromJSON Coord where
    parseJSON = genericParseJSON defaultOptions

Methods

parseJSON :: Value -> Parser a #

parseJSONList :: Value -> Parser [a] #

Instances

FromJSON Bool 
FromJSON Char 
FromJSON Double 
FromJSON Float 
FromJSON Int 
FromJSON Int8 
FromJSON Int16 
FromJSON Int32 
FromJSON Int64 
FromJSON Integer

WARNING: Only parse Integers from trusted input since an attacker could easily fill up the memory of the target system by specifying a scientific number with a big exponent like 1e1000000000.

FromJSON Ordering 
FromJSON Word 
FromJSON Word8 
FromJSON Word16 
FromJSON Word32 
FromJSON Word64 
FromJSON () 

Methods

parseJSON :: Value -> Parser () #

parseJSONList :: Value -> Parser [()] #

FromJSON Scientific 
FromJSON Number 
FromJSON Text 
FromJSON UTCTime 
FromJSON Value 
FromJSON DotNetTime 
FromJSON Text 
FromJSON Natural 
FromJSON Version 
FromJSON IntSet 
FromJSON LocalTime 
FromJSON ZonedTime 
FromJSON TimeOfDay 
FromJSON NominalDiffTime

WARNING: Only parse lengths of time from trusted input since an attacker could easily fill up the memory of the target system by specifying a scientific number with a big exponent like 1e1000000000.

FromJSON Day 
FromJSON a => FromJSON [a] 

Methods

parseJSON :: Value -> Parser [a] #

parseJSONList :: Value -> Parser [[a]] #

FromJSON a => FromJSON (Maybe a) 
(FromJSON a, Integral a) => FromJSON (Ratio a) 
FromJSON a => FromJSON (Identity a) 
FromJSON a => FromJSON (Min a) 

Methods

parseJSON :: Value -> Parser (Min a) #

parseJSONList :: Value -> Parser [Min a] #

FromJSON a => FromJSON (Max a) 

Methods

parseJSON :: Value -> Parser (Max a) #

parseJSONList :: Value -> Parser [Max a] #

FromJSON a => FromJSON (First a) 
FromJSON a => FromJSON (Last a) 
FromJSON a => FromJSON (WrappedMonoid a) 
FromJSON a => FromJSON (Option a) 
FromJSON a => FromJSON (NonEmpty a) 
HasResolution a => FromJSON (Fixed a)

WARNING: Only parse fixed-precision numbers from trusted input since an attacker could easily fill up the memory of the target system by specifying a scientific number with a big exponent like 1e1000000000.

FromJSON a => FromJSON (Dual a) 
FromJSON a => FromJSON (First a) 
FromJSON a => FromJSON (Last a) 
FromJSON a => FromJSON (IntMap a) 
FromJSON v => FromJSON (Tree v) 
FromJSON a => FromJSON (Seq a) 

Methods

parseJSON :: Value -> Parser (Seq a) #

parseJSONList :: Value -> Parser [Seq a] #

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

Methods

parseJSON :: Value -> Parser (Set a) #

parseJSONList :: Value -> Parser [Set a] #

FromJSON a => FromJSON (DList a) 
FromJSON a => FromJSON (Vector a) 
(Prim a, FromJSON a) => FromJSON (Vector a) 
(Storable a, FromJSON a) => FromJSON (Vector a) 
(Vector Vector a, FromJSON a) => FromJSON (Vector a) 
(Eq a, Hashable a, FromJSON a) => FromJSON (HashSet a) 
(FromJSON a, FromJSON b) => FromJSON (Either a b) 

Methods

parseJSON :: Value -> Parser (Either a b) #

parseJSONList :: Value -> Parser [Either a b] #

(FromJSON a, FromJSON b) => FromJSON (a, b) 

Methods

parseJSON :: Value -> Parser (a, b) #

parseJSONList :: Value -> Parser [(a, b)] #

(FromJSON v, FromJSONKey k, Eq k, Hashable k) => FromJSON (HashMap k v) 
(FromJSONKey k, Ord k, FromJSON v) => FromJSON (Map k v) 

Methods

parseJSON :: Value -> Parser (Map k v) #

parseJSONList :: Value -> Parser [Map k v] #

FromJSON (Proxy k a) 

Methods

parseJSON :: Value -> Parser (Proxy k a) #

parseJSONList :: Value -> Parser [Proxy k a] #

(FromJSON a, FromJSON b, FromJSON c) => FromJSON (a, b, c) 

Methods

parseJSON :: Value -> Parser (a, b, c) #

parseJSONList :: Value -> Parser [(a, b, c)] #

FromJSON a => FromJSON (Const k a b) 

Methods

parseJSON :: Value -> Parser (Const k a b) #

parseJSONList :: Value -> Parser [Const k a b] #

FromJSON b => FromJSON (Tagged k a b) 

Methods

parseJSON :: Value -> Parser (Tagged k a b) #

parseJSONList :: Value -> Parser [Tagged k a b] #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSON (a, b, c, d) 

Methods

parseJSON :: Value -> Parser (a, b, c, d) #

parseJSONList :: Value -> Parser [(a, b, c, d)] #

(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Sum * f g a) 

Methods

parseJSON :: Value -> Parser (Sum * f g a) #

parseJSONList :: Value -> Parser [Sum * f g a] #

(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Product * f g a) 

Methods

parseJSON :: Value -> Parser (Product * f g a) #

parseJSONList :: Value -> Parser [Product * f g a] #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e) => FromJSON (a, b, c, d, e) 

Methods

parseJSON :: Value -> Parser (a, b, c, d, e) #

parseJSONList :: Value -> Parser [(a, b, c, d, e)] #

(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Compose * * f g a) 

Methods

parseJSON :: Value -> Parser (Compose * * f g a) #

parseJSONList :: Value -> Parser [Compose * * f g a] #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f) => FromJSON (a, b, c, d, e, f) 

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f)] #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g) => FromJSON (a, b, c, d, e, f, g) 

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g)] #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h) => FromJSON (a, b, c, d, e, f, g, h) 

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h)] #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i) => FromJSON (a, b, c, d, e, f, g, h, i) 

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i)] #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j) => FromJSON (a, b, c, d, e, f, g, h, i, j) 

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j)] #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k) => FromJSON (a, b, c, d, e, f, g, h, i, j, k) 

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k)] #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l) 

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l)] #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m) 

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, m)] #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, n) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n, FromJSON o) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] #

data Value :: * #

A JSON value represented as a Haskell value.

Instances

Eq Value 

Methods

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

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

Data Value 

Methods

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

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

toConstr :: Value -> Constr #

dataTypeOf :: Value -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Value 
Show Value 

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

IsString Value 

Methods

fromString :: String -> Value #

Lift Value 

Methods

lift :: Value -> Q Exp #

Hashable Value 

Methods

hashWithSalt :: Int -> Value -> Int #

hash :: Value -> Int #

ToJSON Value 
KeyValue Pair 

Methods

(.=) :: ToJSON v => Text -> v -> Pair #

FromJSON Value 
NFData Value 

Methods

rnf :: Value -> () #

object :: [Pair] -> Value #

Create a Value from a list of name/value Pairs. If duplicate keys arise, earlier keys and their associated values win.

deriveJSON #

Arguments

:: Options

Encoding options.

-> Name

Name of the type for which to generate ToJSON and FromJSON instances.

-> Q [Dec] 

Generates both ToJSON and FromJSON instance declarations for the given data type or data family instance constructor.

This is a convienience function which is equivalent to calling both deriveToJSON and deriveFromJSON.

(~>) :: ToJSON a => Text -> a -> (Text, Value) Source #

Base-64

Concurrency And Exception Handling

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.

forkIO :: IO () -> IO ThreadId #

Creates a new thread to run the IO computation passed as the first argument, and returns the ThreadId of the newly created thread.

The new thread will be a lightweight, unbound thread. Foreign calls made by this thread are not guaranteed to be made by any particular OS thread; if you need foreign calls to be made by a particular OS thread, then use forkOS instead.

The new thread inherits the masked state of the parent (see mask).

The newly created thread has an exception handler that discards the exceptions BlockedIndefinitelyOnMVar, BlockedIndefinitelyOnSTM, and ThreadKilled, and passes all other exceptions to the uncaught exception handler.

bracket #

Arguments

:: IO a

computation to run first ("acquire resource")

-> (a -> IO b)

computation to run last ("release resource")

-> (a -> IO c)

computation to run in-between

-> IO c 

When you want to acquire a resource, do some work with it, and then release the resource, it is a good idea to use bracket, because bracket will install the necessary exception handler to release the resource in the event that an exception is raised during the computation. If an exception is raised, then bracket will re-raise the exception (after performing the release).

A common example is opening a file:

bracket
  (openFile "filename" ReadMode)
  (hClose)
  (\fileHandle -> do { ... })

The arguments to bracket are in this order so that we can partially apply it, e.g.:

withFile name mode = bracket (openFile name mode) hClose

bracket_ :: IO a -> IO b -> IO c -> IO c #

A variant of bracket where the return value from the first computation is not required.

throw :: Exception e => e -> a #

Throw an exception. Exceptions may be thrown from purely functional code, but may only be caught within the IO monad.

catch #

Arguments

:: Exception e 
=> IO a

The computation to run

-> (e -> IO a)

Handler to invoke if an exception is raised

-> IO a 

This is the simplest of the exception-catching functions. It takes a single argument, runs it, and if an exception is raised the "handler" is executed, with the value of the exception passed as an argument. Otherwise, the result is returned as normal. For example:

  catch (readFile f)
        (\e -> do let err = show (e :: IOException)
                  hPutStr stderr ("Warning: Couldn't open " ++ f ++ ": " ++ err)
                  return "")

Note that we have to give a type signature to e, or the program will not typecheck as the type is ambiguous. While it is possible to catch exceptions of any type, see the section "Catching all exceptions" (in Control.Exception) for an explanation of the problems with doing so.

For catching exceptions in pure (non-IO) expressions, see the function evaluate.

Note that due to Haskell's unspecified evaluation order, an expression may throw one of several possible exceptions: consider the expression (error "urk") + (1 `div` 0). Does the expression throw ErrorCall "urk", or DivideByZero?

The answer is "it might throw either"; the choice is non-deterministic. If you are catching any type of exception then you might catch either. If you are calling catch with type IO Int -> (ArithException -> IO Int) -> IO Int then the handler may get run with DivideByZero as an argument, or an ErrorCall "urk" exception may be propogated further up. If you call it again, you might get a the opposite behaviour. This is ok, because catch is an IO computation.

catches :: IO a -> [Handler a] -> IO a #

Sometimes you want to catch two different sorts of exception. You could do something like

f = expr `catch` \ (ex :: ArithException) -> handleArith ex
         `catch` \ (ex :: IOException)    -> handleIO    ex

However, there are a couple of problems with this approach. The first is that having two exception handlers is inefficient. However, the more serious issue is that the second exception handler will catch exceptions in the first, e.g. in the example above, if handleArith throws an IOException then the second exception handler will catch it.

Instead, we provide a function catches, which would be used thus:

f = expr `catches` [Handler (\ (ex :: ArithException) -> handleArith ex),
                    Handler (\ (ex :: IOException)    -> handleIO    ex)]

Generics

class Generic a #

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

Minimal complete definition

from, to

Instances

Generic Bool 

Associated Types

type Rep Bool :: * -> * #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Generic Ordering 

Associated Types

type Rep Ordering :: * -> * #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Generic Exp 

Associated Types

type Rep Exp :: * -> * #

Methods

from :: Exp -> Rep Exp x #

to :: Rep Exp x -> Exp #

Generic Match 

Associated Types

type Rep Match :: * -> * #

Methods

from :: Match -> Rep Match x #

to :: Rep Match x -> Match #

Generic Clause 

Associated Types

type Rep Clause :: * -> * #

Methods

from :: Clause -> Rep Clause x #

to :: Rep Clause x -> Clause #

Generic Pat 

Associated Types

type Rep Pat :: * -> * #

Methods

from :: Pat -> Rep Pat x #

to :: Rep Pat x -> Pat #

Generic Type 

Associated Types

type Rep Type :: * -> * #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

Generic Dec 

Associated Types

type Rep Dec :: * -> * #

Methods

from :: Dec -> Rep Dec x #

to :: Rep Dec x -> Dec #

Generic Name 

Associated Types

type Rep Name :: * -> * #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

Generic FunDep 

Associated Types

type Rep FunDep :: * -> * #

Methods

from :: FunDep -> Rep FunDep x #

to :: Rep FunDep x -> FunDep #

Generic TyVarBndr 

Associated Types

type Rep TyVarBndr :: * -> * #

Generic InjectivityAnn 

Associated Types

type Rep InjectivityAnn :: * -> * #

Generic Overlap 

Associated Types

type Rep Overlap :: * -> * #

Methods

from :: Overlap -> Rep Overlap x #

to :: Rep Overlap x -> Overlap #

Generic () 

Associated Types

type Rep () :: * -> * #

Methods

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

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

Generic Con 

Associated Types

type Rep Con :: * -> * #

Methods

from :: Con -> Rep Con x #

to :: Rep Con x -> Con #

Generic Void 

Associated Types

type Rep Void :: * -> * #

Methods

from :: Void -> Rep Void x #

to :: Rep Void x -> Void #

Generic Version 

Associated Types

type Rep Version :: * -> * #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Generic ExitCode 

Associated Types

type Rep ExitCode :: * -> * #

Methods

from :: ExitCode -> Rep ExitCode x #

to :: Rep ExitCode x -> ExitCode #

Generic All 

Associated Types

type Rep All :: * -> * #

Methods

from :: All -> Rep All x #

to :: Rep All x -> All #

Generic Any 

Associated Types

type Rep Any :: * -> * #

Methods

from :: Any -> Rep Any x #

to :: Rep Any x -> Any #

Generic Fixity 

Associated Types

type Rep Fixity :: * -> * #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic Associativity 

Associated Types

type Rep Associativity :: * -> * #

Generic SourceUnpackedness 
Generic SourceStrictness 
Generic DecidedStrictness 
Generic ModName 

Associated Types

type Rep ModName :: * -> * #

Methods

from :: ModName -> Rep ModName x #

to :: Rep ModName x -> ModName #

Generic PkgName 

Associated Types

type Rep PkgName :: * -> * #

Methods

from :: PkgName -> Rep PkgName x #

to :: Rep PkgName x -> PkgName #

Generic Module 

Associated Types

type Rep Module :: * -> * #

Methods

from :: Module -> Rep Module x #

to :: Rep Module x -> Module #

Generic OccName 

Associated Types

type Rep OccName :: * -> * #

Methods

from :: OccName -> Rep OccName x #

to :: Rep OccName x -> OccName #

Generic NameFlavour 

Associated Types

type Rep NameFlavour :: * -> * #

Generic NameSpace 

Associated Types

type Rep NameSpace :: * -> * #

Generic Loc 

Associated Types

type Rep Loc :: * -> * #

Methods

from :: Loc -> Rep Loc x #

to :: Rep Loc x -> Loc #

Generic Info 

Associated Types

type Rep Info :: * -> * #

Methods

from :: Info -> Rep Info x #

to :: Rep Info x -> Info #

Generic ModuleInfo 

Associated Types

type Rep ModuleInfo :: * -> * #

Generic Fixity 

Associated Types

type Rep Fixity :: * -> * #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic FixityDirection 
Generic Lit 

Associated Types

type Rep Lit :: * -> * #

Methods

from :: Lit -> Rep Lit x #

to :: Rep Lit x -> Lit #

Generic Body 

Associated Types

type Rep Body :: * -> * #

Methods

from :: Body -> Rep Body x #

to :: Rep Body x -> Body #

Generic Guard 

Associated Types

type Rep Guard :: * -> * #

Methods

from :: Guard -> Rep Guard x #

to :: Rep Guard x -> Guard #

Generic Stmt 

Associated Types

type Rep Stmt :: * -> * #

Methods

from :: Stmt -> Rep Stmt x #

to :: Rep Stmt x -> Stmt #

Generic Range 

Associated Types

type Rep Range :: * -> * #

Methods

from :: Range -> Rep Range x #

to :: Rep Range x -> Range #

Generic TypeFamilyHead 

Associated Types

type Rep TypeFamilyHead :: * -> * #

Generic TySynEqn 

Associated Types

type Rep TySynEqn :: * -> * #

Methods

from :: TySynEqn -> Rep TySynEqn x #

to :: Rep TySynEqn x -> TySynEqn #

Generic FamFlavour 

Associated Types

type Rep FamFlavour :: * -> * #

Generic Foreign 

Associated Types

type Rep Foreign :: * -> * #

Methods

from :: Foreign -> Rep Foreign x #

to :: Rep Foreign x -> Foreign #

Generic Callconv 

Associated Types

type Rep Callconv :: * -> * #

Methods

from :: Callconv -> Rep Callconv x #

to :: Rep Callconv x -> Callconv #

Generic Safety 

Associated Types

type Rep Safety :: * -> * #

Methods

from :: Safety -> Rep Safety x #

to :: Rep Safety x -> Safety #

Generic Pragma 

Associated Types

type Rep Pragma :: * -> * #

Methods

from :: Pragma -> Rep Pragma x #

to :: Rep Pragma x -> Pragma #

Generic Inline 

Associated Types

type Rep Inline :: * -> * #

Methods

from :: Inline -> Rep Inline x #

to :: Rep Inline x -> Inline #

Generic RuleMatch 

Associated Types

type Rep RuleMatch :: * -> * #

Generic Phases 

Associated Types

type Rep Phases :: * -> * #

Methods

from :: Phases -> Rep Phases x #

to :: Rep Phases x -> Phases #

Generic RuleBndr 

Associated Types

type Rep RuleBndr :: * -> * #

Methods

from :: RuleBndr -> Rep RuleBndr x #

to :: Rep RuleBndr x -> RuleBndr #

Generic AnnTarget 

Associated Types

type Rep AnnTarget :: * -> * #

Generic SourceUnpackedness 
Generic SourceStrictness 
Generic DecidedStrictness 
Generic Bang 

Associated Types

type Rep Bang :: * -> * #

Methods

from :: Bang -> Rep Bang x #

to :: Rep Bang x -> Bang #

Generic FamilyResultSig 
Generic TyLit 

Associated Types

type Rep TyLit :: * -> * #

Methods

from :: TyLit -> Rep TyLit x #

to :: Rep TyLit x -> TyLit #

Generic Role 

Associated Types

type Rep Role :: * -> * #

Methods

from :: Role -> Rep Role x #

to :: Rep Role x -> Role #

Generic AnnLookup 

Associated Types

type Rep AnnLookup :: * -> * #

Generic [a] 

Associated Types

type Rep [a] :: * -> * #

Methods

from :: [a] -> Rep [a] x #

to :: Rep [a] x -> [a] #

Generic (Maybe a) 

Associated Types

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

Methods

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

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

Generic (V1 p) 

Associated Types

type Rep (V1 p) :: * -> * #

Methods

from :: V1 p -> Rep (V1 p) x #

to :: Rep (V1 p) x -> V1 p #

Generic (U1 p) 

Associated Types

type Rep (U1 p) :: * -> * #

Methods

from :: U1 p -> Rep (U1 p) x #

to :: Rep (U1 p) x -> U1 p #

Generic (Par1 p) 

Associated Types

type Rep (Par1 p) :: * -> * #

Methods

from :: Par1 p -> Rep (Par1 p) x #

to :: Rep (Par1 p) x -> Par1 p #

Generic (Identity a) 

Associated Types

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

Methods

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

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

Generic (Min a) 

Associated Types

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

Methods

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

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

Generic (Max a) 

Associated Types

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

Methods

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

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

Generic (First a) 

Associated Types

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

Methods

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

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

Generic (Last a) 

Associated Types

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

Methods

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

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

Generic (WrappedMonoid m) 

Associated Types

type Rep (WrappedMonoid m) :: * -> * #

Generic (Option a) 

Associated Types

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

Methods

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

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

Generic (NonEmpty a) 

Associated Types

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

Methods

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

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

Generic (Complex a) 

Associated Types

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

Methods

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

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

Generic (ZipList a) 

Associated Types

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

Methods

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

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

Generic (Dual a) 

Associated Types

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

Methods

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

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

Generic (Endo a) 

Associated Types

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

Methods

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

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

Generic (Sum a) 

Associated Types

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

Methods

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

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

Generic (Product a) 

Associated Types

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

Methods

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

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

Generic (First a) 

Associated Types

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

Methods

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

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

Generic (Last a) 

Associated Types

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

Methods

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

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

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 #

Generic (Rec1 f p) 

Associated Types

type Rep (Rec1 f p) :: * -> * #

Methods

from :: Rec1 f p -> Rep (Rec1 f p) x #

to :: Rep (Rec1 f p) x -> Rec1 f p #

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 #

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 #

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 #

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 #

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 #

Generic (URec (Ptr ()) p) 

Associated Types

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

Methods

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

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

Generic (a, b) 

Associated Types

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

Methods

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

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

Generic (Arg a b) 

Associated Types

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

Methods

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

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

Generic (WrappedMonad m a) 

Associated Types

type Rep (WrappedMonad m a) :: * -> * #

Methods

from :: WrappedMonad m a -> Rep (WrappedMonad m a) x #

to :: Rep (WrappedMonad m a) x -> WrappedMonad m a #

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 #

Generic (AList k v) # 

Associated Types

type Rep (AList k v) :: * -> * #

Methods

from :: AList k v -> Rep (AList k v) x #

to :: Rep (AList k v) x -> AList k v #

Generic (LHashMap k v) # 

Associated Types

type Rep (LHashMap k v) :: * -> * #

Methods

from :: LHashMap k v -> Rep (LHashMap k v) x #

to :: Rep (LHashMap k v) x -> LHashMap k v #

Generic (K1 i c p) 

Associated Types

type Rep (K1 i c p) :: * -> * #

Methods

from :: K1 i c p -> Rep (K1 i c p) x #

to :: Rep (K1 i c p) x -> K1 i c p #

Generic ((:+:) f g p) 

Associated Types

type Rep ((:+:) f g p) :: * -> * #

Methods

from :: (f :+: g) p -> Rep ((f :+: g) p) x #

to :: Rep ((f :+: g) p) x -> (f :+: g) p #

Generic ((:*:) f g p) 

Associated Types

type Rep ((:*:) f g p) :: * -> * #

Methods

from :: (f :*: g) p -> Rep ((f :*: g) p) x #

to :: Rep ((f :*: g) p) x -> (f :*: g) p #

Generic ((:.:) f g p) 

Associated Types

type Rep ((:.:) f g p) :: * -> * #

Methods

from :: (f :.: g) p -> Rep ((f :.: g) p) x #

to :: Rep ((f :.: g) p) x -> (f :.: g) p #

Generic (a, b, c) 

Associated Types

type Rep (a, b, c) :: * -> * #

Methods

from :: (a, b, c) -> Rep (a, b, c) x #

to :: Rep (a, b, c) x -> (a, b, c) #

Generic (WrappedArrow a b c) 

Associated Types

type Rep (WrappedArrow a b c) :: * -> * #

Methods

from :: WrappedArrow a b c -> Rep (WrappedArrow a b c) x #

to :: Rep (WrappedArrow a b c) x -> WrappedArrow a b c #

Generic (Const k a b) 

Associated Types

type Rep (Const k a b) :: * -> * #

Methods

from :: Const k a b -> Rep (Const k a b) x #

to :: Rep (Const k a b) x -> Const k a b #

Generic (Alt k f a) 

Associated Types

type Rep (Alt k f a) :: * -> * #

Methods

from :: Alt k f a -> Rep (Alt k f a) x #

to :: Rep (Alt k f a) x -> Alt k f a #

Generic (Join k p a) 

Associated Types

type Rep (Join k p a) :: * -> * #

Methods

from :: Join k p a -> Rep (Join k p a) x #

to :: Rep (Join k p a) x -> Join k p a #

Generic (Tagged k s b) 

Associated Types

type Rep (Tagged k s b) :: * -> * #

Methods

from :: Tagged k s b -> Rep (Tagged k s b) x #

to :: Rep (Tagged k s b) x -> Tagged k s b #

Generic (M1 i c f p) 

Associated Types

type Rep (M1 i c f p) :: * -> * #

Methods

from :: M1 i c f p -> Rep (M1 i c f p) x #

to :: Rep (M1 i c f p) x -> M1 i c f p #

Generic (a, b, c, d) 

Associated Types

type Rep (a, b, c, d) :: * -> * #

Methods

from :: (a, b, c, d) -> Rep (a, b, c, d) x #

to :: Rep (a, b, c, d) x -> (a, b, c, d) #

Generic (Product k f g a) 

Associated Types

type Rep (Product k f g a) :: * -> * #

Methods

from :: Product k f g a -> Rep (Product k f g a) x #

to :: Rep (Product k f g a) x -> Product k f g a #

Generic (a, b, c, d, e) 

Associated Types

type Rep (a, b, c, d, e) :: * -> * #

Methods

from :: (a, b, c, d, e) -> Rep (a, b, c, d, e) x #

to :: Rep (a, b, c, d, e) x -> (a, b, c, d, e) #

Generic (Compose k1 k f g a) 

Associated Types

type Rep (Compose k1 k f g a) :: * -> * #

Methods

from :: Compose k1 k f g a -> Rep (Compose k1 k f g a) x #

to :: Rep (Compose k1 k f g a) x -> Compose k1 k f g a #

Generic (WrappedBifunctor k1 k p a b) 

Associated Types

type Rep (WrappedBifunctor k1 k p a b) :: * -> * #

Methods

from :: WrappedBifunctor k1 k p a b -> Rep (WrappedBifunctor k1 k p a b) x #

to :: Rep (WrappedBifunctor k1 k p a b) x -> WrappedBifunctor k1 k p a b #

Generic (Joker k1 k g a b) 

Associated Types

type Rep (Joker k1 k g a b) :: * -> * #

Methods

from :: Joker k1 k g a b -> Rep (Joker k1 k g a b) x #

to :: Rep (Joker k1 k g a b) x -> Joker k1 k g a b #

Generic (Flip k k1 p a b) 

Associated Types

type Rep (Flip k k1 p a b) :: * -> * #

Methods

from :: Flip k k1 p a b -> Rep (Flip k k1 p a b) x #

to :: Rep (Flip k k1 p a b) x -> Flip k k1 p a b #

Generic (Clown k1 k f a b) 

Associated Types

type Rep (Clown k1 k f a b) :: * -> * #

Methods

from :: Clown k1 k f a b -> Rep (Clown k1 k f a b) x #

to :: Rep (Clown k1 k f a b) x -> Clown k1 k f a b #

Generic (a, b, c, d, e, f) 

Associated Types

type Rep (a, b, c, d, e, f) :: * -> * #

Methods

from :: (a, b, c, d, e, f) -> Rep (a, b, c, d, e, f) x #

to :: Rep (a, b, c, d, e, f) x -> (a, b, c, d, e, f) #

Generic (Product k1 k f g a b) 

Associated Types

type Rep (Product k1 k f g a b) :: * -> * #

Methods

from :: Product k1 k f g a b -> Rep (Product k1 k f g a b) x #

to :: Rep (Product k1 k f g a b) x -> Product k1 k f g a b #

Generic (Sum k1 k p q a b) 

Associated Types

type Rep (Sum k1 k p q a b) :: * -> * #

Methods

from :: Sum k1 k p q a b -> Rep (Sum k1 k p q a b) x #

to :: Rep (Sum k1 k p q a b) x -> Sum k1 k p q a b #

Generic (a, b, c, d, e, f, g) 

Associated Types

type Rep (a, b, c, d, e, f, g) :: * -> * #

Methods

from :: (a, b, c, d, e, f, g) -> Rep (a, b, c, d, e, f, g) x #

to :: Rep (a, b, c, d, e, f, g) x -> (a, b, c, d, e, f, g) #

Generic (Tannen k2 k1 k f p a b) 

Associated Types

type Rep (Tannen k2 k1 k f p a b) :: * -> * #

Methods

from :: Tannen k2 k1 k f p a b -> Rep (Tannen k2 k1 k f p a b) x #

to :: Rep (Tannen k2 k1 k f p a b) x -> Tannen k2 k1 k f p a b #

Generic (Biff k3 k2 k1 k p f g a b) 

Associated Types

type Rep (Biff k3 k2 k1 k p f g a b) :: * -> * #

Methods

from :: Biff k3 k2 k1 k p f g a b -> Rep (Biff k3 k2 k1 k p f g a b) x #

to :: Rep (Biff k3 k2 k1 k p f g a b) x -> Biff k3 k2 k1 k p f g a b #

Functions

chain :: Traversable t => t (a -> a) -> a -> a Source #

Date and Time

newtype Day :: * #

The Modified Julian Day is a standard count of days, with zero being the day 1858-11-17.

Instances

Enum Day 

Methods

succ :: Day -> Day #

pred :: Day -> Day #

toEnum :: Int -> Day #

fromEnum :: Day -> Int #

enumFrom :: Day -> [Day] #

enumFromThen :: Day -> Day -> [Day] #

enumFromTo :: Day -> Day -> [Day] #

enumFromThenTo :: Day -> Day -> Day -> [Day] #

Eq Day 

Methods

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

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

Data Day 

Methods

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

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

toConstr :: Day -> Constr #

dataTypeOf :: Day -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Day 

Methods

compare :: Day -> Day -> Ordering #

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

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

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

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

max :: Day -> Day -> Day #

min :: Day -> Day -> Day #

Ix Day 

Methods

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

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

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

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

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

unsafeRangeSize :: (Day, Day) -> Int

ToJSON Day 
ToJSONKey Day 
FromJSON Day 
FromJSONKey Day 
NFData Day 

Methods

rnf :: Day -> () #

FormatTime Day 
ParseTime Day 

Methods

buildTime :: TimeLocale -> [(Char, String)] -> Maybe Day #

data TimeOfDay :: * #

Time of day as represented in hour, minute and second (with picoseconds), typically used to express local time of day.

Constructors

TimeOfDay 

Fields

  • todHour :: Int

    range 0 - 23

  • todMin :: Int

    range 0 - 59

  • todSec :: Pico

    Note that 0 <= todSec < 61, accomodating leap seconds. Any local minute may have a leap second, since leap seconds happen in all zones simultaneously

Instances

Eq TimeOfDay 
Data TimeOfDay 

Methods

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

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

toConstr :: TimeOfDay -> Constr #

dataTypeOf :: TimeOfDay -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TimeOfDay 
Show TimeOfDay 
ToJSON TimeOfDay 
ToJSONKey TimeOfDay 
FromJSON TimeOfDay 
FromJSONKey TimeOfDay 
NFData TimeOfDay 

Methods

rnf :: TimeOfDay -> () #

FormatTime TimeOfDay 
ParseTime TimeOfDay 

data UTCTime :: * #

This is the simplest representation of UTC. It consists of the day number, and a time offset from midnight. Note that if a day has a leap second added to it, it will have 86401 seconds.

Constructors

UTCTime 

Fields

Instances

Eq UTCTime 

Methods

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

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

Data UTCTime 

Methods

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

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

toConstr :: UTCTime -> Constr #

dataTypeOf :: UTCTime -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord UTCTime 
ToJSON UTCTime 
ToJSONKey UTCTime 
FromJSON UTCTime 
FromJSONKey UTCTime 
NFData UTCTime 

Methods

rnf :: UTCTime -> () #

FormatTime UTCTime 
ParseTime UTCTime 

data LocalTime :: * #

A simple day and time aggregate, where the day is of the specified parameter, and the time is a TimeOfDay. Conversion of this (as local civil time) to UTC depends on the time zone. Conversion of this (as local mean time) to UT1 depends on the longitude.

Constructors

LocalTime 

Instances

Eq LocalTime 
Data LocalTime 

Methods

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

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

toConstr :: LocalTime -> Constr #

dataTypeOf :: LocalTime -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LocalTime 
Show LocalTime 
ToJSON LocalTime 
ToJSONKey LocalTime 
FromJSON LocalTime 
FromJSONKey LocalTime 
NFData LocalTime 

Methods

rnf :: LocalTime -> () #

FormatTime LocalTime 
ParseTime LocalTime 

data TimeZone :: * #

A TimeZone is a whole number of minutes offset from UTC, together with a name and a "just for summer" flag.

Constructors

TimeZone 

Fields

Instances

Eq TimeZone 
Data TimeZone 

Methods

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

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

toConstr :: TimeZone -> Constr #

dataTypeOf :: TimeZone -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TimeZone 
Show TimeZone 
NFData TimeZone 

Methods

rnf :: TimeZone -> () #

FormatTime TimeZone 
ParseTime TimeZone 

data ZonedTime :: * #

A local time together with a TimeZone.

Instances

Data ZonedTime 

Methods

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

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

toConstr :: ZonedTime -> Constr #

dataTypeOf :: ZonedTime -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ZonedTime 
ToJSON ZonedTime 
ToJSONKey ZonedTime 
FromJSON ZonedTime 
FromJSONKey ZonedTime 
NFData ZonedTime 

Methods

rnf :: ZonedTime -> () #

FormatTime ZonedTime 
ParseTime ZonedTime 

data TimeLocale :: * #

Constructors

TimeLocale 

Fields

data DiffTime :: * #

This is a length of time, as measured by a clock. Conversion functions will treat it as seconds. It has a precision of 10^-12 s.

Instances

Enum DiffTime 
Eq DiffTime 
Fractional DiffTime 
Data DiffTime 

Methods

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

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

toConstr :: DiffTime -> Constr #

dataTypeOf :: DiffTime -> DataType #

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

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

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

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

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

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

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

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

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

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

Num DiffTime 
Ord DiffTime 
Real DiffTime 
RealFrac DiffTime 

Methods

properFraction :: Integral b => DiffTime -> (b, DiffTime) #

truncate :: Integral b => DiffTime -> b #

round :: Integral b => DiffTime -> b #

ceiling :: Integral b => DiffTime -> b #

floor :: Integral b => DiffTime -> b #

Show DiffTime 
NFData DiffTime 

Methods

rnf :: DiffTime -> () #

data NominalDiffTime :: * #

This is a length of time, as measured by UTC. Conversion functions will treat it as seconds. It has a precision of 10^-12 s. It ignores leap-seconds, so it's not necessarily a fixed amount of clock time. For instance, 23:00 UTC + 2 hours of NominalDiffTime = 01:00 UTC (+ 1 day), regardless of whether a leap-second intervened.

Instances

Enum NominalDiffTime 
Eq NominalDiffTime 
Fractional NominalDiffTime 
Data NominalDiffTime 

Methods

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

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

toConstr :: NominalDiffTime -> Constr #

dataTypeOf :: NominalDiffTime -> DataType #

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

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

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

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

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

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

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

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

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

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

Num NominalDiffTime 
Ord NominalDiffTime 
Real NominalDiffTime 
RealFrac NominalDiffTime 
Show NominalDiffTime 
ToJSON NominalDiffTime 
FromJSON NominalDiffTime

WARNING: Only parse lengths of time from trusted input since an attacker could easily fill up the memory of the target system by specifying a scientific number with a big exponent like 1e1000000000.

NFData NominalDiffTime 

Methods

rnf :: NominalDiffTime -> () #

secondsToDiffTime :: Integer -> DiffTime #

Create a DiffTime which represents an integral number of seconds.

picosecondsToDiffTime :: Integer -> DiffTime #

Create a DiffTime from a number of picoseconds.

addUTCTime :: NominalDiffTime -> UTCTime -> UTCTime #

addUTCTime a b = a + b

diffUTCTime :: UTCTime -> UTCTime -> NominalDiffTime #

diffUTCTime a b = a - b

getCurrentTime :: IO UTCTime #

Get the current UTC time from the system clock.

defaultTimeLocale :: TimeLocale #

Locale representing American usage.

knownTimeZones contains only the ten time-zones mentioned in RFC 822 sec. 5: "UT", "GMT", "EST", "EDT", "CST", "CDT", "MST", "MDT", "PST", "PDT". Note that the parsing functions will regardless parse single-letter military time-zones and +HHMM format.

toGregorian :: Day -> (Integer, Int, Int) #

convert to proleptic Gregorian calendar. First element of result is year, second month number (1-12), third day (1-31).

fromGregorian :: Integer -> Int -> Int -> Day #

convert from proleptic Gregorian calendar. First argument is year, second month number (1-12), third day (1-31). Invalid values will be clipped to the correct range, month first, then day.

formatTime :: FormatTime t => TimeLocale -> String -> t -> String #

Substitute various time-related information for each %-code in the string, as per formatCharacter.

For all types (note these three are done here, not by formatCharacter):

%%
%
%t
tab
%n
newline

glibc-style modifiers can be used before the letter (here marked as z):

%-z
no padding
%_z
pad with spaces
%0z
pad with zeros
%^z
convert to upper case
%#z
convert to lower case (consistently, unlike glibc)

For TimeZone (and ZonedTime and UTCTime):

%z
timezone offset in the format -HHMM.
%Z
timezone name

For LocalTime (and ZonedTime and UTCTime and UniversalTime):

%c
as dateTimeFmt locale (e.g. %a %b %e %H:%M:%S %Z %Y)

For TimeOfDay (and LocalTime and ZonedTime and UTCTime and UniversalTime):

%R
same as %H:%M
%T
same as %H:%M:%S
%X
as timeFmt locale (e.g. %H:%M:%S)
%r
as time12Fmt locale (e.g. %I:%M:%S %p)
%P
day-half of day from (amPm locale), converted to lowercase, am, pm
%p
day-half of day from (amPm locale), AM, PM
%H
hour of day (24-hour), 0-padded to two chars, 00 - 23
%k
hour of day (24-hour), space-padded to two chars, 0 - 23
%I
hour of day-half (12-hour), 0-padded to two chars, 01 - 12
%l
hour of day-half (12-hour), space-padded to two chars, 1 - 12
%M
minute of hour, 0-padded to two chars, 00 - 59
%S
second of minute (without decimal part), 0-padded to two chars, 00 - 60
%q
picosecond of second, 0-padded to twelve chars, 000000000000 - 999999999999.
%Q
decimal point and fraction of second, up to 12 second decimals, without trailing zeros. For a whole number of seconds, %Q produces the empty string.

For UTCTime and ZonedTime:

%s
number of whole seconds since the Unix epoch. For times before the Unix epoch, this is a negative number. Note that in %s.%q and %s%Q the decimals are positive, not negative. For example, 0.9 seconds before the Unix epoch is formatted as -1.1 with %s%Q.

For Day (and LocalTime and ZonedTime and UTCTime and UniversalTime):

%D
same as %m/%d/%y
%F
same as %Y-%m-%d
%x
as dateFmt locale (e.g. %m/%d/%y)
%Y
year, no padding. Note %0Y and %_Y pad to four chars
%y
year of century, 0-padded to two chars, 00 - 99
%C
century, no padding. Note %0C and %_C pad to two chars
%B
month name, long form (fst from months locale), January - December
%b, %h
month name, short form (snd from months locale), Jan - Dec
%m
month of year, 0-padded to two chars, 01 - 12
%d
day of month, 0-padded to two chars, 01 - 31
%e
day of month, space-padded to two chars, 1 - 31
%j
day of year, 0-padded to three chars, 001 - 366
%G
year for Week Date format, no padding. Note %0G and %_G pad to four chars
%g
year of century for Week Date format, 0-padded to two chars, 00 - 99
%f
century for Week Date format, no padding. Note %0f and %_f pad to two chars
%V
week of year for Week Date format, 0-padded to two chars, 01 - 53
%u
day of week for Week Date format, 1 - 7
%a
day of week, short form (snd from wDays locale), Sun - Sat
%A
day of week, long form (fst from wDays locale), Sunday - Saturday
%U
week of year where weeks start on Sunday (as sundayStartWeek), 0-padded to two chars, 00 - 53
%w
day of week number, 0 (= Sunday) - 6 (= Saturday)
%W
week of year where weeks start on Monday (as mondayStartWeek), 0-padded to two chars, 00 - 53