module Aeson (
    module Data.Aeson,
    module Data.Aeson.Types,
    module JSONSchema.Draft4,
    module Generics,
    lawlessJSONOptions,
    lawlessToJSONEncoding,
    lawlessParseJSON
    ) where

import Lawless
import Generics
import Data.Char
import Data.Aeson
import Data.Aeson.Types
import GHC.Generics (Rep)
import JSONSchema.Draft4

dropLensPrefix ∷ [Char] → [Char]
dropLensPrefix =
    let
        p c = c ≡ '_' ∨ isLower c
    in
        toListOf (droppingWhile p folded)

lawlessJSONOptions ∷ Options
lawlessJSONOptions = defaultOptions {
    fieldLabelModifier = camelTo2 '_' ∘ dropLensPrefix,
    constructorTagModifier = camelTo2 '_' ∘ dropLensPrefix,
    allNullaryToStringTag = False,
    omitNothingFields = False,
    sumEncoding = ObjectWithSingleField}

lawlessToJSONEncoding ∷ ∀ a. (GToEncoding (Rep a), Generic a) ⇒ a → Encoding
lawlessToJSONEncoding = genericToEncoding lawlessJSONOptions

lawlessParseJSON ∷ ∀ a. (GFromJSON (Rep a), Generic a) ⇒ Value → Parser a
lawlessParseJSON = genericParseJSON lawlessJSONOptions