ghcjs-base-0.2.0.0: base library for GHCJS

Safe HaskellNone
LanguageHaskell98

JavaScript.JSON.Types.Internal

Contents

Synopsis

Core JSON types

newtype SomeValue (m :: MutabilityType s) Source #

Constructors

SomeValue JSVal 
Instances
FromJSON Value Source # 
Instance details

Defined in JavaScript.JSON.Types.Instances

ToJSON Value Source # 
Instance details

Defined in JavaScript.JSON.Types.Instances

Methods

toJSON :: Value -> Value Source #

Lookup Int Value Source # 
Instance details

Defined in JavaScript.JSON.Types.Internal

Methods

(!) :: Int -> Value -> Value Source #

lookup :: Int -> Value -> Maybe Value Source #

Lookup JSString Value Source # 
Instance details

Defined in JavaScript.JSON.Types.Internal

NFData (SomeValue m) Source # 
Instance details

Defined in JavaScript.JSON.Types.Internal

Methods

rnf :: SomeValue m -> ()

m ~ Immutable => ResponseType (SomeValue m) Source # 
Instance details

Defined in JavaScript.Web.XMLHttpRequest

type Value = SomeValue Immutable Source #

data SomeValue' (m :: MutabilityType s) Source #

Constructors

Object !(SomeObject m) 
Array !(SomeJSArray m) 
String !JSString 
Number !Double 
Bool !Bool 
Null 

type Value' = SomeValue' Immutable Source #

type Object = SomeObject Immutable Source #

type MutableObject = SomeObject Mutable Source #

objectPropertiesIO :: SomeObject o -> IO JSArray Source #

objectAssocsIO :: SomeObject m -> IO [(JSString, Value)] Source #

class Lookup k a where Source #

Minimal complete definition

(!), lookup

Methods

(!) Source #

Arguments

:: k 
-> a 
-> Value

throws when result is not a JSON value

lookup Source #

Arguments

:: k 
-> a 
-> Maybe Value

returns Nothing when result is not a JSON value fixme more optimized matching lookup' :: k -> a -> Maybe Value' -- ^ returns Nothing when result is not a JSON value

class IOLookup k a where Source #

Minimal complete definition

(^!), lookupIO, lookupIO'

Methods

(^!) Source #

Arguments

:: k 
-> a 
-> IO MutableValue

throws when result is not a JSON value

lookupIO Source #

Arguments

:: k 
-> a 
-> IO (Maybe MutableValue)

returns Nothing when result is not a JSON value

lookupIO' Source #

Arguments

:: k 
-> a 
-> IO (Maybe MutableValue')

returns Nothing when result is not a JSON value

Type conversion

data Parser a #

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.

Instances
Monad Parser 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

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

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

return :: a -> Parser a #

fail :: String -> Parser a #

Functor Parser 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

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

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

MonadFail Parser 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

fail :: String -> Parser a

Applicative Parser 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

pure :: a -> Parser a #

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

liftA2 :: (a -> b -> c) -> Parser a -> Parser b -> Parser c

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

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

Alternative Parser 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

empty :: Parser a

(<|>) :: Parser a -> Parser a -> Parser a

some :: Parser a -> Parser [a]

many :: Parser a -> Parser [a]

MonadPlus Parser 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

mzero :: Parser a #

mplus :: Parser a -> Parser a -> Parser a #

Semigroup (Parser a) 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

(<>) :: Parser a -> Parser a -> Parser a #

sconcat :: NonEmpty (Parser a) -> Parser a #

stimes :: Integral b => b -> Parser a -> Parser a #

Monoid (Parser a) 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

mempty :: Parser a #

mappend :: Parser a -> Parser a -> Parser a #

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

data Result a #

The result of running a Parser.

Constructors

Error String 
Success a 
Instances
Monad Result 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

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

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

return :: a -> Result a #

fail :: String -> Result a #

Functor Result 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

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

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

MonadFail Result 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

fail :: String -> Result a

Applicative Result 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

pure :: a -> Result a #

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

liftA2 :: (a -> b -> c) -> Result a -> Result b -> Result c

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

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

Foldable Result 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

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 #

toList :: Result a -> [a]

null :: Result a -> Bool #

length :: Result a -> Int #

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

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

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

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

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

Traversable Result 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

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

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

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

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

Alternative Result 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

empty :: Result a

(<|>) :: Result a -> Result a -> Result a

some :: Result a -> Result [a]

many :: Result a -> Result [a]

MonadPlus Result 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

mzero :: Result a #

mplus :: Result a -> Result a -> Result a #

Eq a => Eq (Result a) 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

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

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

Show a => Show (Result a) 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

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

show :: Result a -> String #

showList :: [Result a] -> ShowS #

Semigroup (Result a) 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

(<>) :: Result a -> Result a -> Result a #

sconcat :: NonEmpty (Result a) -> Result a #

stimes :: Integral b => b -> Result a -> Result a #

Monoid (Result a) 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

mempty :: Result a #

mappend :: Result a -> Result a -> Result a #

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

NFData a => NFData (Result a) 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

rnf :: Result a -> ()

parse :: (a -> Parser b) -> a -> Result b #

Run a Parser.

parseEither :: (a -> Parser b) -> a -> Either String b #

Run a Parser with an Either result type. If the parse fails, the Left payload will contain an error message.

parseMaybe :: (a -> Parser b) -> a -> Maybe b #

Run a Parser with a Maybe result type.

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

data Options #

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.

Instances
Show Options 
Instance details

Defined in Data.Aeson.Types.Internal

data SumEncoding #

Specifies how to encode constructors of a sum datatype.

Constructors

TaggedObject

A constructor will be encoded to an object with a field tagFieldName which specifies the constructor tag (modified by the constructorTagModifier). If the constructor is a record the encoded record fields will be unpacked into this object. So make sure that your record doesn't have a field with the same label as the tagFieldName. Otherwise the tag gets overwritten by the encoded value of that field! If the constructor is not a record the encoded constructor contents will be stored under the contentsFieldName 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 constructorTagModifier). Having a nullary constructor alongside a single field constructor that encodes to a string leads to ambiguity.

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 constructorTagModifier) which maps to the encoded contents of the constructor.

TwoElemArray

A constructor will be encoded to a 2-element array where the first element is the tag of the constructor (modified by the constructorTagModifier) and the second element the encoded contents of the constructor.

Instances
Eq SumEncoding 
Instance details

Defined in Data.Aeson.Types.Internal

Show SumEncoding 
Instance details

Defined in Data.Aeson.Types.Internal

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.

Constructors

DotNetTime 

Fields

Instances
Eq DotNetTime 
Instance details

Defined in Data.Aeson.Types.Internal

Ord DotNetTime 
Instance details

Defined in Data.Aeson.Types.Internal

Read DotNetTime 
Instance details

Defined in Data.Aeson.Types.Internal

Show DotNetTime 
Instance details

Defined in Data.Aeson.Types.Internal

ToJSON DotNetTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

FormatTime DotNetTime 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

formatCharacter :: Char -> Maybe (TimeLocale -> Maybe NumericPadOption -> Maybe Int -> DotNetTime -> String)

FromJSON DotNetTime Source # 
Instance details

Defined in JavaScript.JSON.Types.Instances

ToJSON DotNetTime Source # 
Instance details

Defined in JavaScript.JSON.Types.Instances