{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ < 710
{-# LANGUAGE OverlappingInstances #-}
#endif
module Data.Unjson
(
unjsonToJSON
, unjsonToJSON'
, unjsonToByteStringLazy
, unjsonToByteStringLazy'
, unjsonToByteStringBuilder
, unjsonToByteStringBuilder'
, unjsonToByteStringBuilder''
, Options(..)
, Unjson(..)
, UnjsonDef(..)
, objectOf
, field
, fieldBy
, fieldOpt
, fieldOptBy
, fieldDef
, fieldDefBy
, fieldReadonly
, fieldReadonlyBy
, FieldDef(..)
, arrayOf
, arrayWithModeOf
, arrayWithModeOf'
, arrayWithPrimaryKeyOf
, arrayWithModeAndPrimaryKeyOf
, ArrayMode(..)
, mapOf
, enumOf
, enumUnjsonDef
, disjointUnionOf
, unionOf
, unjsonAeson
, unjsonAesonWithDoc
, render
, renderForPath
, renderDoc
, renderDocForPath
, parse
, update
, Result(..)
, Anchored(..)
, Problem
, Problems
, Path(..)
, PathElem(..)
, unjsonInvmapR
, unjsonIsConstrByName
, unjsonIPv4AsWord32
)
where
import qualified Data.Aeson as Aeson
import qualified Data.Aeson.Types as Aeson
import qualified Data.ByteString.Lazy as BSL
import qualified Data.ByteString.Lazy.Builder as Builder
import qualified Data.HashSet as HashSet
import qualified Data.IntMap as IntMap
import qualified Data.IntSet as IntSet
import qualified Data.Map as Map
import qualified Data.Semigroup as SG
import qualified Data.Set as Set
import qualified Data.Text as Text
import qualified Data.Text.Lazy as LazyText
import qualified Data.Vector as Vector
import qualified Data.Vector.Generic
import qualified Data.Vector.Primitive
import qualified Data.Vector.Storable
import qualified Data.Vector.Unboxed
import Data.Typeable
import Data.Data
import Data.Maybe
import Data.Monoid hiding (Ap)
import Data.Primitive.Types
import Data.Hashable
import Data.Scientific
import Data.Time.LocalTime
import Data.Time.Clock
import Data.Fixed
import Foreign.Storable
import Control.Applicative.Free
import Data.Functor.Invariant
import qualified Data.HashMap.Strict as HashMap
import qualified Data.HashMap.Lazy as LazyHashMap
import Control.Exception
import Control.Monad
import Data.Bits
import Data.Word
import Data.Int
import Data.Ratio
import Data.List
import qualified Text.ParserCombinators.ReadP as ReadP
import Data.Char
#if !MIN_VERSION_base(4,6,0)
import Prelude hiding (catch)
#endif
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative
import Data.Traversable
#endif
import qualified Text.PrettyPrint.HughesPJ as P
data PathElem = PathElemKey Text.Text
| PathElemIndex Int
deriving (Typeable, Eq, Ord, Show)
newtype Path = Path [PathElem]
deriving (Eq, Ord, Typeable, SG.Semigroup, Monoid)
instance Show Path where
show (Path p) = Text.unpack (showPath True p)
showPath :: Bool -> [PathElem] -> Text.Text
showPath _ [] = ""
showPath True (PathElemKey key : rest) = key <> showPath False rest
showPath False (PathElemKey key : rest) = "." <> key <> showPath False rest
showPath _ (PathElemIndex key : rest) = "[" <> Text.pack (show key) <> "]" <> showPath False rest
data Anchored a = Anchored Path a
deriving (Typeable, Functor, Eq, Ord)
instance (Show a) => Show (Anchored a) where
show (Anchored (Path path) value) = Text.unpack (showPath True path) ++ ": " ++ show value
instance (Typeable a, Show a) => Exception (Anchored a)
type Problem = Anchored Text.Text
type Problems = [Problem]
data Result a = Result a Problems
deriving (Functor, Show, Ord, Eq)
instance Applicative Result where
pure a = Result a []
Result a pa <*> Result b pb = Result (a b) (pa ++ pb)
instance Monad Result where
return = pure
Result a [] >>= m = m a
Result _ es@(e:_) >>= _ = Result (throw e) es
fail str = Result (throw anchoredMessage) [anchoredMessage]
where anchoredMessage = Anchored mempty (Text.pack str)
class Unjson a where
unjsonDef :: UnjsonDef a
instance {-# OVERLAPPABLE #-} (Unjson a, Typeable a) => Unjson [a] where
unjsonDef = arrayOf unjsonDef
instance Unjson String where
unjsonDef = unjsonAesonWithDoc "String"
instance Unjson Bool where unjsonDef = unjsonAeson
instance Unjson Char where unjsonDef = unjsonAeson
instance Unjson Double where unjsonDef = unjsonAeson
instance Unjson Float where unjsonDef = unjsonAeson
instance Unjson Int where unjsonDef = unjsonAeson
instance Unjson Int8 where unjsonDef = unjsonAeson
instance Unjson Int16 where unjsonDef = unjsonAeson
instance Unjson Int32 where unjsonDef = unjsonAeson
instance Unjson Int64 where unjsonDef = unjsonAeson
instance Unjson Integer where unjsonDef = unjsonAeson
instance Unjson Word where unjsonDef = unjsonAeson
instance Unjson Word8 where unjsonDef = unjsonAeson
instance Unjson Word16 where unjsonDef = unjsonAeson
instance Unjson Word32 where unjsonDef = unjsonAeson
instance Unjson Word64 where unjsonDef = unjsonAeson
instance Unjson () where unjsonDef = unjsonAeson
instance Unjson Text.Text where unjsonDef = unjsonAeson
instance Unjson IntSet.IntSet where unjsonDef = unjsonAeson
instance Unjson Scientific where unjsonDef = unjsonAeson
instance Unjson LazyText.Text where unjsonDef = unjsonAeson
instance Unjson ZonedTime where unjsonDef = unjsonAeson
instance Unjson UTCTime where unjsonDef = unjsonAeson
instance Unjson Aeson.DotNetTime where unjsonDef = unjsonAeson
instance Unjson Aeson.Value where unjsonDef = unjsonAeson
instance Unjson (Ratio Integer) where unjsonDef = unjsonAeson
instance (HasResolution a, Typeable a, Aeson.FromJSON a, Aeson.ToJSON a) => Unjson (Fixed a) where unjsonDef = unjsonAeson
instance Unjson a => Unjson (Dual a) where unjsonDef = invmap Dual getDual unjsonDef
instance (Unjson a, Typeable a) => Unjson (IntMap.IntMap a)
where unjsonDef = invmap IntMap.fromList IntMap.toList unjsonDef
instance (Ord a, Unjson a, Typeable a) => Unjson (Set.Set a)
where unjsonDef = invmap Set.fromList Set.toList unjsonDef
instance (Eq a, Hashable a, Unjson a, Typeable a) => Unjson (HashSet.HashSet a)
where unjsonDef = invmap HashSet.fromList HashSet.toList unjsonDef
instance (Unjson a, Typeable a) => Unjson (Vector.Vector a)
where unjsonDef = invmap Vector.fromList Vector.toList unjsonDef
instance (Data.Vector.Generic.Vector Data.Vector.Unboxed.Vector a, Unjson a, Data.Vector.Unboxed.Unbox a, Typeable a) => Unjson (Data.Vector.Unboxed.Vector a)
where unjsonDef = invmap Data.Vector.Unboxed.fromList Data.Vector.Unboxed.toList unjsonDef
instance (Storable a, Unjson a, Typeable a) => Unjson (Data.Vector.Storable.Vector a)
where unjsonDef = invmap Data.Vector.Storable.fromList Data.Vector.Storable.toList unjsonDef
instance (Prim a, Unjson a, Typeable a) => Unjson (Data.Vector.Primitive.Vector a)
where unjsonDef = invmap Data.Vector.Primitive.fromList Data.Vector.Primitive.toList unjsonDef
mapFst :: (a -> c) -> (a,b) -> (c,b)
mapFst f (a,b) = (f a, b)
instance (Typeable v, Unjson v) => Unjson (Map.Map String v)
where unjsonDef = invmap (Map.fromList . map (mapFst Text.unpack) . HashMap.toList)
(HashMap.fromList . map (mapFst Text.pack) . Map.toList)
unjsonDef
instance (Typeable v, Unjson v) => Unjson (Map.Map Text.Text v)
where unjsonDef = invmap (Map.fromList . HashMap.toList)
(HashMap.fromList . Map.toList)
unjsonDef
instance (Typeable v, Unjson v) => Unjson (Map.Map LazyText.Text v)
where unjsonDef = invmap (Map.fromList . map (mapFst LazyText.fromStrict) . HashMap.toList)
(HashMap.fromList . map (mapFst LazyText.toStrict) . Map.toList)
unjsonDef
instance (Typeable v, Unjson v) => Unjson (HashMap.HashMap String v)
where unjsonDef = invmap (HashMap.fromList . map (mapFst Text.unpack) . HashMap.toList)
(HashMap.fromList . map (mapFst Text.pack) . HashMap.toList)
unjsonDef
instance (Typeable v, Unjson v) => Unjson (HashMap.HashMap Text.Text v)
where unjsonDef = MapUnjsonDef unjsonDef pure id
instance (Typeable v, Unjson v) => Unjson (HashMap.HashMap LazyText.Text v)
where unjsonDef = invmap (HashMap.fromList . map (mapFst LazyText.fromStrict) . HashMap.toList)
(HashMap.fromList . map (mapFst LazyText.toStrict) . HashMap.toList)
unjsonDef
instance (Unjson a,Unjson b) => Unjson (a,b) where
unjsonDef = TupleUnjsonDef $ fmap pure
$ pure (,)
<*> liftAp (TupleFieldDef 0 (\(p,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 1 (\(_,p) -> p) unjsonDef)
instance (Unjson a,Unjson b,Unjson c) => Unjson (a,b,c) where
unjsonDef = TupleUnjsonDef $ fmap pure
$ pure (,,)
<*> liftAp (TupleFieldDef 0 (\(p,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 1 (\(_,p,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 2 (\(_,_,p) -> p) unjsonDef)
instance (Unjson a,Unjson b,Unjson c,Unjson d) => Unjson (a,b,c,d) where
unjsonDef = TupleUnjsonDef $ fmap pure
$ pure (,,,)
<*> liftAp (TupleFieldDef 0 (\(p,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 1 (\(_,p,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 2 (\(_,_,p,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 3 (\(_,_,_,p) -> p) unjsonDef)
instance (Unjson a,Unjson b,Unjson c,Unjson d
,Unjson e) => Unjson (a,b,c,d
,e) where
unjsonDef = TupleUnjsonDef $ fmap pure
$ pure (,,,,)
<*> liftAp (TupleFieldDef 0 (\(p,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 1 (\(_,p,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 2 (\(_,_,p,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 3 (\(_,_,_,p,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 4 (\(_,_,_,_,p) -> p) unjsonDef)
instance (Unjson a,Unjson b,Unjson c,Unjson d
,Unjson e,Unjson f)
=> Unjson (a,b,c,d
,e,f) where
unjsonDef = TupleUnjsonDef $ fmap pure
$ pure (,,,,,)
<*> liftAp (TupleFieldDef 0 (\(p,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 1 (\(_,p,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 2 (\(_,_,p,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 3 (\(_,_,_,p,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 4 (\(_,_,_,_,p,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 5 (\(_,_,_,_,_,p) -> p) unjsonDef)
instance (Unjson a,Unjson b,Unjson c,Unjson d
,Unjson e,Unjson f,Unjson g)
=> Unjson (a,b,c,d
,e,f,g) where
unjsonDef = TupleUnjsonDef $ fmap pure
$ pure (,,,,,,)
<*> liftAp (TupleFieldDef 0 (\(p,_,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 1 (\(_,p,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 2 (\(_,_,p,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 3 (\(_,_,_,p,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 4 (\(_,_,_,_,p,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 5 (\(_,_,_,_,_,p,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 6 (\(_,_,_,_,_,_,p) -> p) unjsonDef)
instance (Unjson a,Unjson b,Unjson c,Unjson d
,Unjson e,Unjson f,Unjson g,Unjson h)
=> Unjson (a,b,c,d
,e,f,g,h) where
unjsonDef = TupleUnjsonDef $ fmap pure
$ pure (,,,,,,,)
<*> liftAp (TupleFieldDef 0 (\(p,_,_,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 1 (\(_,p,_,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 2 (\(_,_,p,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 3 (\(_,_,_,p,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 4 (\(_,_,_,_,p,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 5 (\(_,_,_,_,_,p,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 6 (\(_,_,_,_,_,_,p,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 7 (\(_,_,_,_,_,_,_,p) -> p) unjsonDef)
instance (Unjson a,Unjson b,Unjson c,Unjson d
,Unjson e,Unjson f,Unjson g,Unjson h
,Unjson i)
=> Unjson (a,b,c,d
,e,f,g,h
,i) where
unjsonDef = TupleUnjsonDef $ fmap pure
$ pure (,,,,,,,,)
<*> liftAp (TupleFieldDef 0 (\(p,_,_,_,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 1 (\(_,p,_,_,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 2 (\(_,_,p,_,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 3 (\(_,_,_,p,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 4 (\(_,_,_,_,p,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 5 (\(_,_,_,_,_,p,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 6 (\(_,_,_,_,_,_,p,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 7 (\(_,_,_,_,_,_,_,p,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 8 (\(_,_,_,_,_,_,_,_,p) -> p) unjsonDef)
instance (Unjson a,Unjson b,Unjson c,Unjson d
,Unjson e,Unjson f,Unjson g,Unjson h
,Unjson i,Unjson j)
=> Unjson (a,b,c,d
,e,f,g,h
,i,j) where
unjsonDef = TupleUnjsonDef $ fmap pure
$ pure (,,,,,,,,,)
<*> liftAp (TupleFieldDef 0 (\(p,_,_,_,_,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 1 (\(_,p,_,_,_,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 2 (\(_,_,p,_,_,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 3 (\(_,_,_,p,_,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 4 (\(_,_,_,_,p,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 5 (\(_,_,_,_,_,p,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 6 (\(_,_,_,_,_,_,p,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 7 (\(_,_,_,_,_,_,_,p,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 8 (\(_,_,_,_,_,_,_,_,p,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 9 (\(_,_,_,_,_,_,_,_,_,p) -> p) unjsonDef)
instance (Unjson a,Unjson b,Unjson c,Unjson d
,Unjson e,Unjson f,Unjson g,Unjson h
,Unjson i,Unjson j,Unjson k)
=> Unjson (a,b,c,d
,e,f,g,h
,i,j,k) where
unjsonDef = TupleUnjsonDef $ fmap pure
$ pure (,,,,,,,,,,)
<*> liftAp (TupleFieldDef 0 (\(p,_,_,_,_,_,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 1 (\(_,p,_,_,_,_,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 2 (\(_,_,p,_,_,_,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 3 (\(_,_,_,p,_,_,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 4 (\(_,_,_,_,p,_,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 5 (\(_,_,_,_,_,p,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 6 (\(_,_,_,_,_,_,p,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 7 (\(_,_,_,_,_,_,_,p,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 8 (\(_,_,_,_,_,_,_,_,p,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 9 (\(_,_,_,_,_,_,_,_,_,p,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 10 (\(_,_,_,_,_,_,_,_,_,_,p) -> p) unjsonDef)
instance (Unjson a,Unjson b,Unjson c,Unjson d
,Unjson e,Unjson f,Unjson g,Unjson h
,Unjson i,Unjson j,Unjson k,Unjson l)
=> Unjson (a,b,c,d
,e,f,g,h
,i,j,k,l) where
unjsonDef = TupleUnjsonDef $ fmap pure
$ pure (,,,,,,,,,,,)
<*> liftAp (TupleFieldDef 0 (\(p,_,_,_,_,_,_,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 1 (\(_,p,_,_,_,_,_,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 2 (\(_,_,p,_,_,_,_,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 3 (\(_,_,_,p,_,_,_,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 4 (\(_,_,_,_,p,_,_,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 5 (\(_,_,_,_,_,p,_,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 6 (\(_,_,_,_,_,_,p,_,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 7 (\(_,_,_,_,_,_,_,p,_,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 8 (\(_,_,_,_,_,_,_,_,p,_,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 9 (\(_,_,_,_,_,_,_,_,_,p,_,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 10 (\(_,_,_,_,_,_,_,_,_,_,p,_) -> p) unjsonDef)
<*> liftAp (TupleFieldDef 11 (\(_,_,_,_,_,_,_,_,_,_,_,p) -> p) unjsonDef)
data ArrayMode
= ArrayModeStrict
| ArrayModeParseSingle
| ArrayModeParseAndOutputSingle
deriving (Eq, Ord, Show, Typeable)
data PrimaryKeyExtraction k = forall pk . (Ord pk) => PrimaryKeyExtraction (k -> pk) (UnjsonDef pk)
data UnjsonDef a where
SimpleUnjsonDef :: Text.Text -> (Aeson.Value -> Result k) -> (k -> Aeson.Value) -> UnjsonDef k
ArrayUnjsonDef :: Typeable k => Maybe (PrimaryKeyExtraction k) -> ArrayMode -> ([k] -> Result v) -> (v -> [k]) -> UnjsonDef k -> UnjsonDef v
ObjectUnjsonDef :: Ap (FieldDef k) (Result k) -> UnjsonDef k
TupleUnjsonDef :: Ap (TupleFieldDef k) (Result k) -> UnjsonDef k
DisjointUnjsonDef :: Text.Text -> [(Text.Text, k -> Bool, Ap (FieldDef k) (Result k))] -> UnjsonDef k
UnionUnjsonDef :: [(k -> Bool, Ap (FieldDef k) (Result k))] -> UnjsonDef k
MapUnjsonDef :: Typeable k => UnjsonDef k -> (HashMap.HashMap Text.Text k -> Result v) -> (v -> HashMap.HashMap Text.Text k) -> UnjsonDef v
instance Invariant UnjsonDef where
invmap f g (SimpleUnjsonDef name p s) = SimpleUnjsonDef name (fmap f . p) (s . g)
invmap f g (ArrayUnjsonDef mpk am n k d) = ArrayUnjsonDef mpk am (fmap f . n) (k . g) d
invmap f g (MapUnjsonDef d n k) = MapUnjsonDef d (fmap f . n) (k . g)
invmap f g (ObjectUnjsonDef fd) = ObjectUnjsonDef (fmap (fmap f) (hoistAp (contramapFieldDef g) fd))
invmap f g (TupleUnjsonDef td) = TupleUnjsonDef (fmap (fmap f) (hoistAp (contramapTupleFieldDef g) td))
invmap f g (DisjointUnjsonDef d l) = DisjointUnjsonDef d (map (\(a,b,c) -> (a,b . g,fmap (fmap f) (hoistAp (contramapFieldDef g) c))) l)
invmap f g (UnionUnjsonDef l) = UnionUnjsonDef (map (\(b,c) -> (b . g,fmap (fmap f) (hoistAp (contramapFieldDef g) c))) l)
unjsonInvmapR :: (a -> Result b) -> (b -> a) -> UnjsonDef a -> UnjsonDef b
unjsonInvmapR f g (SimpleUnjsonDef name p s) = SimpleUnjsonDef name (join . fmap f . p) (s . g)
unjsonInvmapR f g (ArrayUnjsonDef mpk am n k d) = ArrayUnjsonDef mpk am (join . fmap f . n) (k . g) d
unjsonInvmapR f g (MapUnjsonDef d n k) = MapUnjsonDef d (join . fmap f . n) (k . g)
unjsonInvmapR f g (ObjectUnjsonDef fd) = ObjectUnjsonDef (fmap (join . fmap f) (hoistAp (contramapFieldDef g) fd))
unjsonInvmapR f g (TupleUnjsonDef td) = TupleUnjsonDef (fmap (join . fmap f) (hoistAp (contramapTupleFieldDef g) td))
unjsonInvmapR f g (DisjointUnjsonDef d l) = DisjointUnjsonDef d (map (\(a,b,c) -> (a,b . g,fmap (join . fmap f) (hoistAp (contramapFieldDef g) c))) l)
unjsonInvmapR f g (UnionUnjsonDef l) = UnionUnjsonDef (map (\(b,c) -> (b . g,fmap (join . fmap f) (hoistAp (contramapFieldDef g) c))) l)
contramapFieldDef :: (b -> a) -> FieldDef a x -> FieldDef b x
contramapFieldDef f (FieldReqDef name doc ext d) = FieldReqDef name doc (ext . f) d
contramapFieldDef f (FieldOptDef name doc ext d) = FieldOptDef name doc (ext . f) d
contramapFieldDef f (FieldDefDef name doc def ext d) = FieldDefDef name doc def (ext . f) d
contramapFieldDef f (FieldRODef name doc ext d) = FieldRODef name doc (ext . f) d
contramapTupleFieldDef :: (b -> a) -> TupleFieldDef a x -> TupleFieldDef b x
contramapTupleFieldDef f (TupleFieldDef i e d) = TupleFieldDef i (e . f) d
data FieldDef s a where
FieldReqDef :: Typeable a => Text.Text -> Text.Text -> (s -> a) -> UnjsonDef a -> FieldDef s a
FieldOptDef :: Typeable a => Text.Text -> Text.Text -> (s -> Maybe a) -> UnjsonDef a -> FieldDef s (Maybe a)
FieldDefDef :: Typeable a => Text.Text -> Text.Text -> a -> (s -> a) -> UnjsonDef a -> FieldDef s a
FieldRODef :: Typeable a => Text.Text -> Text.Text -> (s -> a) -> UnjsonDef a -> FieldDef s ()
data TupleFieldDef s a where
TupleFieldDef :: Int -> (s -> a) -> UnjsonDef a -> TupleFieldDef s a
tupleDefToArray :: (forall b . UnjsonDef b -> b -> v) -> s -> Ap (TupleFieldDef s) a -> [v]
tupleDefToArray _sx _ (Pure _) = []
tupleDefToArray sx s (Ap (TupleFieldDef _ f d) r) = (sx d (f s)) : tupleDefToArray sx s r
objectDefToArray :: Bool -> (forall b . UnjsonDef b -> b -> v) -> s -> Ap (FieldDef s) a -> [(Text.Text,v)]
objectDefToArray _ _sx _ (Pure _) = []
objectDefToArray explicitNulls sx s (Ap (FieldReqDef key _ f d) r) = (key,sx d (f s)) : objectDefToArray explicitNulls sx s r
objectDefToArray explicitNulls sx s (Ap (FieldOptDef key _ f d) r) =
case f s of
Nothing -> (if explicitNulls then [(key,sx unjsonDef Aeson.Null)] else []) ++ objectDefToArray explicitNulls sx s r
Just g -> (key,sx d g) : objectDefToArray explicitNulls sx s r
objectDefToArray explicitNulls sx s (Ap (FieldDefDef key _ _ f d) r) = (key,sx d (f s)) : objectDefToArray explicitNulls sx s r
objectDefToArray explicitNulls sx s (Ap (FieldRODef key _ f d) r) = (key,sx d (f s)) : objectDefToArray explicitNulls sx s r
data Options = Options
{ pretty :: Bool
, indent :: Int
, nulls :: Bool
}
deriving (Eq, Ord, Show)
unjsonToJSON :: UnjsonDef a -> a -> Aeson.Value
unjsonToJSON = unjsonToJSON' (Options { pretty = False, indent = 4, nulls = False })
unjsonToJSON' :: Options -> UnjsonDef a -> a -> Aeson.Value
unjsonToJSON' _ (SimpleUnjsonDef _ _ g) a = g a
unjsonToJSON' opt (ArrayUnjsonDef _ m _g k f) a =
case (m, k a) of
(ArrayModeParseAndOutputSingle,[b]) -> unjsonToJSON' opt f b
(_,c) -> Aeson.toJSON (map (unjsonToJSON' opt f) c)
unjsonToJSON' opt (ObjectUnjsonDef f) a =
Aeson.object (objectDefToArray (nulls opt) (unjsonToJSON' opt) a f)
unjsonToJSON' opt (TupleUnjsonDef f) a =
Aeson.toJSON (tupleDefToArray (unjsonToJSON' opt) a f)
unjsonToJSON' opt (DisjointUnjsonDef k l) a =
Aeson.object ((k,Aeson.toJSON nm) : objectDefToArray (nulls opt) (unjsonToJSON' opt) a f)
where
[(nm,_,f)] = filter (\(_,is,_) -> is a) l
unjsonToJSON' opt (UnionUnjsonDef l) a =
Aeson.object (objectDefToArray (nulls opt) (unjsonToJSON' opt) a f)
where
[(_,f)] = filter (\(is,_) -> is a) l
unjsonToJSON' opt (MapUnjsonDef f _ g) a =
Aeson.Object $ fmap (unjsonToJSON' opt f) (g a)
unjsonToByteStringLazy :: UnjsonDef a -> a -> BSL.ByteString
unjsonToByteStringLazy = unjsonToByteStringLazy' (Options { pretty = False, indent = 4, nulls = False })
unjsonToByteStringLazy' :: Options -> UnjsonDef a -> a -> BSL.ByteString
unjsonToByteStringLazy' opt ud a = Builder.toLazyByteString (unjsonToByteStringBuilder' opt ud a)
unjsonGroup :: Int -> Options -> Builder.Builder -> Builder.Builder -> (a -> Builder.Builder) -> [a] -> Builder.Builder
unjsonGroup _level _ open close _peritem [] =
mconcat $ [open, close]
unjsonGroup level opt open close peritem items =
mconcat $ [open, newline] ++ intersperse (Builder.char8 ',' <> newline) (map ((idnt2 <>) . peritem) items) ++ [newline, idnt, close]
where
newline :: Builder.Builder
newline = if pretty opt then Builder.char8 '\n' else mempty
idnt :: Builder.Builder
idnt = if pretty opt then mconcat (take level (repeat (Builder.char8 ' '))) else mempty
idnt2 :: Builder.Builder
idnt2 = if pretty opt then mconcat (take (level + indent opt) (repeat (Builder.char8 ' '))) else mempty
unjsonToByteStringBuilder' :: Options -> UnjsonDef a -> a -> Builder.Builder
unjsonToByteStringBuilder' = unjsonToByteStringBuilder'' 0
unjsonToByteStringBuilder :: UnjsonDef a -> a -> Builder.Builder
unjsonToByteStringBuilder = unjsonToByteStringBuilder' (Options { pretty = False, indent = 4, nulls = False })
unjsonToByteStringBuilder'' :: Int -> Options -> UnjsonDef a -> a -> Builder.Builder
unjsonToByteStringBuilder'' _level _opt (SimpleUnjsonDef _ _ g) a = Builder.lazyByteString (Aeson.encode (g a))
unjsonToByteStringBuilder'' level opt (ArrayUnjsonDef _ m _g k f) a =
case (m, k a) of
(ArrayModeParseAndOutputSingle,[b]) -> unjsonToByteStringBuilder'' level opt f b
(_,c) -> unjsonGroup level opt (Builder.char8 '[') (Builder.char8 ']') (unjsonToByteStringBuilder'' (level+indent opt) opt f) c
unjsonToByteStringBuilder'' level opt (ObjectUnjsonDef f) a =
unjsonGroup level opt (Builder.char8 '{') (Builder.char8 '}') serx obj
where
obj :: [(Text.Text, Builder.Builder)]
obj = objectDefToArray (nulls opt) (unjsonToByteStringBuilder'' (level + indent opt) opt) a f
serx :: (Text.Text, Builder.Builder) -> Builder.Builder
serx (key,val) = Builder.lazyByteString (Aeson.encode (Aeson.toJSON key)) <> Builder.char8 ':'
<> (if pretty opt then Builder.char8 ' ' else mempty) <> val
unjsonToByteStringBuilder'' level opt (TupleUnjsonDef f) a =
unjsonGroup level opt (Builder.char8 '[') (Builder.char8 ']') id (tupleDefToArray (unjsonToByteStringBuilder'' (level+indent opt) opt) a f)
unjsonToByteStringBuilder'' level opt (DisjointUnjsonDef k l) a =
unjsonGroup level opt (Builder.char8 '{') (Builder.char8 '}') serx obj
where
obj :: [(Text.Text, Builder.Builder)]
obj = (k,Builder.lazyByteString (Aeson.encode (Aeson.toJSON nm))) : objectDefToArray (nulls opt) (unjsonToByteStringBuilder'' (level + indent opt) opt) a f
serx :: (Text.Text, Builder.Builder) -> Builder.Builder
serx (key,val) = Builder.lazyByteString (Aeson.encode (Aeson.toJSON key)) <> Builder.char8 ':'
<> (if pretty opt then Builder.char8 ' ' else mempty) <> val
[(nm,_,f)] = filter (\(_,is,_) -> is a) l
unjsonToByteStringBuilder'' level opt (UnionUnjsonDef l) a =
unjsonGroup level opt (Builder.char8 '{') (Builder.char8 '}') serx obj
where
obj :: [(Text.Text, Builder.Builder)]
obj = objectDefToArray (nulls opt) (unjsonToByteStringBuilder'' (level + indent opt) opt) a f
serx :: (Text.Text, Builder.Builder) -> Builder.Builder
serx (key,val) = Builder.lazyByteString (Aeson.encode (Aeson.toJSON key)) <> Builder.char8 ':'
<> (if pretty opt then Builder.char8 ' ' else mempty) <> val
[(_,f)] = filter (\(is,_) -> is a) l
unjsonToByteStringBuilder'' level opt (MapUnjsonDef f _ g) a =
unjsonGroup level opt (Builder.char8 '{') (Builder.char8 '}') serx obj
where
obj = LazyHashMap.toList (fmap (unjsonToByteStringBuilder'' (level + indent opt) opt f) (g a))
serx (key,val) = Builder.lazyByteString (Aeson.encode (Aeson.toJSON key)) <> Builder.char8 ':'
<> (if pretty opt then Builder.char8 ' ' else mempty) <> val
listRequiredKeysForField :: FieldDef s a -> [Text.Text]
listRequiredKeysForField (FieldReqDef key _docstring _f _d) = [key]
listRequiredKeysForField (FieldOptDef _key _docstring _f _d) = []
listRequiredKeysForField (FieldDefDef _key _docstring _f _ _d) = []
listRequiredKeysForField (FieldRODef _key _docstring _f _d) = []
listRequiredKeys :: Ap (FieldDef s) a -> [Text.Text]
listRequiredKeys (Pure _) = []
listRequiredKeys (Ap f r) =
listRequiredKeysForField f ++ listRequiredKeys r
countAp :: Int -> Ap x a -> Int
countAp !n (Pure _) = n
countAp n (Ap _ r) = countAp (succ n) r
mapResultsIssuePaths :: (Path -> Path) -> Result a -> Result a
mapResultsIssuePaths f (Result v paths) = Result v' paths'
where
paths' = map fa paths
v' = mapException fa v
fa (Anchored path x) = Anchored (f path) x
resultPrependIndex :: Int -> Result a -> Result a
resultPrependIndex i = mapResultsIssuePaths (Path [PathElemIndex i]<>)
resultPrependKey :: Text.Text -> Result a -> Result a
resultPrependKey k = mapResultsIssuePaths (Path [PathElemKey k]<>)
parseUpdating :: UnjsonDef a -> Maybe a -> Aeson.Value -> Result a
parseUpdating (SimpleUnjsonDef _ f _) _ov v = f v
parseUpdating (ArrayUnjsonDef (Just (PrimaryKeyExtraction pk_from_object pk_from_json)) m g k f) (Just ov) v
= case Aeson.parseEither Aeson.parseJSON v of
Right v' -> join $ fmap g $
sequenceA (zipWith (\v'' i -> lookupObjectByJson v'' >>= \ov' -> (resultPrependIndex i $ parseUpdating f ov' v''))
(Vector.toList v') [0..])
Left e -> case m of
ArrayModeStrict ->
fail e
_ -> join $ fmap g $
sequenceA [lookupObjectByJson v >>= \ov' ->
parseUpdating f ov'
v]
where
objectMap = Map.fromListWith (flip const) (map (\o -> (pk_from_object o, o)) (k ov))
lookupObjectByJson js = parseUpdating pk_from_json Nothing js >>= \val -> return (Map.lookup val objectMap)
parseUpdating (ArrayUnjsonDef _ m g _k f) _ov v
= case Aeson.parseEither Aeson.parseJSON v of
Right v' -> join $ fmap g $
sequenceA (zipWith (\v'' i -> resultPrependIndex i $ parseUpdating f Nothing v'') (Vector.toList v') [0..])
Left e -> case m of
ArrayModeStrict ->
fail e
_ -> join $ fmap g $
sequenceA [parseUpdating f Nothing v]
parseUpdating (ObjectUnjsonDef f) ov v
= case Aeson.parseEither Aeson.parseJSON v of
Right v' ->
join (runAp (lookupByFieldDef v' ov) f)
Left e ->
fail e
parseUpdating (TupleUnjsonDef f) ov v
= case Aeson.parseEither Aeson.parseJSON v of
Right v' ->
let r@(Result g h) = runAp (lookupByTupleFieldDef v' ov) f
tupleSize = countAp 0 f
arrayLength = Vector.length v'
in if tupleSize == arrayLength
then join r
else join $ Result g ([Anchored mempty ("cannot parse array of length " <> Text.pack (show arrayLength) <>
" into tuple of size " <> Text.pack (show tupleSize))] <> h)
Left e ->
fail e
parseUpdating (DisjointUnjsonDef k l) ov v
= case Aeson.parseEither Aeson.parseJSON v of
Right v' -> case HashMap.lookup k v' of
Just x -> case Aeson.parseEither Aeson.parseJSON x of
Right xx -> case filter (\(nm,_,_) -> nm==xx) l of
[(_,_,f)] -> join (runAp (lookupByFieldDef v' ov) f)
_ ->
resultPrependKey k $ fail $ "value '" ++ Text.unpack xx ++ "' is not one of the allowed for enumeration [" ++ intercalate "," (map (\(a,_,_) -> Text.unpack a) l) ++ "]"
Left e ->
fail e
Nothing -> case ov of
Just xov -> Result xov []
Nothing -> resultPrependKey k $ fail "missing key"
Left e ->
fail e
parseUpdating (UnionUnjsonDef l) ov v
= case Aeson.parseEither Aeson.parseJSON v of
Right v' -> case filter (\(_,f) -> isJust (mapM_ (\k -> HashMap.lookup k v') (listRequiredKeys f))) l of
((_,f):_) -> join (runAp (lookupByFieldDef v' ov) f)
_ -> fail $ "union value type could not be recognized based on presence of keys"
Left e ->
fail e
parseUpdating (MapUnjsonDef f g h) ov v
= case Aeson.parseEither Aeson.parseJSON v of
Right v' ->
let hov = fmap h ov in
join $ fmap g $ HashMap.traverseWithKey (\k1 v1 -> resultPrependKey k1 $ parseUpdating f (join (fmap (HashMap.lookup k1) hov)) v1) v'
Left e ->
fail e
parse :: UnjsonDef a -> Aeson.Value -> Result a
parse vd = parseUpdating vd Nothing
update :: a -> UnjsonDef a -> Aeson.Value -> Result a
update a vd = parseUpdating vd (Just a)
lookupByFieldDef :: Aeson.Object -> Maybe s -> FieldDef s a -> Result a
lookupByFieldDef v ov (FieldReqDef name _docstring f valuedef)
= resultPrependKey name $ case HashMap.lookup name v of
Just x -> parseUpdating valuedef (fmap f ov) x
Nothing -> case ov of
Just xov -> Result (f xov) []
Nothing -> fail "missing key"
lookupByFieldDef v ov (FieldDefDef name _docstring def f valuedef)
= resultPrependKey name $ case HashMap.lookup name v of
Just Aeson.Null -> Result def []
Just x -> parseUpdating valuedef (fmap f ov) x
Nothing -> case ov of
Just xov -> Result (f xov) []
Nothing -> Result def []
lookupByFieldDef v ov (FieldOptDef name _docstring f valuedef)
= resultPrependKey name $ case HashMap.lookup name v of
Just Aeson.Null -> Result Nothing []
Just x -> case ov of
Just xov -> fmap Just (parseUpdating valuedef (f xov) x)
Nothing -> fmap Just (parseUpdating valuedef Nothing x)
Nothing -> case ov of
Just xov -> Result (f xov) []
Nothing -> Result Nothing []
lookupByFieldDef _ _ (FieldRODef _name _docstring _f _valuedef) = Result () []
lookupByTupleFieldDef :: Aeson.Array -> Maybe s -> TupleFieldDef s a -> Result a
lookupByTupleFieldDef v ov (TupleFieldDef idx f valuedef)
= resultPrependIndex idx $ case v Vector.!? idx of
Just x -> parseUpdating valuedef (fmap f ov) x
Nothing -> fail "missing key"
fieldBy :: Typeable a => Text.Text -> (s -> a) -> Text.Text -> UnjsonDef a -> Ap (FieldDef s) a
fieldBy key f docstring valuedef = liftAp (FieldReqDef key docstring f valuedef)
field :: (Unjson a, Typeable a) => Text.Text -> (s -> a) -> Text.Text -> Ap (FieldDef s) a
field key f docstring = fieldBy key f docstring unjsonDef
fieldOptBy :: Typeable a => Text.Text -> (s -> Maybe a) -> Text.Text -> UnjsonDef a -> Ap (FieldDef s) (Maybe a)
fieldOptBy key f docstring valuedef = liftAp (FieldOptDef key docstring f valuedef)
fieldOpt :: (Unjson a, Typeable a) => Text.Text -> (s -> Maybe a) -> Text.Text -> Ap (FieldDef s) (Maybe a)
fieldOpt key f docstring = fieldOptBy key f docstring unjsonDef
fieldDefBy :: Typeable a => Text.Text -> a -> (s -> a) -> Text.Text -> UnjsonDef a -> Ap (FieldDef s) a
fieldDefBy key def f docstring valuedef = liftAp (FieldDefDef key docstring def f valuedef)
fieldDef :: (Unjson a, Typeable a) => Text.Text -> a -> (s -> a) -> Text.Text -> Ap (FieldDef s) a
fieldDef key def f docstring = fieldDefBy key def f docstring unjsonDef
fieldReadonly :: (Unjson a, Typeable a) => Text.Text -> (s -> a) -> Text.Text -> Ap (FieldDef s) ()
fieldReadonly key f docstring = fieldReadonlyBy key f docstring unjsonDef
fieldReadonlyBy :: Typeable a => Text.Text -> (s -> a) -> Text.Text -> UnjsonDef a -> Ap (FieldDef s) ()
fieldReadonlyBy key f docstring valuedef = liftAp (FieldRODef key docstring f valuedef)
objectOf :: Ap (FieldDef a) a -> UnjsonDef a
objectOf fields = ObjectUnjsonDef (fmap pure fields)
mapOf :: Typeable x => UnjsonDef x -> UnjsonDef (LazyHashMap.HashMap Text.Text x)
mapOf def = MapUnjsonDef def pure id
disjointUnionOf :: Text.Text -> [(Text.Text, k -> Bool, Ap (FieldDef k) k)] -> UnjsonDef k
disjointUnionOf key alternates =
DisjointUnjsonDef key (map (\(a,b,c) -> (a,b,fmap return c)) alternates)
unionOf :: [(k -> Bool, Ap (FieldDef k) k)] -> UnjsonDef k
unionOf alternates =
UnionUnjsonDef (map (\(b,c) -> (b,fmap return c)) alternates)
enumOf :: (Eq k) => Text.Text -> [(Text.Text, k)] -> UnjsonDef k
enumOf key alternates =
DisjointUnjsonDef key (map (\(a,b) -> (a,(==)b,fmap return (pure b))) alternates)
enumUnjsonDef
:: forall a. (Eq a, Typeable a, Enum a, Bounded a, Data a)
=> UnjsonDef a
enumUnjsonDef = enumOf typeName [ (Text.pack $ show $ toConstr c, c) | c <- constructors ]
where
typeName = Text.pack . show . typeRep $ (Proxy :: Proxy a)
constructors = enumFromTo minBound maxBound :: [a]
arrayOf :: Typeable a => UnjsonDef a -> UnjsonDef [a]
arrayOf = arrayWithModeOf ArrayModeStrict
arrayWithModeOf :: Typeable a => ArrayMode -> UnjsonDef a -> UnjsonDef [a]
arrayWithModeOf mode valuedef = ArrayUnjsonDef Nothing mode pure id valuedef
arrayWithModeOf' :: (Aeson.FromJSON a,Aeson.ToJSON a, Typeable a)
=> ArrayMode
-> UnjsonDef [a]
arrayWithModeOf' mode = arrayWithModeOf mode unjsonAeson
arrayWithModeAndPrimaryKeyOf :: (Ord pk, Typeable a)
=> ArrayMode
-> (a -> pk)
-> UnjsonDef pk
-> UnjsonDef a
-> UnjsonDef [a]
arrayWithModeAndPrimaryKeyOf mode pk1 pk2 valuedef =
ArrayUnjsonDef (Just (PrimaryKeyExtraction pk1 pk2)) mode pure id valuedef
arrayWithPrimaryKeyOf :: (Ord pk, Typeable a)
=> (a -> pk)
-> UnjsonDef pk
-> UnjsonDef a
-> UnjsonDef [a]
arrayWithPrimaryKeyOf pk1 pk2 valuedef =
arrayWithModeAndPrimaryKeyOf ArrayModeStrict pk1 pk2 valuedef
unjsonAeson :: forall a . (Aeson.FromJSON a,Aeson.ToJSON a, Typeable a) => UnjsonDef a
unjsonAeson = unjsonAesonFixCharArrayToString
unjsonAesonWithDoc :: (Aeson.FromJSON a,Aeson.ToJSON a) => Text.Text -> UnjsonDef a
unjsonAesonWithDoc docstring = SimpleUnjsonDef docstring
(\value ->
case Aeson.fromJSON value of
Aeson.Success result -> Result result []
Aeson.Error message -> fail message)
Aeson.toJSON
unjsonAesonFixCharArrayToString :: forall a . (Aeson.FromJSON a,Aeson.ToJSON a, Typeable a) => UnjsonDef a
unjsonAesonFixCharArrayToString =
unjsonAesonWithDoc (Text.pack typeNameFixed)
where
typeName = show (typeOf (undefined :: a))
typeNameFixed = fixup typeName
fixup [] = []
fixup ('[':'C':'h':'a':'r':']':rest) = "String" ++ fixup rest
fixup (x:xs) = x : fixup xs
unjsonIsConstrByName :: (Data a) => String -> a -> Bool
unjsonIsConstrByName nm v = nm == show (toConstr v)
render :: UnjsonDef a -> String
render = P.render . renderDoc
renderForPath :: (Functor m, Monad m) => Path -> UnjsonDef a -> m String
renderForPath path def = fmap P.render (renderDocForPath path def)
renderDoc :: UnjsonDef a -> P.Doc
renderDoc (SimpleUnjsonDef doc _ _) = P.text (ansiDimmed ++ Text.unpack doc ++ ansiReset)
renderDoc (ArrayUnjsonDef _ _m _g _k f) = P.text (ansiDimmed ++ "array of" ++ ansiReset ++ ":") P.$+$
P.nest 4 (renderDoc f)
renderDoc (MapUnjsonDef f _ _) = P.text (ansiDimmed ++ "map of" ++ ansiReset ++ ":") P.$+$
P.nest 4 (renderDoc f)
renderDoc (ObjectUnjsonDef f) =
P.vcat (renderFields f)
renderDoc (TupleUnjsonDef f) = P.text (ansiDimmed ++ "tuple of size " ++ show (countAp 0 f) ++ " with elements:" ++ ansiReset) P.$+$
P.vcat (renderTupleFields f)
renderDoc (DisjointUnjsonDef k z) = P.text (ansiDimmed ++ "disjoint union based on key:" ++ ansiReset) P.$+$
P.vcat [P.text (ansiBold ++ Text.unpack k ++ ": " ++ Text.unpack l ++ ansiReset) P.$+$ P.nest 4 (P.vcat (renderFields f)) | (l,_,f) <- z]
renderDoc (UnionUnjsonDef z) = P.text (ansiDimmed ++ "plain union based on presence of required keys:" ++ ansiReset) P.$+$
P.vcat [P.text (ansiBold ++ "case " ++ show (i::Int) ++ ":" ++ ansiReset) P.$+$ P.nest 4 (P.vcat (renderFields f)) | ((_,f),i) <- zip z [1..]]
renderDocForPath :: (Monad m) => Path -> UnjsonDef a -> m P.Doc
renderDocForPath path def = findNestedUnjson path def
renderField :: FieldDef s a -> P.Doc
renderField (FieldReqDef key docstring _f d) =
P.text (ansiBold ++ Text.unpack key ++ ansiReset) P.<> P.text " (req):" P.$+$ P.nest 4 (P.text (Text.unpack docstring) P.$+$ renderDoc d)
renderField (FieldOptDef key docstring _f d) =
P.text (ansiBold ++ Text.unpack key ++ ansiReset) P.<> P.text " (opt):" P.$+$ P.nest 4 (P.text (Text.unpack docstring) P.$+$ renderDoc d)
renderField (FieldDefDef key docstring _f _ d) =
P.text (ansiBold ++ Text.unpack key ++ ansiReset) P.<> P.text " (def):" P.$+$ P.nest 4 (P.text (Text.unpack docstring) P.$+$ renderDoc d)
renderField (FieldRODef key docstring _f d) =
P.text (ansiBold ++ Text.unpack key ++ ansiReset) P.<> P.text " (ro):" P.$+$ P.nest 4 (P.text (Text.unpack docstring) P.$+$ renderDoc d)
renderFields :: Ap (FieldDef s) a -> [P.Doc]
renderFields (Pure _) = []
renderFields (Ap f r) =
renderField f : renderFields r
renderTupleFields :: Ap (TupleFieldDef s) a -> [P.Doc]
renderTupleFields (Pure _) = []
renderTupleFields (Ap f r) =
renderTupleField f : renderTupleFields r
renderTupleField :: TupleFieldDef s a -> P.Doc
renderTupleField (TupleFieldDef index _f d) =
P.text (ansiBold ++ show index ++ ansiReset) P.<> P.text ":" P.$+$ P.nest 4 s
where
s = renderDoc d
findNestedUnjson :: (Monad m) => Path -> UnjsonDef a -> m P.Doc
findNestedUnjson (Path []) u = return (renderDoc u)
findNestedUnjson (Path (PathElemIndex n : rest)) (TupleUnjsonDef d) = findNestedTupleUnjson n (Path rest) d
findNestedUnjson (Path (PathElemIndex _ : rest)) (ArrayUnjsonDef _ _ _ _ d) = findNestedUnjson (Path rest) d
findNestedUnjson (Path (PathElemKey k : rest)) (ObjectUnjsonDef d) = findNestedFieldUnjson k (Path rest) d
findNestedUnjson _ _ = fail "cannot find crap"
findNestedTupleUnjson :: (Monad m) => Int -> Path -> Ap (TupleFieldDef s) a -> m P.Doc
findNestedTupleUnjson n path (Ap (TupleFieldDef index _f d) _r) | n == index = findNestedUnjson path d
findNestedTupleUnjson n path (Ap (TupleFieldDef _index _f _d) r) =
findNestedTupleUnjson n path r
findNestedTupleUnjson _ _ _ = fail "findNestedTupleUnjson"
findNestedFieldUnjson :: (Monad m) => Text.Text -> Path -> Ap (FieldDef s) a -> m P.Doc
findNestedFieldUnjson key (Path []) (Ap f@(FieldReqDef k _ _ _d) _r) | k==key = return (renderField f)
findNestedFieldUnjson key (Path []) (Ap f@(FieldOptDef k _ _ _d) _r) | k==key = return (renderField f)
findNestedFieldUnjson key (Path []) (Ap f@(FieldDefDef k _ _ _ _d) _r) | k==key = return (renderField f)
findNestedFieldUnjson key (Path []) (Ap f@(FieldRODef k _ _ _d) _r) | k==key = return (renderField f)
findNestedFieldUnjson key path (Ap (FieldReqDef k _ _ d) _r) | k==key = findNestedUnjson path d
findNestedFieldUnjson key path (Ap (FieldOptDef k _ _ d) _r) | k==key = findNestedUnjson path d
findNestedFieldUnjson key path (Ap (FieldDefDef k _ _ _ d) _r) | k==key = findNestedUnjson path d
findNestedFieldUnjson key path (Ap (FieldRODef k _ _ d) _r) | k==key = findNestedUnjson path d
findNestedFieldUnjson key path (Ap _ r) =
findNestedFieldUnjson key path r
findNestedFieldUnjson _ _ _ = fail "findNestedFieldUnjson"
ansiReset :: String
ansiReset = "\ESC[0m"
ansiBold :: String
ansiBold = "\ESC[1m"
ansiDimmed :: String
ansiDimmed = "\ESC[2m"
parseIPv4 :: ReadP.ReadP Word32
parseIPv4 = do
d1 <- ReadP.munch1 isDigit
_ <- ReadP.char '.'
d2 <- ReadP.munch1 isDigit
_ <- ReadP.char '.'
d3 <- ReadP.munch1 isDigit
_ <- ReadP.char '.'
d4 <- ReadP.munch1 isDigit
ReadP.eof
let r = map read [d1,d2,d3,d4]
when (any (>255) r) ReadP.pfail
return (sum (zipWith shiftL r [24,16,8,0]))
unjsonIPv4AsWord32 :: UnjsonDef Word32
unjsonIPv4AsWord32 = SimpleUnjsonDef "IPv4 in decimal dot notation A.B.C.D"
(\value ->
case Aeson.fromJSON value of
Aeson.Success result ->
Result result []
Aeson.Error _ ->
case Aeson.fromJSON value of
Aeson.Success result -> case ReadP.readP_to_S parseIPv4 result of
[(r,"")] -> Result r []
_ -> fail "cannot parse as decimal dot IPv4"
Aeson.Error _ ->
fail "expected IPv4 as decimal dot string or a single integer")
(Aeson.toJSON . showAsIPv4)
where
showAsIPv4 :: Word32 -> String
showAsIPv4 v = intercalate "." [show (shiftR v b .&. 255) | b <- [24,16,8,0]]