Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Modification
- type Path = [Text]
- data Value
- modificationPath :: Modification -> Path
- applyModification :: Modification -> Value -> Value
- delete :: Path -> Value -> Value
- insert :: Path -> Value -> Value -> Value
- lookup :: Path -> Value -> Maybe Value
- lookupOrNull :: Path -> Value -> Value
Documentation
data Modification Source #
Instances
Eq Modification Source # | |
Defined in Store (==) :: Modification -> Modification -> Bool # (/=) :: Modification -> Modification -> Bool # | |
Show Modification Source # | |
Defined in Store showsPrec :: Int -> Modification -> ShowS # show :: Modification -> String # showList :: [Modification] -> ShowS # | |
ToJSON Modification Source # | |
Defined in Store toJSON :: Modification -> Value # toEncoding :: Modification -> Encoding # toJSONList :: [Modification] -> Value # toEncodingList :: [Modification] -> Encoding # | |
FromJSON Modification Source # | |
Defined in Store parseJSON :: Value -> Parser Modification # parseJSONList :: Value -> Parser [Modification] # |
A JSON value represented as a Haskell value.
Instances
Eq Value | |
Data Value | |
Defined in Data.Aeson.Types.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Value -> c Value # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Value # dataTypeOf :: Value -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Value) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Value) # gmapT :: (forall b. Data b => b -> b) -> Value -> Value # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r # gmapQ :: (forall d. Data d => d -> u) -> Value -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Value -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Value -> m Value # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value # | |
Ord Value | The ordering is total, consistent with Since: aeson-1.5.2.0 |
Read Value | |
Show Value | |
IsString Value | |
Defined in Data.Aeson.Types.Internal fromString :: String -> Value # | |
Generic Value | |
Hashable Value | |
Defined in Data.Aeson.Types.Internal | |
ToJSON Value | |
Defined in Data.Aeson.Types.ToJSON | |
KeyValue Object | Constructs a singleton |
KeyValue Pair | |
FromJSON Value | |
NFData Value | |
Defined in Data.Aeson.Types.Internal | |
FromString Encoding | |
Defined in Data.Aeson.Types.ToJSON fromString :: String -> Encoding | |
FromString Value | |
Defined in Data.Aeson.Types.ToJSON fromString :: String -> Value | |
Lift Value | |
GToJSON' Encoding arity (U1 :: Type -> Type) | |
GToJSON' Value arity (V1 :: Type -> Type) | |
GToJSON' Value arity (U1 :: Type -> Type) | |
ToJSON1 f => GToJSON' Encoding One (Rec1 f) | |
ToJSON1 f => GToJSON' Value One (Rec1 f) | |
ToJSON a => GToJSON' Encoding arity (K1 i a :: Type -> Type) | |
(EncodeProduct arity a, EncodeProduct arity b) => GToJSON' Encoding arity (a :*: b) | |
ToJSON a => GToJSON' Value arity (K1 i a :: Type -> Type) | |
(WriteProduct arity a, WriteProduct arity b, ProductSize a, ProductSize b) => GToJSON' Value arity (a :*: b) | |
(ToJSON1 f, GToJSON' Encoding One g) => GToJSON' Encoding One (f :.: g) | |
(ToJSON1 f, GToJSON' Value One g) => GToJSON' Value One (f :.: g) | |
FromPairs Value (DList Pair) | |
Defined in Data.Aeson.Types.ToJSON | |
v ~ Value => KeyValuePair v (DList Pair) | |
Defined in Data.Aeson.Types.ToJSON | |
(GToJSON' Encoding arity a, ConsToJSON Encoding arity a, Constructor c) => SumToJSON' TwoElemArray Encoding arity (C1 c a) | |
Defined in Data.Aeson.Types.ToJSON | |
(GToJSON' Value arity a, ConsToJSON Value arity a, Constructor c) => SumToJSON' TwoElemArray Value arity (C1 c a) | |
Defined in Data.Aeson.Types.ToJSON | |
type Rep Value | |
Defined in Data.Aeson.Types.Internal type Rep Value = D1 ('MetaData "Value" "Data.Aeson.Types.Internal" "aeson-1.5.4.1-2iH9sCvI8L4G0DvVegkVtc" 'False) ((C1 ('MetaCons "Object" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Object)) :+: (C1 ('MetaCons "Array" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Array)) :+: C1 ('MetaCons "String" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))) :+: (C1 ('MetaCons "Number" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Scientific)) :+: (C1 ('MetaCons "Bool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "Null" 'PrefixI 'False) (U1 :: Type -> Type)))) |
modificationPath :: Modification -> Path Source #
Return the path that is touched by a modification.
applyModification :: Modification -> Value -> Value Source #
Execute a modification.