Copyright | (c) 2015-2016 Martijn Rijkeboer <mrr@sru-systems.com> |
---|---|
License | MIT |
Maintainer | Martijn Rijkeboer <mrr@sru-systems.com> |
Safe Haskell | None |
Language | Haskell2010 |
Internal functions used by the generated types.
Synopsis
- class Default a where
- defaultVal :: a
- newtype FieldNumber = FieldNumber Word32
- fromFieldNumber :: FieldNumber -> Word32
- toFieldNumber :: Word32 -> Either String FieldNumber
- class Mergeable a where
- merge :: a -> a -> a
- class Required a where
- class WireEnum a where
- class Default a where
- defaultVal :: a
- newtype FieldNumber = FieldNumber Word32
- fromFieldNumber :: FieldNumber -> Word32
- toFieldNumber :: Word32 -> Either String FieldNumber
- class Mergeable a where
- merge :: a -> a -> a
- class Required a where
- class WireEnum a where
- class WireMessage a where
- fieldToValue :: WireTag -> a -> Get a
- messageToFields :: a -> Put
- data WireTag = WireTag FieldNumber WireType
- fromWireTag :: WireTag -> Word32
- toWireTag :: Word32 -> Either String WireTag
- data WireType
- fromWireType :: WireType -> Word32
- toWireType :: Word32 -> Either String WireType
- decode :: (Default a, Required a, WireMessage a) => ByteString -> Either String a
- encode :: WireMessage a => a -> ByteString
- getBool :: Get Bool
- getBoolOpt :: Get (Maybe Bool)
- getBoolPacked :: Get (Seq Bool)
- getBytes :: Get ByteString
- getBytesOpt :: Get (Maybe ByteString)
- getDouble :: Get Double
- getDoubleOpt :: Get (Maybe Double)
- getDoublePacked :: Get (Seq Double)
- getEnum :: WireEnum a => Get a
- getEnumOpt :: WireEnum a => Get (Maybe a)
- getEnumPacked :: WireEnum a => Get (Seq a)
- getFixed32 :: Get Word32
- getFixed32Opt :: Get (Maybe Word32)
- getFixed32Packed :: Get (Seq Word32)
- getFixed64 :: Get Word64
- getFixed64Opt :: Get (Maybe Word64)
- getFixed64Packed :: Get (Seq Word64)
- getFloat :: Get Float
- getFloatOpt :: Get (Maybe Float)
- getFloatPacked :: Get (Seq Float)
- getGroup :: (Default a, Required a, WireMessage a) => Get a
- getGroupOpt :: (Default a, Required a, WireMessage a) => Get (Maybe a)
- getInt32 :: Get Int32
- getInt32Opt :: Get (Maybe Int32)
- getInt32Packed :: Get (Seq Int32)
- getInt64 :: Get Int64
- getInt64Opt :: Get (Maybe Int64)
- getInt64Packed :: Get (Seq Int64)
- getMessage :: (Default a, Required a, WireMessage a) => Get a
- getMessageOpt :: (Default a, Required a, WireMessage a) => Get (Maybe a)
- getSFixed32 :: Get Int32
- getSFixed32Opt :: Get (Maybe Int32)
- getSFixed32Packed :: Get (Seq Int32)
- getSFixed64 :: Get Int64
- getSFixed64Opt :: Get (Maybe Int64)
- getSFixed64Packed :: Get (Seq Int64)
- getSInt32 :: Get Int32
- getSInt32Opt :: Get (Maybe Int32)
- getSInt32Packed :: Get (Seq Int32)
- getSInt64 :: Get Int64
- getSInt64Opt :: Get (Maybe Int64)
- getSInt64Packed :: Get (Seq Int64)
- getString :: Get Text
- getStringOpt :: Get (Maybe Text)
- getUInt32 :: Get Word32
- getUInt32Opt :: Get (Maybe Word32)
- getUInt32Packed :: Get (Seq Word32)
- getUInt64 :: Get Word64
- getUInt64Opt :: Get (Maybe Word64)
- getUInt64Packed :: Get (Seq Word64)
- getUnknown :: WireTag -> a -> Get a
- getWireTag :: Get WireTag
- putBool :: WireTag -> Bool -> Put
- putBoolList :: WireTag -> Seq Bool -> Put
- putBoolOpt :: WireTag -> Maybe Bool -> Put
- putBoolPacked :: WireTag -> Seq Bool -> Put
- putBytes :: WireTag -> ByteString -> Put
- putBytesList :: WireTag -> Seq ByteString -> Put
- putBytesOpt :: WireTag -> Maybe ByteString -> Put
- putDouble :: WireTag -> Double -> Put
- putDoubleList :: WireTag -> Seq Double -> Put
- putDoubleOpt :: WireTag -> Maybe Double -> Put
- putDoublePacked :: WireTag -> Seq Double -> Put
- putEnum :: WireEnum a => WireTag -> a -> Put
- putEnumList :: WireEnum a => WireTag -> Seq a -> Put
- putEnumOpt :: WireEnum a => WireTag -> Maybe a -> Put
- putEnumPacked :: WireEnum a => WireTag -> Seq a -> Put
- putFixed32 :: WireTag -> Word32 -> Put
- putFixed32List :: WireTag -> Seq Word32 -> Put
- putFixed32Opt :: WireTag -> Maybe Word32 -> Put
- putFixed32Packed :: WireTag -> Seq Word32 -> Put
- putFixed64 :: WireTag -> Word64 -> Put
- putFixed64List :: WireTag -> Seq Word64 -> Put
- putFixed64Opt :: WireTag -> Maybe Word64 -> Put
- putFixed64Packed :: WireTag -> Seq Word64 -> Put
- putFloat :: WireTag -> Float -> Put
- putFloatList :: WireTag -> Seq Float -> Put
- putFloatOpt :: WireTag -> Maybe Float -> Put
- putFloatPacked :: WireTag -> Seq Float -> Put
- putGroup :: WireMessage a => a -> Put
- putGroupOpt :: WireMessage a => Maybe a -> Put
- putInt32 :: WireTag -> Int32 -> Put
- putInt32List :: WireTag -> Seq Int32 -> Put
- putInt32Opt :: WireTag -> Maybe Int32 -> Put
- putInt32Packed :: WireTag -> Seq Int32 -> Put
- putInt64 :: WireTag -> Int64 -> Put
- putInt64List :: WireTag -> Seq Int64 -> Put
- putInt64Opt :: WireTag -> Maybe Int64 -> Put
- putInt64Packed :: WireTag -> Seq Int64 -> Put
- putSFixed32 :: WireTag -> Int32 -> Put
- putSFixed32List :: WireTag -> Seq Int32 -> Put
- putSFixed32Opt :: WireTag -> Maybe Int32 -> Put
- putSFixed32Packed :: WireTag -> Seq Int32 -> Put
- putSFixed64 :: WireTag -> Int64 -> Put
- putSFixed64List :: WireTag -> Seq Int64 -> Put
- putSFixed64Opt :: WireTag -> Maybe Int64 -> Put
- putSFixed64Packed :: WireTag -> Seq Int64 -> Put
- putSInt32 :: WireTag -> Int32 -> Put
- putSInt32List :: WireTag -> Seq Int32 -> Put
- putSInt32Opt :: WireTag -> Maybe Int32 -> Put
- putSInt32Packed :: WireTag -> Seq Int32 -> Put
- putSInt64 :: WireTag -> Int64 -> Put
- putSInt64List :: WireTag -> Seq Int64 -> Put
- putSInt64Opt :: WireTag -> Maybe Int64 -> Put
- putSInt64Packed :: WireTag -> Seq Int64 -> Put
- putMessage :: WireMessage a => WireTag -> a -> Put
- putMessageList :: WireMessage a => WireTag -> Seq a -> Put
- putMessageOpt :: WireMessage a => WireTag -> Maybe a -> Put
- putString :: WireTag -> Text -> Put
- putStringList :: WireTag -> Seq Text -> Put
- putStringOpt :: WireTag -> Maybe Text -> Put
- putUInt32 :: WireTag -> Word32 -> Put
- putUInt32List :: WireTag -> Seq Word32 -> Put
- putUInt32Opt :: WireTag -> Maybe Word32 -> Put
- putUInt32Packed :: WireTag -> Seq Word32 -> Put
- putUInt64 :: WireTag -> Word64 -> Put
- putUInt64List :: WireTag -> Seq Word64 -> Put
- putUInt64Opt :: WireTag -> Maybe Word64 -> Put
- putUInt64Packed :: WireTag -> Seq Word64 -> Put
- putWireTag :: WireTag -> Put
- class WireMessage a where
- fieldToValue :: WireTag -> a -> Get a
- messageToFields :: a -> Put
- data WireTag = WireTag FieldNumber WireType
- fromWireTag :: WireTag -> Word32
- toWireTag :: Word32 -> Either String WireTag
- data WireType
- fromWireType :: WireType -> Word32
- toWireType :: Word32 -> Either String WireType
- class Eq a
- return :: Monad m => a -> m a
- class Eq a => Ord a
- class Show a
- data Bool
- data Double
- data Float
- data Int32
- data Int64
- data Maybe a
- data Word32
- data Word64
- data ByteString
- data Seq a
- fromList :: Ord a => [a] -> Set a
- pack :: String -> Text
- data Text
- append :: Seq a -> a -> Seq a
Documentation
class Default a where Source #
Typeclass to handle default values.
defaultVal :: a Source #
The default value for the field.
Instances
Default Bool Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Bool Source # | |
Default Double Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Double Source # | |
Default Float Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Float Source # | |
Default Int32 Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Int32 Source # | |
Default Int64 Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Int64 Source # | |
Default Word32 Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Word32 Source # | |
Default Word64 Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Word64 Source # | |
Default ByteString Source # | |
Defined in Data.ProtoBuf.Default | |
Default Text Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Text Source # | |
Default (Maybe a) Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Maybe a Source # | |
Default (Seq a) Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Seq a Source # |
newtype FieldNumber Source #
Type to represent a field number (unique numbered tag).
Instances
fromFieldNumber :: FieldNumber -> Word32 Source #
Convert a FieldNumber into a Word32.
toFieldNumber :: Word32 -> Either String FieldNumber Source #
Convert a Word32 into a FieldNumber or an error.
class Mergeable a where Source #
Typeclass to handle merging of values.
Nothing
Instances
Mergeable Bool Source # | |
Mergeable Double Source # | |
Mergeable Float Source # | |
Mergeable Int32 Source # | |
Mergeable Int64 Source # | |
Mergeable Word32 Source # | |
Mergeable Word64 Source # | |
Mergeable ByteString Source # | |
Defined in Data.ProtoBuf.Mergeable merge :: ByteString -> ByteString -> ByteString Source # | |
Mergeable Text Source # | |
Mergeable a => Mergeable (Maybe a) Source # | |
Mergeable (Seq a) Source # | |
class Default a where Source #
Typeclass to handle default values.
defaultVal :: a Source #
The default value for the field.
Instances
Default Bool Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Bool Source # | |
Default Double Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Double Source # | |
Default Float Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Float Source # | |
Default Int32 Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Int32 Source # | |
Default Int64 Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Int64 Source # | |
Default Word32 Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Word32 Source # | |
Default Word64 Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Word64 Source # | |
Default ByteString Source # | |
Defined in Data.ProtoBuf.Default | |
Default Text Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Text Source # | |
Default (Maybe a) Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Maybe a Source # | |
Default (Seq a) Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Seq a Source # |
newtype FieldNumber Source #
Type to represent a field number (unique numbered tag).
Instances
fromFieldNumber :: FieldNumber -> Word32 Source #
Convert a FieldNumber into a Word32.
toFieldNumber :: Word32 -> Either String FieldNumber Source #
Convert a Word32 into a FieldNumber or an error.
class Mergeable a where Source #
Typeclass to handle merging of values.
Nothing
Instances
Mergeable Bool Source # | |
Mergeable Double Source # | |
Mergeable Float Source # | |
Mergeable Int32 Source # | |
Mergeable Int64 Source # | |
Mergeable Word32 Source # | |
Mergeable Word64 Source # | |
Mergeable ByteString Source # | |
Defined in Data.ProtoBuf.Mergeable merge :: ByteString -> ByteString -> ByteString Source # | |
Mergeable Text Source # | |
Mergeable a => Mergeable (Maybe a) Source # | |
Mergeable (Seq a) Source # | |
class WireMessage a where Source #
Typeclass to handle encoding and decoding of messages.
fieldToValue :: WireTag -> a -> Get a Source #
Decode a field and merge it with the existing value in the message.
messageToFields :: a -> Put Source #
Encode all the fields of the message.
Type to represent a wire tag.
fromWireTag :: WireTag -> Word32 Source #
Convert a WireTag into a Word32.
Type to represent the Protocol Buffers wire type.
VarInt | The varint type: int32, int64, uint32, sint32, sint64, bool enum |
Bit64 | The 64-bit type: fixed64, sfixed64, double |
LenDelim | The length-delimited: string, bytes, embedded messages, packed repeated fields |
Bit32 | The 32-bit type: fixed32, sfixed32, float |
fromWireType :: WireType -> Word32 Source #
Convert a WireType into a Word32.
toWireType :: Word32 -> Either String WireType Source #
Convert a Word32 into a WireType or an error.
decode :: (Default a, Required a, WireMessage a) => ByteString -> Either String a Source #
Decode a ByteString into either the data-type or an error message.
Decode CustomType:
decCustomType :: ByteString -> Either String CustomType decCustomType = decode
encode :: WireMessage a => a -> ByteString Source #
Encode a data-type into a ByteString.
Encode CustomType:
encCustomType :: CustomType -> ByteString encCustomType = encode
getBytes :: Get ByteString Source #
Decode a required bytes field.
getBytesOpt :: Get (Maybe ByteString) Source #
Decode an optional bytes field.
getFixed32 :: Get Word32 Source #
Decode a required fixed32 field.
getFixed64 :: Get Word64 Source #
Decode a required fixed64 field.
getGroupOpt :: (Default a, Required a, WireMessage a) => Get (Maybe a) Source #
Decode an optional group field.
getMessage :: (Default a, Required a, WireMessage a) => Get a Source #
Decode a required message field.
getMessageOpt :: (Default a, Required a, WireMessage a) => Get (Maybe a) Source #
Decode an optional message field.
getSFixed32 :: Get Int32 Source #
Decode a required sfixed32 field.
getSFixed64 :: Get Int64 Source #
Decode a required sfixed64 field.
getUnknown :: WireTag -> a -> Get a Source #
Skip an unknown field.
getWireTag :: Get WireTag Source #
Decode a wire tag.
putBytesList :: WireTag -> Seq ByteString -> Put Source #
Encode a repeated bytes field.
putBytesOpt :: WireTag -> Maybe ByteString -> Put Source #
Encode an optional bytes field.
putGroup :: WireMessage a => a -> Put Source #
Encode a required group field.
putGroupOpt :: WireMessage a => Maybe a -> Put Source #
Encode an optional group field.
putMessage :: WireMessage a => WireTag -> a -> Put Source #
Encode a required message field.
putMessageList :: WireMessage a => WireTag -> Seq a -> Put Source #
Encode a repeated message field.
putMessageOpt :: WireMessage a => WireTag -> Maybe a -> Put Source #
Encode an optional message field.
putWireTag :: WireTag -> Put Source #
Encode a wire tag.
class WireMessage a where Source #
Typeclass to handle encoding and decoding of messages.
fieldToValue :: WireTag -> a -> Get a Source #
Decode a field and merge it with the existing value in the message.
messageToFields :: a -> Put Source #
Encode all the fields of the message.
Type to represent a wire tag.
fromWireTag :: WireTag -> Word32 Source #
Convert a WireTag into a Word32.
Type to represent the Protocol Buffers wire type.
VarInt | The varint type: int32, int64, uint32, sint32, sint64, bool enum |
Bit64 | The 64-bit type: fixed64, sfixed64, double |
LenDelim | The length-delimited: string, bytes, embedded messages, packed repeated fields |
Bit32 | The 32-bit type: fixed32, sfixed32, float |
fromWireType :: WireType -> Word32 Source #
Convert a WireType into a Word32.
toWireType :: Word32 -> Either String WireType Source #
Convert a Word32 into a WireType or an error.
The Eq
class defines equality (==
) and inequality (/=
).
All the basic datatypes exported by the Prelude are instances of Eq
,
and Eq
may be derived for any datatype whose constituents are also
instances of Eq
.
The Haskell Report defines no laws for Eq
. However, ==
is customarily
expected to implement an equivalence relationship where two values comparing
equal are indistinguishable by "public" functions, with a "public" function
being one not allowing to see implementation details. For example, for a
type representing non-normalised natural numbers modulo 100, a "public"
function doesn't make the difference between 1 and 201. It is expected to
have the following properties:
Instances
Eq Bool | |
Eq Char | |
Eq Double | Note that due to the presence of
Also note that
|
Eq Float | Note that due to the presence of
Also note that
|
Eq Int | |
Eq Int8 | Since: base-2.1 |
Eq Int16 | Since: base-2.1 |
Eq Int32 | Since: base-2.1 |
Eq Int64 | Since: base-2.1 |
Eq Integer | |
Eq Natural | Since: base-4.8.0.0 |
Eq Ordering | |
Eq Word | |
Eq Word8 | Since: base-2.1 |
Eq Word16 | Since: base-2.1 |
Eq Word32 | Since: base-2.1 |
Eq Word64 | Since: base-2.1 |
Eq () | |
Eq TyCon | |
Eq Module | |
Eq TrName | |
Eq SpecConstrAnnotation | Since: base-4.3.0.0 |
Defined in GHC.Exts (==) :: SpecConstrAnnotation -> SpecConstrAnnotation -> Bool # (/=) :: SpecConstrAnnotation -> SpecConstrAnnotation -> Bool # | |
Eq AsyncException | Since: base-4.2.0.0 |
Defined in GHC.IO.Exception (==) :: AsyncException -> AsyncException -> Bool # (/=) :: AsyncException -> AsyncException -> Bool # | |
Eq ArrayException | Since: base-4.2.0.0 |
Defined in GHC.IO.Exception (==) :: ArrayException -> ArrayException -> Bool # (/=) :: ArrayException -> ArrayException -> Bool # | |
Eq ExitCode | |
Eq IOErrorType | Since: base-4.1.0.0 |
Defined in GHC.IO.Exception (==) :: IOErrorType -> IOErrorType -> Bool # (/=) :: IOErrorType -> IOErrorType -> Bool # | |
Eq MaskingState | Since: base-4.3.0.0 |
Defined in GHC.IO (==) :: MaskingState -> MaskingState -> Bool # (/=) :: MaskingState -> MaskingState -> Bool # | |
Eq IOException | Since: base-4.1.0.0 |
Defined in GHC.IO.Exception (==) :: IOException -> IOException -> Bool # (/=) :: IOException -> IOException -> Bool # | |
Eq ByteString | |
Defined in Data.ByteString.Lazy.Internal (==) :: ByteString -> ByteString -> Bool # (/=) :: ByteString -> ByteString -> Bool # | |
Eq BigNat | |
Eq UnicodeException | |
Defined in Data.Text.Encoding.Error (==) :: UnicodeException -> UnicodeException -> Bool # (/=) :: UnicodeException -> UnicodeException -> Bool # | |
Eq FieldNumber Source # | |
Defined in Data.ProtoBuf.FieldNumber (==) :: FieldNumber -> FieldNumber -> Bool # (/=) :: FieldNumber -> FieldNumber -> Bool # | |
Eq WireType Source # | |
Eq WireTag Source # | |
Eq a => Eq [a] | |
Eq a => Eq (Maybe a) | Since: base-2.1 |
Eq a => Eq (Ratio a) | Since: base-2.1 |
Eq a => Eq (NonEmpty a) | Since: base-4.9.0.0 |
Eq a => Eq (Seq a) | |
Eq a => Eq (ViewL a) | |
Eq a => Eq (ViewR a) | |
Eq a => Eq (Set a) | |
(Eq a, Eq b) => Eq (Either a b) | Since: base-2.1 |
(Eq a, Eq b) => Eq (a, b) | |
(Eq a, Eq b, Eq c) => Eq (a, b, c) | |
(Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) | |
(Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (a, b, c, d, e, f) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (a, b, c, d, e, f, g) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h) => Eq (a, b, c, d, e, f, g, h) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) => Eq (a, b, c, d, e, f, g, h, i) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j) => Eq (a, b, c, d, e, f, g, h, i, j) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k) => Eq (a, b, c, d, e, f, g, h, i, j, k) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l) => Eq (a, b, c, d, e, f, g, h, i, j, k, l) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | |
The Ord
class is used for totally ordered datatypes.
Instances of Ord
can be derived for any user-defined datatype whose
constituent types are in Ord
. The declared order of the constructors in
the data declaration determines the ordering in derived Ord
instances. The
Ordering
datatype allows a single comparison to determine the precise
ordering of two objects.
The Haskell Report defines no laws for Ord
. However, <=
is customarily
expected to implement a non-strict partial order and have the following
properties:
- Transitivity
- if
x <= y && y <= z
=True
, thenx <= z
=True
- Reflexivity
x <= x
=True
- Antisymmetry
- if
x <= y && y <= x
=True
, thenx == y
=True
Note that the following operator interactions are expected to hold:
x >= y
=y <= x
x < y
=x <= y && x /= y
x > y
=y < x
x < y
=compare x y == LT
x > y
=compare x y == GT
x == y
=compare x y == EQ
min x y == if x <= y then x else y
=True
max x y == if x >= y then x else y
=True
Note that (7.) and (8.) do not require min
and max
to return either of
their arguments. The result is merely required to equal one of the
arguments in terms of (==)
.
Minimal complete definition: either compare
or <=
.
Using compare
can be more efficient for complex types.
Instances
Ord Bool | |
Ord Char | |
Ord Double | Note that due to the presence of
Also note that, due to the same,
|
Ord Float | Note that due to the presence of
Also note that, due to the same,
|
Ord Int | |
Ord Int8 | Since: base-2.1 |
Ord Int16 | Since: base-2.1 |
Ord Int32 | Since: base-2.1 |
Ord Int64 | Since: base-2.1 |
Ord Integer | |
Ord Natural | Since: base-4.8.0.0 |
Ord Ordering | |
Defined in GHC.Classes | |
Ord Word | |
Ord Word8 | Since: base-2.1 |
Ord Word16 | Since: base-2.1 |
Ord Word32 | Since: base-2.1 |
Ord Word64 | Since: base-2.1 |
Ord () | |
Ord TyCon | |
Ord AsyncException | Since: base-4.2.0.0 |
Defined in GHC.IO.Exception compare :: AsyncException -> AsyncException -> Ordering # (<) :: AsyncException -> AsyncException -> Bool # (<=) :: AsyncException -> AsyncException -> Bool # (>) :: AsyncException -> AsyncException -> Bool # (>=) :: AsyncException -> AsyncException -> Bool # max :: AsyncException -> AsyncException -> AsyncException # min :: AsyncException -> AsyncException -> AsyncException # | |
Ord ArrayException | Since: base-4.2.0.0 |
Defined in GHC.IO.Exception compare :: ArrayException -> ArrayException -> Ordering # (<) :: ArrayException -> ArrayException -> Bool # (<=) :: ArrayException -> ArrayException -> Bool # (>) :: ArrayException -> ArrayException -> Bool # (>=) :: ArrayException -> ArrayException -> Bool # max :: ArrayException -> ArrayException -> ArrayException # min :: ArrayException -> ArrayException -> ArrayException # | |
Ord ExitCode | |
Defined in GHC.IO.Exception | |
Ord ByteString | |
Defined in Data.ByteString.Lazy.Internal compare :: ByteString -> ByteString -> Ordering # (<) :: ByteString -> ByteString -> Bool # (<=) :: ByteString -> ByteString -> Bool # (>) :: ByteString -> ByteString -> Bool # (>=) :: ByteString -> ByteString -> Bool # max :: ByteString -> ByteString -> ByteString # min :: ByteString -> ByteString -> ByteString # | |
Ord BigNat | |
Ord FieldNumber Source # | |
Defined in Data.ProtoBuf.FieldNumber compare :: FieldNumber -> FieldNumber -> Ordering # (<) :: FieldNumber -> FieldNumber -> Bool # (<=) :: FieldNumber -> FieldNumber -> Bool # (>) :: FieldNumber -> FieldNumber -> Bool # (>=) :: FieldNumber -> FieldNumber -> Bool # max :: FieldNumber -> FieldNumber -> FieldNumber # min :: FieldNumber -> FieldNumber -> FieldNumber # | |
Ord WireType Source # | |
Defined in Data.ProtoBuf.WireType | |
Ord WireTag Source # | |
Ord a => Ord [a] | |
Ord a => Ord (Maybe a) | Since: base-2.1 |
Integral a => Ord (Ratio a) | Since: base-2.0.1 |
Ord a => Ord (NonEmpty a) | Since: base-4.9.0.0 |
Ord a => Ord (Seq a) | |
Ord a => Ord (ViewL a) | |
Ord a => Ord (ViewR a) | |
Ord a => Ord (Set a) | |
(Ord a, Ord b) => Ord (Either a b) | Since: base-2.1 |
(Ord a, Ord b) => Ord (a, b) | |
(Ord a, Ord b, Ord c) => Ord (a, b, c) | |
Defined in GHC.Classes | |
(Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) | |
Defined in GHC.Classes | |
(Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) | |
Defined in GHC.Classes compare :: (a, b, c, d, e) -> (a, b, c, d, e) -> Ordering # (<) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool # (<=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool # (>) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool # (>=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool # max :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) # min :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f) => Ord (a, b, c, d, e, f) | |
Defined in GHC.Classes compare :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Ordering # (<) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool # (<=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool # (>) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool # (>=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool # max :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) # min :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g) => Ord (a, b, c, d, e, f, g) | |
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Ordering # (<) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool # (<=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool # (>) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool # (>=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool # max :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) # min :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h) => Ord (a, b, c, d, e, f, g, h) | |
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Ordering # (<) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool # (<=) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool # (>) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool # (>=) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool # max :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) # min :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) => Ord (a, b, c, d, e, f, g, h, i) | |
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Ordering # (<) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool # (<=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool # (>) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool # (>=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool # max :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) # min :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j) => Ord (a, b, c, d, e, f, g, h, i, j) | |
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Ordering # (<) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool # (<=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool # (>) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool # (>=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool # max :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) # min :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k) => Ord (a, b, c, d, e, f, g, h, i, j, k) | |
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Ordering # (<) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool # (<=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool # (>) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool # (>=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool # max :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) # min :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l) => Ord (a, b, c, d, e, f, g, h, i, j, k, l) | |
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Ordering # (<) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool # (<=) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool # (>) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool # (>=) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool # max :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) # min :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m) | |
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Ordering # (<) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool # (<=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool # (>) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool # (>=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool # max :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) # min :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Ordering # (<) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool # (<=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool # (>) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool # (>=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool # max :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) # min :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n, Ord o) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | |
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Ordering # (<) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool # (<=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool # (>) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool # (>=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool # max :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) # min :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) # |
Conversion of values to readable String
s.
Derived instances of Show
have the following properties, which
are compatible with derived instances of Read
:
- The result of
show
is a syntactically correct Haskell expression containing only constants, given the fixity declarations in force at the point where the type is declared. It contains only the constructor names defined in the data type, parentheses, and spaces. When labelled constructor fields are used, braces, commas, field names, and equal signs are also used. - If the constructor is defined to be an infix operator, then
showsPrec
will produce infix applications of the constructor. - the representation will be enclosed in parentheses if the
precedence of the top-level constructor in
x
is less thand
(associativity is ignored). Thus, ifd
is0
then the result is never surrounded in parentheses; ifd
is11
it is always surrounded in parentheses, unless it is an atomic expression. - If the constructor is defined using record syntax, then
show
will produce the record-syntax form, with the fields given in the same order as the original declaration.
For example, given the declarations
infixr 5 :^: data Tree a = Leaf a | Tree a :^: Tree a
the derived instance of Show
is equivalent to
instance (Show a) => Show (Tree a) where showsPrec d (Leaf m) = showParen (d > app_prec) $ showString "Leaf " . showsPrec (app_prec+1) m where app_prec = 10 showsPrec d (u :^: v) = showParen (d > up_prec) $ showsPrec (up_prec+1) u . showString " :^: " . showsPrec (up_prec+1) v where up_prec = 5
Note that right-associativity of :^:
is ignored. For example,
produces the stringshow
(Leaf 1 :^: Leaf 2 :^: Leaf 3)"Leaf 1 :^: (Leaf 2 :^: Leaf 3)"
.
Instances
Instances
Bounded Bool | Since: base-2.1 |
Enum Bool | Since: base-2.1 |
Eq Bool | |
Ord Bool | |
Read Bool | Since: base-2.1 |
Show Bool | Since: base-2.1 |
Bits Bool | Interpret Since: base-4.7.0.0 |
Defined in Data.Bits (.&.) :: Bool -> Bool -> Bool # (.|.) :: Bool -> Bool -> Bool # complement :: Bool -> Bool # shift :: Bool -> Int -> Bool # rotate :: Bool -> Int -> Bool # setBit :: Bool -> Int -> Bool # clearBit :: Bool -> Int -> Bool # complementBit :: Bool -> Int -> Bool # testBit :: Bool -> Int -> Bool # bitSizeMaybe :: Bool -> Maybe Int # shiftL :: Bool -> Int -> Bool # unsafeShiftL :: Bool -> Int -> Bool # shiftR :: Bool -> Int -> Bool # unsafeShiftR :: Bool -> Int -> Bool # rotateL :: Bool -> Int -> Bool # | |
FiniteBits Bool | Since: base-4.7.0.0 |
Defined in Data.Bits | |
Default Bool Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Bool Source # | |
Mergeable Bool Source # | |
Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.
Instances
Eq Double | Note that due to the presence of
Also note that
|
Floating Double | Since: base-2.1 |
Ord Double | Note that due to the presence of
Also note that, due to the same,
|
Read Double | Since: base-2.1 |
RealFloat Double | Since: base-2.1 |
Defined in GHC.Float floatRadix :: Double -> Integer # floatDigits :: Double -> Int # floatRange :: Double -> (Int, Int) # decodeFloat :: Double -> (Integer, Int) # encodeFloat :: Integer -> Int -> Double # significand :: Double -> Double # scaleFloat :: Int -> Double -> Double # isInfinite :: Double -> Bool # isDenormalized :: Double -> Bool # isNegativeZero :: Double -> Bool # | |
Default Double Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Double Source # | |
Mergeable Double Source # | |
Foldable (UDouble :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => UDouble m -> m # foldMap :: Monoid m => (a -> m) -> UDouble a -> m # foldMap' :: Monoid m => (a -> m) -> UDouble a -> m # foldr :: (a -> b -> b) -> b -> UDouble a -> b # foldr' :: (a -> b -> b) -> b -> UDouble a -> b # foldl :: (b -> a -> b) -> b -> UDouble a -> b # foldl' :: (b -> a -> b) -> b -> UDouble a -> b # foldr1 :: (a -> a -> a) -> UDouble a -> a # foldl1 :: (a -> a -> a) -> UDouble a -> a # elem :: Eq a => a -> UDouble a -> Bool # maximum :: Ord a => UDouble a -> a # minimum :: Ord a => UDouble a -> a # | |
Traversable (UDouble :: Type -> Type) | Since: base-4.9.0.0 |
Single-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE single-precision type.
Instances
Eq Float | Note that due to the presence of
Also note that
|
Floating Float | Since: base-2.1 |
Ord Float | Note that due to the presence of
Also note that, due to the same,
|
Read Float | Since: base-2.1 |
RealFloat Float | Since: base-2.1 |
Defined in GHC.Float floatRadix :: Float -> Integer # floatDigits :: Float -> Int # floatRange :: Float -> (Int, Int) # decodeFloat :: Float -> (Integer, Int) # encodeFloat :: Integer -> Int -> Float # significand :: Float -> Float # scaleFloat :: Int -> Float -> Float # isInfinite :: Float -> Bool # isDenormalized :: Float -> Bool # isNegativeZero :: Float -> Bool # | |
Default Float Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Float Source # | |
Mergeable Float Source # | |
Foldable (UFloat :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => UFloat m -> m # foldMap :: Monoid m => (a -> m) -> UFloat a -> m # foldMap' :: Monoid m => (a -> m) -> UFloat a -> m # foldr :: (a -> b -> b) -> b -> UFloat a -> b # foldr' :: (a -> b -> b) -> b -> UFloat a -> b # foldl :: (b -> a -> b) -> b -> UFloat a -> b # foldl' :: (b -> a -> b) -> b -> UFloat a -> b # foldr1 :: (a -> a -> a) -> UFloat a -> a # foldl1 :: (a -> a -> a) -> UFloat a -> a # elem :: Eq a => a -> UFloat a -> Bool # maximum :: Ord a => UFloat a -> a # minimum :: Ord a => UFloat a -> a # | |
Traversable (UFloat :: Type -> Type) | Since: base-4.9.0.0 |
32-bit signed integer type
Instances
64-bit signed integer type
Instances
The Maybe
type encapsulates an optional value. A value of type
either contains a value of type Maybe
aa
(represented as
),
or it is empty (represented as Just
aNothing
). Using Maybe
is a good way to
deal with errors or exceptional cases without resorting to drastic
measures such as error
.
The Maybe
type is also a monad. It is a simple kind of error
monad, where all errors are represented by Nothing
. A richer
error monad can be built using the Either
type.
Instances
Monad Maybe | Since: base-2.1 |
Functor Maybe | Since: base-2.1 |
MonadFail Maybe | Since: base-4.9.0.0 |
Defined in Control.Monad.Fail | |
Applicative Maybe | Since: base-2.1 |
Foldable Maybe | Since: base-2.1 |
Defined in Data.Foldable fold :: Monoid m => Maybe m -> m # foldMap :: Monoid m => (a -> m) -> Maybe a -> m # foldMap' :: Monoid m => (a -> m) -> Maybe a -> m # foldr :: (a -> b -> b) -> b -> Maybe a -> b # foldr' :: (a -> b -> b) -> b -> Maybe a -> b # foldl :: (b -> a -> b) -> b -> Maybe a -> b # foldl' :: (b -> a -> b) -> b -> Maybe a -> b # foldr1 :: (a -> a -> a) -> Maybe a -> a # foldl1 :: (a -> a -> a) -> Maybe a -> a # elem :: Eq a => a -> Maybe a -> Bool # maximum :: Ord a => Maybe a -> a # minimum :: Ord a => Maybe a -> a # | |
Traversable Maybe | Since: base-2.1 |
Alternative Maybe | Since: base-2.1 |
MonadPlus Maybe | Since: base-2.1 |
Eq a => Eq (Maybe a) | Since: base-2.1 |
Ord a => Ord (Maybe a) | Since: base-2.1 |
Read a => Read (Maybe a) | Since: base-2.1 |
Show a => Show (Maybe a) | Since: base-2.1 |
Semigroup a => Semigroup (Maybe a) | Since: base-4.9.0.0 |
Semigroup a => Monoid (Maybe a) | Lift a semigroup into Since 4.11.0: constraint on inner Since: base-2.1 |
Default (Maybe a) Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Maybe a Source # | |
Mergeable a => Mergeable (Maybe a) Source # | |
32-bit unsigned integer type
Instances
64-bit unsigned integer type
Instances
data ByteString #
A space-efficient representation of a Word8
vector, supporting many
efficient operations.
A lazy ByteString
contains 8-bit bytes, or by using the operations
from Data.ByteString.Lazy.Char8 it can be interpreted as containing
8-bit characters.
Instances
General-purpose finite sequences.
Instances
Monad Seq | |
Functor Seq | |
MonadFix Seq | Since: containers-0.5.11 |
Defined in Data.Sequence.Internal | |
Applicative Seq | Since: containers-0.5.4 |
Foldable Seq | |
Defined in Data.Sequence.Internal fold :: Monoid m => Seq m -> m # foldMap :: Monoid m => (a -> m) -> Seq a -> m # foldMap' :: Monoid m => (a -> m) -> Seq a -> m # foldr :: (a -> b -> b) -> b -> Seq a -> b # foldr' :: (a -> b -> b) -> b -> Seq a -> b # foldl :: (b -> a -> b) -> b -> Seq a -> b # foldl' :: (b -> a -> b) -> b -> Seq a -> b # foldr1 :: (a -> a -> a) -> Seq a -> a # foldl1 :: (a -> a -> a) -> Seq a -> a # elem :: Eq a => a -> Seq a -> Bool # maximum :: Ord a => Seq a -> a # | |
Traversable Seq | |
Eq1 Seq | Since: containers-0.5.9 |
Ord1 Seq | Since: containers-0.5.9 |
Defined in Data.Sequence.Internal | |
Read1 Seq | Since: containers-0.5.9 |
Defined in Data.Sequence.Internal | |
Show1 Seq | Since: containers-0.5.9 |
MonadZip Seq |
|
Alternative Seq | Since: containers-0.5.4 |
MonadPlus Seq | |
UnzipWith Seq | |
Defined in Data.Sequence.Internal unzipWith' :: (x -> (a, b)) -> Seq x -> (Seq a, Seq b) | |
IsList (Seq a) | |
Eq a => Eq (Seq a) | |
Data a => Data (Seq a) | |
Defined in Data.Sequence.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Seq a -> c (Seq a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Seq a) # dataTypeOf :: Seq a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Seq a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Seq a)) # gmapT :: (forall b. Data b => b -> b) -> Seq a -> Seq a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r # gmapQ :: (forall d. Data d => d -> u) -> Seq a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Seq a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) # | |
Ord a => Ord (Seq a) | |
Read a => Read (Seq a) | |
Show a => Show (Seq a) | |
a ~ Char => IsString (Seq a) | Since: containers-0.5.7 |
Defined in Data.Sequence.Internal fromString :: String -> Seq a # | |
Semigroup (Seq a) | Since: containers-0.5.7 |
Monoid (Seq a) | |
NFData a => NFData (Seq a) | |
Defined in Data.Sequence.Internal | |
Default (Seq a) Source # | |
Defined in Data.ProtoBuf.Default defaultVal :: Seq a Source # | |
Mergeable (Seq a) Source # | |
type Item (Seq a) | |
Defined in Data.Sequence.Internal |
fromList :: Ord a => [a] -> Set a #
O(n*log n). Create a set from a list of elements.
If the elements are ordered, a linear-time implementation is used,
with the performance equal to fromDistinctAscList
.