{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
module Waargonaut.Types.JObject
(
JObject (..)
, HasJObject (..)
, JAssoc (..)
, HasJAssoc (..)
, MapLikeObj
, toMapLikeObj
, fromMapLikeObj
, _MapLikeObj
, parseJObject
) where
import Prelude (Eq, Int, Show, elem, fst, not,
otherwise, (==))
import Control.Category (id, (.))
import Control.Lens (AsEmpty (..), At (..), Index,
IxValue, Ixed (..), Lens',
Prism', Rewrapped,
Wrapped (..), cons, iso,
nearly, prism', to, ( # ),
(<&>), (^.), _Wrapped)
import Control.Lens.Extras (is)
import Control.Monad (Monad)
import Data.Bifoldable (Bifoldable (bifoldMap))
import Data.Bifunctor (Bifunctor (bimap))
import Data.Bitraversable (Bitraversable (bitraverse))
import Data.Bool (Bool (..))
import Data.Foldable (Foldable, find, foldr)
import Data.Function (($))
import Data.Functor (Functor, (<$>))
import Data.Maybe (Maybe (..), maybe)
import Data.Monoid (Monoid (mappend, mempty))
import Data.Semigroup (Semigroup ((<>)))
import Data.Text (Text)
import Data.Traversable (Traversable, traverse)
import qualified Data.Witherable as W
import Text.Parser.Char (CharParsing, char)
import Waargonaut.Types.CommaSep (CommaSeparated (..),
parseCommaSeparated)
import Waargonaut.Types.JObject.JAssoc (HasJAssoc (..), JAssoc (..),
jAssocAlterF, parseJAssoc)
import Waargonaut.Types.JString (_JStringText)
newtype JObject ws a =
JObject (CommaSeparated ws (JAssoc ws a))
deriving (Eq, Show, Functor, Foldable, Traversable)
instance (Semigroup ws, Monoid ws) => AsEmpty (JObject ws a) where
_Empty = nearly (_Wrapped # _Empty # ()) (^. _Wrapped . to (is _Empty))
{-# INLINE _Empty #-}
instance JObject ws a ~ t => Rewrapped (JObject ws a) t
instance Wrapped (JObject ws a) where
type Unwrapped (JObject ws a) = CommaSeparated ws (JAssoc ws a)
_Wrapped' = iso (\ (JObject x) -> x) JObject
type instance IxValue (JObject ws a) = a
type instance Index (JObject ws a) = Int
instance (Semigroup ws, Monoid ws) => Semigroup (JObject ws a) where
(JObject a) <> (JObject b) = JObject (a <> b)
instance (Semigroup ws, Monoid ws) => Monoid (JObject ws a) where
mempty = JObject mempty
mappend = (<>)
instance Bifunctor JObject where
bimap f g (JObject c) = JObject (bimap f (bimap f g) c)
instance Bifoldable JObject where
bifoldMap f g (JObject c) = bifoldMap f (bifoldMap f g) c
instance Bitraversable JObject where
bitraverse f g (JObject c) = JObject <$> bitraverse f (bitraverse f g) c
instance Monoid ws => Ixed (JObject ws a) where
ix i f (JObject cs) = JObject <$> ix i (traverse f) cs
class HasJObject c ws a | c -> ws a where
jObject :: Lens' c (JObject ws a)
instance HasJObject (JObject ws a) ws a where
jObject = id
newtype MapLikeObj ws a = MLO
{ fromMapLikeObj :: JObject ws a
}
deriving (Eq, Show, Functor, Foldable, Traversable)
_MapLikeObj :: (Semigroup ws, Monoid ws) => Prism' (JObject ws a) (MapLikeObj ws a)
_MapLikeObj = prism' fromMapLikeObj (Just . fst . toMapLikeObj)
instance MapLikeObj ws a ~ t => Rewrapped (MapLikeObj ws a) t
instance Wrapped (MapLikeObj ws a) where
type Unwrapped (MapLikeObj ws a) = JObject ws a
_Wrapped' = iso (\ (MLO x) -> x) MLO
instance (Monoid ws, Semigroup ws) => AsEmpty (MapLikeObj ws a) where
_Empty = nearly (_Wrapped # _Empty # ()) (^. _Wrapped . to (is _Empty))
{-# INLINE _Empty #-}
type instance IxValue (MapLikeObj ws a) = a
type instance Index (MapLikeObj ws a) = Text
instance Monoid ws => Ixed (MapLikeObj ws a) where
instance Monoid ws => At (MapLikeObj ws a) where
at k f (MLO (JObject cs)) = jAssocAlterF k f (find (textKeyMatch k) cs) <&>
MLO . JObject . maybe (W.filter (not . textKeyMatch k) cs) (`cons` cs)
instance Bifunctor MapLikeObj where
bimap f g (MLO o) = MLO (bimap f g o)
instance Bifoldable MapLikeObj where
bifoldMap f g (MLO o) = bifoldMap f g o
instance Bitraversable MapLikeObj where
bitraverse f g (MLO o) = MLO <$> bitraverse f g o
toMapLikeObj :: (Semigroup ws, Monoid ws) => JObject ws a -> (MapLikeObj ws a, [JAssoc ws a])
toMapLikeObj (JObject xs) = (\(_,a,b) -> (MLO (JObject a), b)) $ foldr f (mempty,mempty,mempty) xs
where
f x (ys,acc,discards)
| _jsonAssocKey x `elem` ys = (ys, acc, x:discards)
| otherwise = (_jsonAssocKey x:ys, cons x acc, discards)
textKeyMatch :: Text -> JAssoc ws a -> Bool
textKeyMatch k = (== k) . (^. jsonAssocKey . _JStringText)
parseJObject
:: ( Monad f
, CharParsing f
)
=> f ws
-> f a
-> f (JObject ws a)
parseJObject ws a = JObject <$>
parseCommaSeparated (char '{') (char '}') ws (parseJAssoc ws a)