module Control.Lens.Aeson
(
AsNumber(..)
, integralValue
, nonNull
, Primitive(..)
, AsPrimitive(..)
, AsValue(..)
, key, nth
, AsJSON(..)
) where
import Control.Applicative
import Control.Lens
import Data.Aeson
import Data.Attoparsec.Number
import Data.ByteString.Lazy.Char8 as Lazy hiding (putStrLn)
import Data.ByteString.Lazy.UTF8 as UTF8 hiding (decode)
import Data.Data
import Data.HashMap.Strict (HashMap)
import Data.Text
import Data.Vector (Vector)
import Numeric.Lens
import Prelude hiding(null)
class AsNumber t where
_Number :: Prism' t Number
default _Number :: AsPrimitive t => Prism' t Number
_Number = _Primitive._Number
_Double :: Prism' t Double
_Double = _Number.prism D (\v -> case v of D d -> Right d; _ -> Left v)
_Integer :: Prism' t Integer
_Integer = _Number.prism I (\v -> case v of I i -> Right i; _ -> Left v)
instance AsNumber Value where
_Number = prism Number $ \v -> case v of Number n -> Right n; _ -> Left v
instance AsNumber Number where
_Number = id
instance AsNumber ByteString
instance AsNumber String
integralValue :: (AsNumber t, Integral a) => Prism' t a
integralValue = _Integer . integral
data Primitive
= StringPrim !Text
| NumberPrim !Number
| BoolPrim !Bool
| NullPrim
deriving (Eq,Ord,Show,Data,Typeable)
instance AsNumber Primitive where
_Number = prism NumberPrim $ \v -> case v of NumberPrim s -> Right s; _ -> Left v
class AsNumber t => AsPrimitive t where
_Primitive :: Prism' t Primitive
default _Primitive :: AsValue t => Prism' t Primitive
_Primitive = _Value._Primitive
_String :: Prism' t Text
_String = _Primitive.prism StringPrim (\v -> case v of StringPrim s -> Right s; _ -> Left v)
_Bool :: Prism' t Bool
_Bool = _Primitive.prism BoolPrim (\v -> case v of BoolPrim b -> Right b; _ -> Left v)
_Null :: Prism' t ()
_Null = _Primitive.prism (const NullPrim) (\v -> case v of NullPrim -> Right (); _ -> Left v)
instance AsPrimitive Value where
_Primitive = prism fromPrim toPrim
where
toPrim (String s) = Right $ StringPrim s
toPrim (Number n) = Right $ NumberPrim n
toPrim (Bool b) = Right $ BoolPrim b
toPrim Null = Right $ NullPrim
toPrim v = Left v
fromPrim (StringPrim s) = String s
fromPrim (NumberPrim n) = Number n
fromPrim (BoolPrim b) = Bool b
fromPrim NullPrim = Null
_String = prism String $ \v -> case v of String s -> Right s; _ -> Left v
_Bool = prism Bool (\v -> case v of Bool b -> Right b; _ -> Left v)
_Null = prism (const Null) (\v -> case v of Null -> Right (); _ -> Left v)
instance AsPrimitive ByteString
instance AsPrimitive String
instance AsPrimitive Primitive where
_Primitive = id
nonNull :: Prism' Value Value
nonNull = prism id (\v -> if isn't _Null v then Right v else Left v)
class AsPrimitive t => AsValue t where
_Value :: Prism' t Value
_Object :: Prism' t (HashMap Text Value)
_Object = _Value.prism Object (\v -> case v of Object o -> Right o; _ -> Left v)
_Array :: Prism' t (Vector Value)
_Array = _Value.prism Array (\v -> case v of Array a -> Right a; _ -> Left v)
instance AsValue Value where
_Value = id
instance AsValue ByteString where
_Value = _JSON
instance AsValue String where
_Value = iso UTF8.fromString UTF8.toString._Value
key :: AsValue t => Text -> IndexedTraversal' Text t Value
key i = _Object . ix i
nth :: AsValue t => Int -> IndexedTraversal' Int t Value
nth i = _Array . ix i
class AsJSON t where
_JSON :: (FromJSON a, ToJSON a) => Prism' t a
instance AsJSON Lazy.ByteString where
_JSON = prism' encode decode
instance AsJSON String where
_JSON = iso UTF8.fromString UTF8.toString._JSON
type instance Index Value = Text
type instance IxValue Value = Value
instance Applicative f => Ixed f Value where
ix i = _Object.ix i
instance (Applicative f, Gettable f) => Contains f Value where
contains i f (Object o) = coerce (contains i f o)
contains i f _ = coerce (indexed f i False)
instance Plated Value where
plate f (Object o) = Object <$> traverse f o
plate f (Array a) = Array <$> traverse f a
plate _ xs = pure xs