| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Text.Toml.Types
- type Table = HashMap Text Node
- emptyTable :: Table
- type VTArray = Vector Table
- type VArray = Vector Node
- data Node
- data Explicitness
- isExplicit :: Explicitness -> Bool
- insert :: Explicitness -> ([Text], Node) -> Table -> Parsec Text (Set [Text]) Table
- class ToJSON a where
- toJSON :: a -> Value
- toEncoding :: a -> Encoding
- class ToBsJSON a where
Documentation
Contruct an empty Table.
Constructors
| VTable !Table | |
| VTArray !VTArray | |
| VString !Text | |
| VInteger !Int64 | |
| VFloat !Double | |
| VBoolean !Bool | |
| VDatetime !UTCTime | |
| VArray !VArray |
Instances
| Eq Node Source | |
| Show Node Source | |
| ToJSON Node Source |
|
| ToBsJSON Node Source |
As seen in this function, BurntSushi's JSON encoding explicitly specifies the types of the values. |
data Explicitness Source
To mark whether or not a Table has been explicitly defined.
See: https://github.com/toml-lang/toml/issues/376
Instances
isExplicit :: Explicitness -> Bool Source
Convenience function to get a boolean value.
class ToJSON a where
A type that can be converted to JSON.
An example type and instance:
-- Allow ourselves to writeTextliterals. {-# LANGUAGE OverloadedStrings #-} data Coord = Coord { x :: Double, y :: Double } instance ToJSON Coord where toJSON (Coord x y) =object["x".=x, "y".=y] toEncoding (Coord x y) =pairs("x".=x<>"y".=y)
Instead of manually writing your ToJSON instance, there are two options
to do it automatically:
- Data.Aeson.TH provides Template Haskell functions which will derive an instance at compile time. The generated instance is optimized for your type so will probably be more efficient than the following two options:
- The compiler can provide a default generic implementation for
toJSON.
To use the second, simply add a deriving clause to your
datatype and declare a GenericToJSON instance for your datatype without giving
definitions for toJSON or toEncoding.
For example, the previous example can be simplified to a more minimal instance:
{-# LANGUAGE DeriveGeneric #-}
import GHC.Generics
data Coord = Coord { x :: Double, y :: Double } deriving Generic
instance ToJSON Coord where
toEncoding = genericToEncoding defaultOptions
Why do we provide an implementation for toEncoding here? The
toEncoding function is a relatively new addition to this class.
To allow users of older versions of this library to upgrade without
having to edit all of their instances or encounter surprising
incompatibilities, the default implementation of toEncoding uses
toJSON. This produces correct results, but since it performs an
intermediate conversion to a Value, it will be less efficient
than directly emitting an Encoding. Our one-liner definition of
toEncoding above bypasses the intermediate Value.
If DefaultSignatures doesn't give exactly the results you want,
you can customize the generic encoding with only a tiny amount of
effort, using genericToJSON and genericToEncoding with your
preferred Options:
instance ToJSON Coord where
toJSON = genericToJSON defaultOptions
toEncoding = genericToEncoding defaultOptions
Minimal complete definition
Nothing
Methods
Convert a Haskell value to a JSON-friendly intermediate type.
toEncoding :: a -> Encoding
Encode a Haskell value as JSON.
The default implementation of this method creates an
intermediate Value using toJSON. This provides
source-level compatibility for people upgrading from older
versions of this library, but obviously offers no performance
advantage.
To benefit from direct encoding, you must provide an
implementation for this method. The easiest way to do so is by
having your types implement Generic using the DeriveGeneric
extension, and then have GHC generate a method body as follows.
instance ToJSON Coord where
toEncoding = genericToEncoding defaultOptions
Type class for conversion to BurntSushi-style JSON.
BurntSushi has made a language agnostic test suite available that
this library uses. This test suit expects that values are encoded
as JSON objects with a 'type' and a value member.
Instances
| ToBsJSON Node Source |
As seen in this function, BurntSushi's JSON encoding explicitly specifies the types of the values. |
| ToBsJSON a => ToBsJSON (Vector a) Source | |
| ToBsJSON v => ToBsJSON (HashMap Text v) Source | Provide a |