vt-utils-1.3.0.0: Vector and Text utilities

Safe HaskellNone
LanguageHaskell2010

VtUtils.JSON

Description

JSON utilities

Example of the data type, that supports JSON encoding and decoding with Aeson:

  data Foo = Foo
      { foo :: Int
      , bar :: Text
      } deriving Generic
  instance FromJSON Foo
  instance ToJSON Foo
Synopsis

Documentation

jsonDecodeFile :: forall a. FromJSON a => Text -> IO a Source #

Parses contents of a specified JSON file into a typed data

Data type should be specified with a type annotation:

Example:

dt <- jsonDecodeFile "path/to/foo.json" :: IO Foo

Data must be an instance of FromJSON

File contents are decoded as UTF-8

Throws an exception if file cannot be read or data cannot be decoded

Arguments:

  • path :: Text: Path to JSON file

Return value: Decoded data

data JSONDecodeError Source #

Error for jsonDecodeText function

Constructors

JSONDecodeError 

Fields

jsonDecodeText :: forall a. FromJSON a => Text -> Either JSONDecodeError a Source #

Parses a JSON Text string into a typed data

Data type should be specified with a type annotation:

Example:

let Right (dt :: Foo) = jsonDecodeText text

Data must be an instance of FromJSON

Returns an error if data cannot be decoded

Arguments:

  • text :: Text: JSON Text string to parse

Return value: Decoded data or decoding error

jsonEncodeText :: ToJSON a => a -> Text Source #

Encodes a data into a JSON Text string

Data must be an instance of ToJSON

Arguments:

  • data :: ToJSON: some data that supports JSON serialization with Aeson

Return value: JSON Text string

data JSONGetError Source #

Error for jsonGet function

Instances
Show JSONGetError Source # 
Instance details

Defined in VtUtils.JSON

jsonGet :: forall a. FromJSON a => Value -> Text -> Either JSONGetError a Source #

Extract the field value from the specified JSON object

Returns an error, if specified JSON Value is not a JSON object, if it does't contain a specified field, if field type is different from the one specified in type annotation

Data type should be specified with a type annotation:

let obj = object
        [ "foo" .= (42 :: Int)
        , "bar" .= ("baz" :: Text)
        ]
let Right (fooval :: Int) = jsonGet obj "foo"
let Right (barval :: Text) = jsonGet obj "bar"

Arguments:

  • val :: Aeson.Value: JSON value, must be a JSON object
  • field :: Text: Field name

Return value: Field value or an error

jsonUnwrapUnaryOptions :: Options Source #

JSON options with unwrapUnaryRecords flag flipped to True