Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- newtype SomeValue (m :: MutabilityType s) = SomeValue JSVal
- type Value = SomeValue Immutable
- type MutableValue = SomeValue Mutable
- data SomeValue' (m :: MutabilityType s)
- type Value' = SomeValue' Immutable
- type MutableValue' = SomeValue' Mutable
- type MutableValue = SomeValue Mutable
- type MutableValue' = SomeValue' Mutable
- emptyArray :: Value
- isEmptyArray :: Value -> Bool
- type Pair = (JSString, Value)
- type Object = SomeObject Immutable
- type MutableObject = SomeObject Mutable
- objectProperties :: Object -> JSArray
- objectPropertiesIO :: SomeObject o -> IO JSArray
- objectAssocs :: Object -> [(JSString, Value)]
- objectAssocsIO :: SomeObject m -> IO [(JSString, Value)]
- class Lookup k a where
- class IOLookup k a where
- emptyObject :: Object
- match :: SomeValue m -> SomeValue' m
- arrayValue :: JSArray -> Value
- stringValue :: JSString -> Value
- doubleValue :: Double -> Value
- nullValue :: Value
- boolValue :: Bool -> Value
- objectValue :: Object -> Value
- arrayValueList :: [Value] -> JSArray
- indexV :: JSArray -> Int -> Value
- data Parser a
- data Result a
- parse :: (a -> Parser b) -> a -> Result b
- parseEither :: (a -> Parser b) -> a -> Either String b
- parseMaybe :: (a -> Parser b) -> a -> Maybe b
- modifyFailure :: (String -> String) -> Parser a -> Parser a
- encode :: Value -> JSString
- object :: [Pair] -> Object
- data Options
- data SumEncoding
- defaultOptions :: Options
- defaultTaggedObject :: SumEncoding
- camelTo :: Char -> String -> String
- newtype DotNetTime = DotNetTime {
- fromDotNetTime :: UTCTime
Core JSON types
newtype SomeValue (m :: MutabilityType s) Source #
Instances
FromJSON Value Source # | |
ToJSON Value Source # | |
Lookup Int Value Source # | |
Lookup JSString Value Source # | |
NFData (SomeValue m) Source # | |
Defined in JavaScript.JSON.Types.Internal | |
m ~ Immutable => ResponseType (SomeValue m) Source # | |
Defined in JavaScript.Web.XMLHttpRequest getResponseTypeString :: Proxy (SomeValue m) -> JSString Source # wrapResponseType :: JSVal -> SomeValue m Source # |
type MutableValue = SomeValue Mutable Source #
data SomeValue' (m :: MutabilityType s) Source #
type Value' = SomeValue' Immutable Source #
type MutableValue' = SomeValue' Mutable Source #
type MutableValue = SomeValue Mutable Source #
type MutableValue' = SomeValue' Mutable Source #
emptyArray :: Value Source #
isEmptyArray :: Value -> Bool Source #
type MutableObject = SomeObject Mutable Source #
objectProperties :: Object -> JSArray Source #
objectPropertiesIO :: SomeObject o -> IO JSArray Source #
class Lookup k a where Source #
:: k | |
-> a | |
-> Value | throws when result is not a JSON value |
emptyObject :: Object Source #
match :: SomeValue m -> SomeValue' m Source #
arrayValue :: JSArray -> Value Source #
stringValue :: JSString -> Value Source #
doubleValue :: Double -> Value Source #
objectValue :: Object -> Value Source #
arrayValueList :: [Value] -> JSArray Source #
Type conversion
A JSON parser. N.B. This might not fit your usual understanding of
"parser". Instead you might like to think of Parser
as a "parse result",
i.e. a parser to which the input has already been applied.
The result of running a Parser
.
Instances
Monad Result | |
Functor Result | |
MonadFail Result | |
Defined in Data.Aeson.Types.Internal | |
Applicative Result | |
Foldable Result | |
Defined in Data.Aeson.Types.Internal fold :: Monoid m => Result m -> m foldMap :: Monoid m => (a -> m) -> Result a -> m # foldr :: (a -> b -> b) -> b -> Result a -> b # foldr' :: (a -> b -> b) -> b -> Result a -> b foldl :: (b -> a -> b) -> b -> Result a -> b # foldl' :: (b -> a -> b) -> b -> Result a -> b foldr1 :: (a -> a -> a) -> Result a -> a # foldl1 :: (a -> a -> a) -> Result a -> a # elem :: Eq a => a -> Result a -> Bool # maximum :: Ord a => Result a -> a # minimum :: Ord a => Result a -> a # | |
Traversable Result | |
Alternative Result | |
MonadPlus Result | |
Eq a => Eq (Result a) | |
Show a => Show (Result a) | |
Semigroup (Result a) | |
Monoid (Result a) | |
NFData a => NFData (Result a) | |
Defined in Data.Aeson.Types.Internal |
parseEither :: (a -> Parser b) -> a -> Either String b #
modifyFailure :: (String -> String) -> Parser a -> Parser a #
If the inner Parser
failed, modify the failure message using the
provided function. This allows you to create more descriptive error messages.
For example:
parseJSON (Object o) = modifyFailure ("Parsing of the Foo value failed: " ++) (Foo <$> o .: "someField")
Since 0.6.2.0
Constructors and accessors
Generic and TH encoding configuration
Options that specify how to encode/decode your datatype to/from JSON.
Options can be set using record syntax on defaultOptions
with the fields
below.
data SumEncoding #
Specifies how to encode constructors of a sum datatype.
TaggedObject | A constructor will be encoded to an object with a field
|
UntaggedValue | Constructor names won't be encoded. Instead only the contents of the constructor will be encoded as if the type had a single constructor. JSON encodings have to be disjoint for decoding to work properly. When decoding, constructors are tried in the order of definition. If some encodings overlap, the first one defined will succeed. Note: Nullary constructors are encoded as strings (using
Note: Only the last error is kept when decoding, so in the case of malformed JSON, only an error for the last constructor will be reported. |
ObjectWithSingleField | A constructor will be encoded to an object with a single
field named after the constructor tag (modified by the
|
TwoElemArray | A constructor will be encoded to a 2-element array where the
first element is the tag of the constructor (modified by the
|
Instances
Eq SumEncoding | |
Defined in Data.Aeson.Types.Internal (==) :: SumEncoding -> SumEncoding -> Bool # (/=) :: SumEncoding -> SumEncoding -> Bool # | |
Show SumEncoding | |
Defined in Data.Aeson.Types.Internal showsPrec :: Int -> SumEncoding -> ShowS # show :: SumEncoding -> String # showList :: [SumEncoding] -> ShowS # |
Default encoding Options
:
Options
{fieldLabelModifier
= id ,constructorTagModifier
= id ,allNullaryToStringTag
= True ,omitNothingFields
= False ,sumEncoding
=defaultTaggedObject
,unwrapUnaryRecords
= False ,tagSingleConstructors
= False }
defaultTaggedObject :: SumEncoding #
Default TaggedObject
SumEncoding
options:
defaultTaggedObject =TaggedObject
{tagFieldName
= "tag" ,contentsFieldName
= "contents" }
Used for changing CamelCase names into something else.
camelTo :: Char -> String -> String #
Converts from CamelCase to another lower case, interspersing
the character between all capital letters and their previous
entries, except those capital letters that appear together,
like API
.
For use by Aeson template haskell calls.
camelTo '_' 'CamelCaseAPI' == "camel_case_api"
Other types
newtype DotNetTime #
A newtype wrapper for UTCTime
that uses the same non-standard
serialization format as Microsoft .NET, whose
System.DateTime
type is by default serialized to JSON as in the following example:
/Date(1302547608878)/
The number represents milliseconds since the Unix epoch.
DotNetTime | |
|