Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- decodeYaml :: FilePath -> IO (Either String ([String], Value))
- decodeYamlWithParseError :: FilePath -> IO (Either ParseException ([String], Value))
- data ParseException
- formatYamlParseError :: FilePath -> ParseException -> String
- formatWarning :: FilePath -> Warning -> String
- class FromValue a where
- data Parser a
- type Result a = Either String (a, [String], [(String, String)])
- decodeValue :: FromValue a => Value -> Result a
- class Generic a
- class GenericDecode f
- genericFromValue :: forall a d m. (Generic a, Rep a ~ D1 d m, Datatype d, GenericDecode (Rep a)) => Value -> Parser a
- data Options = Options {}
- genericFromValueWith :: (Generic a, GenericDecode (Rep a)) => Options -> Value -> Parser a
- typeMismatch :: String -> Value -> Parser a
- withObject :: (Object -> Parser a) -> Value -> Parser a
- withText :: (Text -> Parser a) -> Value -> Parser a
- withString :: (String -> Parser a) -> Value -> Parser a
- withArray :: (Array -> Parser a) -> Value -> Parser a
- withNumber :: (Scientific -> Parser a) -> Value -> Parser a
- withBool :: (Bool -> Parser a) -> Value -> Parser a
- parseArray :: (Value -> Parser a) -> Array -> Parser [a]
- traverseObject :: (Value -> Parser a) -> Object -> Parser [(Key, a)]
- (.:) :: FromValue a => Object -> Key -> Parser a
- (.:?) :: FromValue a => Object -> Key -> Parser (Maybe a)
- data Key
- data Value
- type Object = KeyMap Value
- type Array = Vector Value
- newtype Alias (deprecated :: Bool) (alias :: Symbol) a = Alias a
- unAlias :: Alias deprecated alias a -> a
Documentation
NOTE: This module is exposed to allow integration of Hpack into other tools. It is not meant for general use by end users. The following caveats apply:
- The API is undocumented, consult the source instead.
- The exposed types and functions primarily serve Hpack's own needs, not that of a public API. Breaking changes can happen as Hpack evolves.
As an Hpack user you either want to use the hpack
executable or a build
tool that supports Hpack (e.g. stack
or cabal2nix
).
decodeYamlWithParseError :: FilePath -> IO (Either ParseException ([String], Value)) Source #
data ParseException #
Instances
Exception ParseException | |
Defined in Data.Yaml.Internal | |
Show ParseException | |
Defined in Data.Yaml.Internal showsPrec :: Int -> ParseException -> ShowS # show :: ParseException -> String # showList :: [ParseException] -> ShowS # |
formatYamlParseError :: FilePath -> ParseException -> String Source #
class FromValue a where Source #
Nothing
Instances
FromValue BuildType Source # | |
FromValue Cond Source # | |
FromValue Language Source # | |
FromValue Verbatim Source # | |
FromValue VerbatimValue Source # | |
Defined in Hpack.Config | |
FromValue Module Source # | |
FromValue SystemBuildTools Source # | |
Defined in Hpack.Syntax.BuildTools | |
FromValue Dependencies Source # | |
Defined in Hpack.Syntax.Dependencies | |
FromValue VersionConstraint Source # | |
Defined in Hpack.Syntax.DependencyVersion | |
FromValue Text Source # | |
FromValue String Source # | |
FromValue Bool Source # | |
FromValue Int Source # | |
FromValue a => FromValue (Maybe a) Source # | |
FromValue a => FromValue [a] Source # | |
(FromValue a, FromValue b) => FromValue (Either a b) Source # | |
FromValue a => FromValue (Map String a) Source # | |
(FromValue a, FromValue b) => FromValue (a, b) Source # | |
Representable types of kind *
.
This class is derivable in GHC with the DeriveGeneric
flag on.
A Generic
instance must satisfy the following laws:
from
.to
≡id
to
.from
≡id
Instances
class GenericDecode f Source #
genericDecode
Instances
(GenericDecode a, GenericDecode b) => GenericDecode (a :*: b) Source # | |
Defined in Data.Aeson.Config.FromValue genericDecode :: Options -> Value -> Parser ((a :*: b) p) | |
GenericDecode a => GenericDecode (C1 c a) Source # | |
Defined in Data.Aeson.Config.FromValue genericDecode :: Options -> Value -> Parser (C1 c a p) | |
GenericDecode a => GenericDecode (D1 d a) Source # | |
Defined in Data.Aeson.Config.FromValue genericDecode :: Options -> Value -> Parser (D1 d a p) |
genericFromValue :: forall a d m. (Generic a, Rep a ~ D1 d m, Datatype d, GenericDecode (Rep a)) => Value -> Parser a Source #
genericFromValueWith :: (Generic a, GenericDecode (Rep a)) => Options -> Value -> Parser a Source #
withNumber :: (Scientific -> Parser a) -> Value -> Parser a Source #
Instances
Arbitrary Key | Since: aeson-2.0.3.0 |
CoArbitrary Key | Since: aeson-2.0.3.0 |
Defined in Data.Aeson.Key coarbitrary :: Key -> Gen b -> Gen b # | |
Function Key | Since: aeson-2.0.3.0 |
FromJSON Key | |
FromJSONKey Key | |
Defined in Data.Aeson.Types.FromJSON | |
ToJSON Key | |
Defined in Data.Aeson.Types.ToJSON | |
ToJSONKey Key | |
Defined in Data.Aeson.Types.ToJSON | |
Data Key | |
Defined in Data.Aeson.Key gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Key -> c Key # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Key # dataTypeOf :: Key -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Key) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Key) # gmapT :: (forall b. Data b => b -> b) -> Key -> Key # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r # gmapQ :: (forall d. Data d => d -> u) -> Key -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Key -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Key -> m Key # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Key -> m Key # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Key -> m Key # | |
IsString Key | |
Defined in Data.Aeson.Key fromString :: String -> Key # | |
Monoid Key | |
Semigroup Key | |
Read Key | |
Show Key | |
NFData Key | |
Defined in Data.Aeson.Key | |
Eq Key | |
Ord Key | |
Hashable Key | |
Defined in Data.Aeson.Key | |
FoldableWithIndex Key KeyMap | |
Defined in Data.Aeson.KeyMap | |
FunctorWithIndex Key KeyMap | |
TraversableWithIndex Key KeyMap | |
Defined in Data.Aeson.KeyMap | |
SemialignWithIndex Key KeyMap | |
Defined in Data.Aeson.KeyMap | |
ZipWithIndex Key KeyMap | |
Lift Key | |
FilterableWithIndex Key KeyMap | |
WitherableWithIndex Key KeyMap | |
FromPairs Value (DList Pair) | |
Defined in Data.Aeson.Types.ToJSON | |
v ~ Value => KeyValuePair v (DList Pair) | |
Defined in Data.Aeson.Types.ToJSON |
A JSON value represented as a Haskell value.
Instances
Arbitrary Value | Since: aeson-2.0.3.0 |
CoArbitrary Value | Since: aeson-2.0.3.0 |
Defined in Data.Aeson.Types.Internal coarbitrary :: Value -> Gen b -> Gen b # | |
Function Value | Since: aeson-2.0.3.0 |
FromJSON Value | |
FromString Encoding | |
Defined in Data.Aeson.Types.ToJSON fromString :: String -> Encoding | |
FromString Value | |
Defined in Data.Aeson.Types.ToJSON fromString :: String -> Value | |
ToJSON Value | |
Defined in Data.Aeson.Types.ToJSON | |
Data Value | |
Defined in Data.Aeson.Types.Internal 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 # 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 :: forall r r'. (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 # | |
IsString Value | |
Defined in Data.Aeson.Types.Internal fromString :: String -> Value # | |
Generic Value | |
Read Value | |
Show Value | Since version 1.5.6.0 version object values are printed in lexicographic key order
|
NFData Value | |
Defined in Data.Aeson.Types.Internal | |
Eq Value | |
Ord Value | The ordering is total, consistent with Since: aeson-1.5.2.0 |
Hashable Value | |
Defined in Data.Aeson.Types.Internal | |
Lift Value | Since: aeson-0.11.0.0 |
(GToJSON' Encoding arity a, ConsToJSON Encoding arity a, Constructor c) => SumToJSON' TwoElemArray Encoding arity (C1 c a) | |
Defined in Data.Aeson.Types.ToJSON | |
(GToJSON' Value arity a, ConsToJSON Value arity a, Constructor c) => SumToJSON' TwoElemArray Value arity (C1 c a) | |
Defined in Data.Aeson.Types.ToJSON | |
GToJSON' Encoding arity (U1 :: TYPE LiftedRep -> Type) | |
GToJSON' Encoding arity (V1 :: TYPE LiftedRep -> Type) | |
GToJSON' Value arity (U1 :: TYPE LiftedRep -> Type) | |
GToJSON' Value arity (V1 :: TYPE LiftedRep -> Type) | |
ToJSON1 f => GToJSON' Encoding One (Rec1 f) | |
ToJSON1 f => GToJSON' Value One (Rec1 f) | |
(EncodeProduct arity a, EncodeProduct arity b) => GToJSON' Encoding arity (a :*: b) | |
ToJSON a => GToJSON' Encoding arity (K1 i a :: TYPE LiftedRep -> Type) | |
(WriteProduct arity a, WriteProduct arity b, ProductSize a, ProductSize b) => GToJSON' Value arity (a :*: b) | |
ToJSON a => GToJSON' Value arity (K1 i a :: TYPE LiftedRep -> Type) | |
(ToJSON1 f, GToJSON' Encoding One g) => GToJSON' Encoding One (f :.: g) | |
(ToJSON1 f, GToJSON' Value One g) => GToJSON' Value One (f :.: g) | |
FromPairs Value (DList Pair) | |
Defined in Data.Aeson.Types.ToJSON | |
v ~ Value => KeyValuePair v (DList Pair) | |
Defined in Data.Aeson.Types.ToJSON | |
type Rep Value | |
Defined in Data.Aeson.Types.Internal type Rep Value = D1 ('MetaData "Value" "Data.Aeson.Types.Internal" "aeson-2.1.2.1-HxqWYVrLN48IB6S2r9ccPm" 'False) ((C1 ('MetaCons "Object" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Object)) :+: (C1 ('MetaCons "Array" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Array)) :+: C1 ('MetaCons "String" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))) :+: (C1 ('MetaCons "Number" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Scientific)) :+: (C1 ('MetaCons "Bool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "Null" 'PrefixI 'False) (U1 :: Type -> Type)))) |
newtype Alias (deprecated :: Bool) (alias :: Symbol) a Source #
Alias a |