lens-indexed-plated: Indexed version of Plated.

[ bsd2, data, generics, lenses, library ] [ Propose Tags ]

This package contains an alternative version of lens' Plated that allows for a user-specified index: where plate returns a Traversal, iplate takes an additional starting index and returns a IndexedTraversal. It also provides an indexed equivalent to most of the Plated functions.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0
Change log CHANGELOG.md
Dependencies base (>=4.16 && <5), lens (>=5.2.2 && <5.3) [details]
License BSD-2-Clause
Copyright Copyright (C) 2023 Antoine Leblanc
Author Antoine Leblanc
Maintainer nicuveo@gmail.com
Category Data, Lenses, Generics
Home page https://github.com/nicuveo/lens-indexed-plated
Bug tracker https://github.com/nicuveo/lens-indexed-plated/issues
Source repo head: git clone https://github.com/nicuveo/lens-indexed-plated.git
Uploaded by nicuveo at 2023-07-08T15:35:48Z
Distributions NixOS:0.1.0
Downloads 43 total (6 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user
Build status unknown [no reports yet]

Readme for lens-indexed-plated-0.1.0

[back to package description]

Indexed Plated

What is Plated?

lens provides Plated, whose purpose is to help with the traversal of self-recursive types, such as trees. The Plated class itself is straightforward:

class Plated a where
  plate :: Traversal' a a

That is, given some value of type a, how do we visit all of its immediate self-similar children. A motivating example, taken directly from Plated's documentation, would be the following:

data Expr
  = Val Int
  | Neg Expr
  | Add Expr Expr

instance Plated Expr where
  plate f = \case
    Val n   -> pure $ Val n
    Neg e   -> Neg <$> f e
    Add x y -> Add <$> f x <*> f y

Using the combinators provided alongside Plated, it is now easy to traverse and transform this recursive structure without having to write the boilerplate ourselves:

simplify :: Expr -> Expr
simplify = rewrite \case
  Neg (Neg x)         -> Just x
  Neg (Val n)         -> Just $ Val $ negate n
  Add (Val 0) x       -> Just x
  Add x (Val 0)       -> Just x
  Add (Neg x) (Neg y) -> Just $ Neg $ Add x y
  _                   -> Nothing

A limitation of Plated, however, is that the function that is expected by the Traversal only takes the value a itself, without context: in our simplify example above, the argument to rewrite operates on any Expr, without knowing whether it is operating at the root of the expression, or at the very bottom of it. And, in some cases, it could be useful to track where we are in the larger data structure. For instance, while introspecting a JSON value, it could be useful to know the path that led to the current inner value.

Introducing IndexedPlated

This library introduces IndexedPlated, which is just like Plated but carries around an "index" of the user's choosing. The definition of IndexedPlated is as follows:

class IndexedPlated i a where
  iplate :: i -> IndexedTraversal' i a a

If we inline the type aliases (and simplify the result), the difference becomes clearer:

 plate ::      (     a -> f b) -> s -> f t
iplate :: i -> (i -> a -> f b) -> s -> f t

iplate takes an additional "starting index" on top of the root value, and the given function also expects the index matching the given value.

This library also provides most of the combinators that accompany Plated. All of them are prefixed with i, similarly to how lens indicate indexed functions (such as iover).

For instance, for Aeson's Value, we could write the following:

type Path = [Step]
data Step = Key Text | Index Int

instance IndexedPlated Path Value where
  iplate parentPath f = \case
    Object o -> fmap Object $
      flip traverseWithKey o \key value ->
        f (parentPath <> [Key key]) value
    Array  a -> fmap Array $
      for (indexed a) \(index, value) ->
        f (parentPath <> [Index index]) value
    String s -> pure $ String s
    Number x -> pure $ Number x
    Bool   b -> pure $ Bool b
    Null     -> pure Null

An example use of this would be to use the path for error reporting in a recursive transformation of a value. For instance, this function attempts to replace all strings starting with a $ by corresponding values from a lookup table. Despite no recursion being present in this function, the underlying use of IndexedPlated means that all such possible expansions will be performed, recursively (preventing infinite expansions from recursive anchors is left as an exercise to the reader).

expandAnchors
  :: MonadError (Path, Text) m
  => HashMap Text Value
  -> Value
  -> m Value
expandAnchors anchors =
  flip irewriteM [] \path value -> runMaybeT do
    text        <- hoistMaybe $ value ^? _String
    ('$', name) <- hoistMaybe $ uncons text
    case lookup name anchors of
      Nothing  -> throwError (path, name)
      Just res -> pure res

Caveats and limitations

Since indices are user-defined, there is no way for this library to provide a default implementation to iplate which, ironically, results in some boilerplate.