{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE UndecidableInstances #-}
module Versioning.JSON
(
Applied
, JsonDecodableTo
, JsonDecodableToFrom
, fromJsonAnyVersion
, fromJsonAnyVersionStrict
, fromJsonAnyVersionEither
, fromJsonAnyVersionEitherStrict
, fromJsonAnyVersionFrom
, withJsonAnyVersion
, withJsonAnyVersionStrict
, withJsonAnyVersionEither
, withJsonAnyVersionEitherStrict
, withJsonAnyVersionFrom
, withJsonAnyVersionM
, withJsonAnyVersionStrictM
, withJsonAnyVersionEitherM
, withJsonAnyVersionEitherStrictM
, withJsonAnyVersionFromM
)
where
import Data.Aeson (FromJSON, decode, decodeStrict,
eitherDecode, eitherDecodeStrict)
import qualified Data.ByteString as StrictBS
import qualified Data.ByteString.Lazy as LazyBS
import Versioning.Base
import Versioning.Internal.Decoding
fromJsonAnyVersion
:: forall v a . JsonDecodableTo v a => LazyBS.ByteString -> Maybe (a v)
fromJsonAnyVersion = decodeAnyVersion jsonDecode
fromJsonAnyVersionStrict
:: forall v a . JsonDecodableTo v a => StrictBS.ByteString -> Maybe (a v)
fromJsonAnyVersionStrict = decodeAnyVersion jsonDecodeStrict
fromJsonAnyVersionEither
:: forall v a
. JsonDecodableTo v a
=> LazyBS.ByteString
-> Either String (a v)
fromJsonAnyVersionEither = decodeAnyVersion jsonEitherDecode
fromJsonAnyVersionEitherStrict
:: forall v a
. JsonDecodableTo v a
=> StrictBS.ByteString
-> Either String (a v)
fromJsonAnyVersionEitherStrict = decodeAnyVersion jsonEitherDecodeStrict
fromJsonAnyVersionFrom
:: forall from v a
. JsonDecodableToFrom from v a
=> LazyBS.ByteString
-> Maybe (a v)
fromJsonAnyVersionFrom = decodeAnyVersionFrom @from jsonDecode
withJsonAnyVersionM
:: forall c a v m
. (WithAnyVersion v a c FromJSON, Applicative m, c (a v))
=> ApplyM m a c
-> LazyBS.ByteString
-> m (Maybe (Applied c a))
withJsonAnyVersionM = withAnyVersionM @v @c @a jsonDecode
withJsonAnyVersionStrictM
:: forall c a v m
. (WithAnyVersion v a c FromJSON, Applicative m, c (a v))
=> ApplyM m a c
-> StrictBS.ByteString
-> m (Maybe (Applied c a))
withJsonAnyVersionStrictM = withAnyVersionM @v @c @a jsonDecodeStrict
withJsonAnyVersionEitherM
:: forall c a v m
. (WithAnyVersion v a c FromJSON, Applicative m, c (a v))
=> ApplyM m a c
-> LazyBS.ByteString
-> m (Either String (Applied c a))
withJsonAnyVersionEitherM = withAnyVersionM @v @c @a jsonEitherDecode
withJsonAnyVersionEitherStrictM
:: forall c a v m
. (WithAnyVersion v a c FromJSON, Applicative m, c (a v))
=> ApplyM m a c
-> StrictBS.ByteString
-> m (Either String (Applied c a))
withJsonAnyVersionEitherStrictM =
withAnyVersionM @v @c @a jsonEitherDecodeStrict
withJsonAnyVersionFromM
:: forall from c a v m
. (WithAnyVersionFrom from v a c FromJSON, Applicative m, c (a v))
=> ApplyM m a c
-> LazyBS.ByteString
-> m (Maybe (Applied c a))
withJsonAnyVersionFromM = withAnyVersionFromM @from @v @c @a jsonDecode
withJsonAnyVersion
:: forall c a v
. (WithAnyVersion v a c FromJSON, c (a v))
=> Apply a c
-> LazyBS.ByteString
-> Maybe (Applied c a)
withJsonAnyVersion = withAnyVersion @v @c @a jsonDecode
withJsonAnyVersionStrict
:: forall c a v
. (WithAnyVersion v a c FromJSON, c (a v))
=> Apply a c
-> StrictBS.ByteString
-> Maybe (Applied c a)
withJsonAnyVersionStrict = withAnyVersion @v @c @a jsonDecodeStrict
withJsonAnyVersionEither
:: forall c a v
. (WithAnyVersion v a c FromJSON, c (a v))
=> Apply a c
-> LazyBS.ByteString
-> Either String (Applied c a)
withJsonAnyVersionEither = withAnyVersion @v @c @a jsonEitherDecode
withJsonAnyVersionEitherStrict
:: forall c a v
. (WithAnyVersion v a c FromJSON, c (a v))
=> Apply a c
-> StrictBS.ByteString
-> Either String (Applied c a)
withJsonAnyVersionEitherStrict = withAnyVersion @v @c @a jsonEitherDecodeStrict
withJsonAnyVersionFrom
:: forall from c a v
. (WithAnyVersionFrom from v a c FromJSON, c (a v))
=> Apply a c
-> LazyBS.ByteString
-> Maybe (Applied c a)
withJsonAnyVersionFrom = withAnyVersionFrom @from @v @c @a jsonDecode
jsonDecode :: Decoder FromJSON LazyBS.ByteString Maybe a
jsonDecode = Decoder decode
jsonDecodeStrict :: Decoder FromJSON StrictBS.ByteString Maybe a
jsonDecodeStrict = Decoder decodeStrict
jsonEitherDecode :: Decoder FromJSON LazyBS.ByteString (Either String) a
jsonEitherDecode = Decoder eitherDecode
jsonEitherDecodeStrict :: Decoder FromJSON StrictBS.ByteString (Either String) a
jsonEitherDecodeStrict = Decoder eitherDecodeStrict
type JsonDecodableTo v a = JsonDecodableToFrom V0 v a
type JsonDecodableToFrom from v a = DecodableToFrom from FromJSON v a