-
Notifications
You must be signed in to change notification settings - Fork 2
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Adds mechanism for converting Fleece schemas to Aeson Values
This allows for the use of Fleece schemas in defining `ToJSON` instances.
- Loading branch information
Showing
5 changed files
with
192 additions
and
4 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,186 @@ | ||
{-# LANGUAGE DataKinds #-} | ||
{-# LANGUAGE InstanceSigs #-} | ||
{-# LANGUAGE RankNTypes #-} | ||
{-# LANGUAGE ScopedTypeVariables #-} | ||
{-# LANGUAGE TypeApplications #-} | ||
{-# LANGUAGE TypeFamilies #-} | ||
{-# LANGUAGE TypeOperators #-} | ||
|
||
module Fleece.Aeson.ToValue | ||
( FleeceToJSON (..) | ||
, fleeceToJSON | ||
) where | ||
|
||
import qualified Data.Aeson as Aeson | ||
import qualified Data.Aeson.Key as AesonKey | ||
import qualified Data.Aeson.Types as AesonTypes | ||
import qualified Data.ByteString.Lazy as LBS | ||
import Data.Coerce (coerce) | ||
import qualified Data.Map.Strict as Map | ||
import qualified Data.Text as T | ||
import qualified Data.Text.Encoding as Enc | ||
import GHC.TypeLits (KnownSymbol, symbolVal) | ||
import Shrubbery (type (@=)) | ||
import qualified Shrubbery | ||
|
||
import qualified Fleece.Core as FC | ||
|
||
fleeceToJSON :: FleeceToJSON a -> a -> Aeson.Value | ||
fleeceToJSON (FleeceToJSON _name f) = | ||
f | ||
|
||
data FleeceToJSON a | ||
= FleeceToJSON FC.Name (a -> Aeson.Value) | ||
|
||
instance FC.Fleece FleeceToJSON where | ||
newtype Object FleeceToJSON object _constructor | ||
= Object (object -> [AesonTypes.Pair]) | ||
|
||
newtype Field FleeceToJSON object _a | ||
= Field (object -> [AesonTypes.Pair]) | ||
|
||
newtype AdditionalFields FleeceToJSON object _a | ||
= AdditionalFields (object -> [AesonTypes.Pair]) | ||
|
||
newtype UnionMembers FleeceToJSON _allTypes handledTypes | ||
= UnionMembers (Shrubbery.BranchBuilder handledTypes Aeson.Value) | ||
|
||
newtype TaggedUnionMembers FleeceToJSON _allTypes handledTypes | ||
= TaggedUnionMembers (Shrubbery.TaggedBranchBuilder handledTypes (T.Text, [AesonTypes.Pair])) | ||
|
||
schemaName (FleeceToJSON name _toJSON) = | ||
name | ||
|
||
number = | ||
FleeceToJSON (FC.unqualifiedName "number") Aeson.toJSON | ||
|
||
text = | ||
FleeceToJSON (FC.unqualifiedName "text") Aeson.toJSON | ||
|
||
boolean = | ||
FleeceToJSON (FC.unqualifiedName "boolean") Aeson.toJSON | ||
|
||
null = | ||
FleeceToJSON | ||
(FC.unqualifiedName "null") | ||
(\FC.Null -> Aeson.Null) | ||
|
||
array (FleeceToJSON name itemToJSON) = | ||
FleeceToJSON | ||
(FC.annotateName name "array") | ||
(Aeson.Array . fmap itemToJSON) | ||
|
||
nullable (FleeceToJSON name toJSON) = | ||
FleeceToJSON (FC.annotateName name "nullable") $ \mbValue -> | ||
case mbValue of | ||
Left FC.Null -> Aeson.Null | ||
Right value -> toJSON value | ||
|
||
required name accessor (FleeceToJSON _name toJSON) = | ||
let | ||
key = AesonKey.fromString name | ||
in | ||
Field $ \object -> | ||
[(key, toJSON (accessor object))] | ||
|
||
optional name accessor (FleeceToJSON _name toJSON) = | ||
let | ||
key = AesonKey.fromString name | ||
in | ||
Field $ \object -> | ||
case accessor object of | ||
Just value -> | ||
[(key, toJSON value)] | ||
Nothing -> | ||
[] | ||
|
||
additionalFields accessor (FleeceToJSON _name toJSON) = | ||
AdditionalFields $ \object -> | ||
map (\(key, value) -> (AesonKey.fromText key, toJSON value)) | ||
. Map.toList | ||
. accessor | ||
$ object | ||
|
||
mapField _f encoder = | ||
coerce encoder | ||
|
||
constructor _f = | ||
Object (\_ -> mempty) | ||
|
||
field (Object mkStart) (Field mkNext) = | ||
Object $ \object -> | ||
mkStart object <> mkNext object | ||
|
||
additional (Object mkStart) (AdditionalFields mkRest) = | ||
Object $ \object -> | ||
mkStart object <> mkRest object | ||
|
||
objectNamed name (Object toObject) = | ||
FleeceToJSON name (Aeson.object . toObject) | ||
|
||
boundedEnumNamed name toText = | ||
FleeceToJSON name (Aeson.toJSON . toText) | ||
|
||
validateNamed name uncheck _check (FleeceToJSON _unvalidatedName toJSON) = | ||
FleeceToJSON name (toJSON . uncheck) | ||
|
||
unionNamed name (UnionMembers builder) = | ||
let | ||
branches = | ||
Shrubbery.branchBuild builder | ||
in | ||
FleeceToJSON name (Shrubbery.dissectUnion branches) | ||
|
||
unionMemberWithIndex _index encoder = | ||
UnionMembers $ | ||
let | ||
-- It's important that this let is _inside_ the 'UnionMembers' | ||
-- constructor so that it lazy enough to allow the recursive reference | ||
-- of 'anyJSON' to itself within arrays. | ||
FleeceToJSON _name toJSON = encoder | ||
in | ||
Shrubbery.singleBranch toJSON | ||
|
||
unionCombine (UnionMembers left) (UnionMembers right) = | ||
UnionMembers (Shrubbery.appendBranches left right) | ||
|
||
taggedUnionNamed name tagProperty (TaggedUnionMembers builder) = | ||
let | ||
branches = | ||
Shrubbery.taggedBranchBuild builder | ||
|
||
tagKey = | ||
AesonKey.fromString tagProperty | ||
in | ||
FleeceToJSON name $ \value -> | ||
let | ||
(tagValue, fields) = | ||
Shrubbery.dissectTaggedUnion branches value | ||
in | ||
Aeson.object ((tagKey, Aeson.toJSON tagValue) : fields) | ||
|
||
taggedUnionMemberWithTag :: | ||
forall tag allTags a proxy. | ||
KnownSymbol tag => | ||
proxy tag -> | ||
FC.Object FleeceToJSON a a -> | ||
FC.TaggedUnionMembers FleeceToJSON allTags '[tag @= a] | ||
taggedUnionMemberWithTag tag (Object mkFields) = | ||
let | ||
tagValue = | ||
T.pack (symbolVal tag) | ||
in | ||
TaggedUnionMembers (Shrubbery.taggedSingleBranch @tag (\a -> (tagValue, mkFields a))) | ||
|
||
taggedUnionCombine (TaggedUnionMembers left) (TaggedUnionMembers right) = | ||
TaggedUnionMembers (Shrubbery.appendTaggedBranches left right) | ||
|
||
jsonString (FleeceToJSON name toJSON) = | ||
FleeceToJSON | ||
name | ||
( Aeson.String | ||
. Enc.decodeUtf8 | ||
. LBS.toStrict | ||
. Aeson.encode | ||
. toJSON | ||
) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters