Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Existential wrapper over Value
type and matching functions.
Synopsis
- data AnyValue = AnyValue (Value t)
- reifyAnyValues :: Value t -> [AnyValue] -> Either TypeMismatchError [Value t]
- toMArray :: [AnyValue] -> Either MatchError (Value TArray)
- data MatchError = MatchError {}
- mkMatchError :: TValue -> Value t -> Either MatchError a
- matchBool :: Value t -> Either MatchError Bool
- matchInteger :: Value t -> Either MatchError Integer
- matchDouble :: Value t -> Either MatchError Double
- matchText :: Value t -> Either MatchError Text
- matchZoned :: Value t -> Either MatchError ZonedTime
- matchLocal :: Value t -> Either MatchError LocalTime
- matchDay :: Value t -> Either MatchError Day
- matchHours :: Value t -> Either MatchError TimeOfDay
- matchArray :: (AnyValue -> Either MatchError a) -> Value t -> Either MatchError [a]
- applyAsToAny :: (AnyValue -> r) -> Value t -> r
Documentation
Existential wrapper for Value
.
reifyAnyValues :: Value t -> [AnyValue] -> Either TypeMismatchError [Value t] Source #
Matching
data MatchError Source #
Value type mismatch error.
Instances
Eq MatchError Source # | |
Defined in Toml.Type.AnyValue (==) :: MatchError -> MatchError -> Bool # (/=) :: MatchError -> MatchError -> Bool # | |
Show MatchError Source # | |
Defined in Toml.Type.AnyValue showsPrec :: Int -> MatchError -> ShowS # show :: MatchError -> String # showList :: [MatchError] -> ShowS # | |
Generic MatchError Source # | |
Defined in Toml.Type.AnyValue type Rep MatchError :: Type -> Type # from :: MatchError -> Rep MatchError x # to :: Rep MatchError x -> MatchError # | |
NFData MatchError Source # | |
Defined in Toml.Type.AnyValue rnf :: MatchError -> () # | |
type Rep MatchError Source # | |
Defined in Toml.Type.AnyValue type Rep MatchError = D1 (MetaData "MatchError" "Toml.Type.AnyValue" "tomland-1.0.0-inplace" False) (C1 (MetaCons "MatchError" PrefixI True) (S1 (MetaSel (Just "valueExpected") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TValue) :*: S1 (MetaSel (Just "valueActual") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AnyValue))) |
mkMatchError :: TValue -> Value t -> Either MatchError a Source #
Helper function to create MatchError
.
matchInteger :: Value t -> Either MatchError Integer Source #
matchDouble :: Value t -> Either MatchError Double Source #
matchZoned :: Value t -> Either MatchError ZonedTime Source #
matchLocal :: Value t -> Either MatchError LocalTime Source #
matchHours :: Value t -> Either MatchError TimeOfDay Source #
matchArray :: (AnyValue -> Either MatchError a) -> Value t -> Either MatchError [a] Source #
Extract list of elements of type a
from array.