Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Using effect of Traversable [] and Applicative Maybe in lens library

I have the following structure:

y = [
  fromList([("c", 1 ::Int)]),
  fromList([("c", 5)]),
  fromList([("d", 20)])
  ]

I can use this to update every "c":

y & mapped . at "c" . mapped  %~ (+ 1)
-- [fromList [("c",2)], fromList [("c",6)], fromList [("d",20)]]

So the third entry is basically just ignored. But I want is for the operation to fail.

Only update, iff all the maps contain the key "c".

So I want:

y & mysteryOp
-- [fromList [("c",1)], fromList [("c",5)], fromList [("d",20)]]
-- fail because third entry does not contain "c" as key

I think I know which functions to use here:

over
-- I want to map the content of the list

mapped
-- map over the structure and transform to [(Maybe Int)]

traverse
-- I need to apply the operation, which will avoid 

at "c"
-- I need to index into the key "c"

I just don't know how to combine them

like image 881
hgiesel Avatar asked Oct 16 '22 05:10

hgiesel


2 Answers

Here's a couple of alternative approaches seeing as you like lenses;

Using laziness to delay deciding whether or not to make the changes,

f y = res
  where (All c, res) = y 
                     & each %%~ (at "c" %%~ (Wrapped . is _Just &&& fmap (applyWhen c succ)))

Or deciding upfront whether to make the changes,

f' y = under (anon y $ anyOf each (nullOf $ ix "c")) (mapped . mapped . ix "c" +~ 1) y
like image 140
moonGoose Avatar answered Oct 18 '22 13:10

moonGoose


I don't see a way to write it as a simple composition of lens combinators, but this is a traversal that you can write from scratch. It should either traverse all values of "c" keys if every map contains such a key or else traverse no values.

We can start with a helper function to "maybe" update a map with a new key value, failing in the Maybe monad if the key doesn't exist. For reasons that will become apparent, we want to allow the update to occur in an arbitrary functor. That is, we want a function:

maybeUpdate :: (Functor f, Ord k) => k -> (v -> f v) -> Map k v -> Maybe (f (Map k v))

Is that signature clear? We check for the key k. If the key is found, we'll return Just an updated map with the key's corresponding value v updated in the f functor. Otherwise, if the key is not found, we return Nothing. We can write this pretty clearly in monad notation, though we need the ApplicativeDo extension if we only want to use Functor f constraint:

maybeUpdate :: (Functor f, Ord k) => k -> (v -> f v) -> Map k v -> Maybe (f (Map k v))
maybeUpdate k f m = do            -- in Maybe monad
  v <- m ^. at k
  return $ do                     -- in "f" functor
    a <- f v
    return $ m & at k .~ Just a

Alternatively, these "monadic actions" are really just functor actions, so this definition can be used:

maybeUpdate' k f m =
  m ^. at k <&> \v -> f v <&> \a -> m & at k .~ Just a

That's the hard part. Now, the traversal is pretty straightforward. We start with the signature:

traverseAll :: (Ord k) => k -> Traversal' [Map k v] v
traverseAll k f maps =

The idea is that this traversal starts by traversing the list of maps over the Maybe applicative using the maybeUpdate helper:

traverse (maybeUpdate k f) maps :: Maybe [f (Map k v)]

If this traversal succeeds (returns Just a list), then all keys were found, and we can sequence the f applicative actions:

sequenceA <$> traverse (maybeUpdate k f) maps :: Maybe (f [Map k v])

Now, we just use maybe to return the original list if the traversal fails:

traverseAll k f maps = maybe (pure maps) id (sequenceA <$> traverse (maybeUpdate k f) maps)

Now, with:

y :: [Map String Int]
y = [
  fromList([("c", 1 ::Int)]),
  fromList([("c", 5)]),
  fromList([("d", 20)])
  ]
y2 :: [Map String Int]
y2 = [
  fromList([("c", 1 ::Int)]),
  fromList([("c", 5)]),
  fromList([("d", 20),("c",6)])
  ]

we have:

> y & traverseAll "c" %~ (1000*)
[fromList [("c",1)],fromList [("c",5)],fromList [("d",20)]]
> y2 & traverseAll "c" %~ (1000*)
[fromList [("c",1000)],fromList [("c",5000)],fromList [("c",6000),("d",20)]]

Full disclosure: I was not able to construct traverseAll like that from scratch. I started with the much stupider "traversal" in the implicit identity applicative:

traverseAllC' :: (Int -> Int) -> [Map String Int] -> [Map String Int]
traverseAllC' f xall = maybe xall id (go xall)
  where go :: [Map String Int] -> Maybe [Map String Int]
        go (x:xs) = case x !? "c" of
          Just a -> (Map.insert "c" (f a) x:) <$> go xs
          Nothing -> Nothing
        go [] = Just []

and once I got that up and running, I simplified it, made the Identity explicit:

traverseAllC_ :: (Int -> Identity Int) -> [Map String Int] -> Identity [Map String Int]

and converted it to a general applicative.

Anyway, here's the code:

{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE RankNTypes #-}

import Data.Map (Map, fromList)
import Control.Lens

y :: [Map [Char] Int]
y = [
  fromList([("c", 1 ::Int)]),
  fromList([("c", 5)]),
  fromList([("d", 20)])
  ]
y2 :: [Map [Char] Int]
y2 = [
  fromList([("c", 1 ::Int)]),
  fromList([("c", 5)]),
  fromList([("d", 20),("c",6)])
  ]

traverseAll :: (Ord k) => k -> Traversal' [Map k v] v
traverseAll k f maps = maybe (pure maps) id (sequenceA <$> traverse (maybeUpdate k f) maps)

maybeUpdate :: (Functor f, Ord k) => k -> (v -> f v) -> Map k v -> Maybe (f (Map k v))
maybeUpdate k f m = do
  v <- m ^. at k
  return $ do
    a <- f v
    return $ m & at k .~ Just a

maybeUpdate' :: (Functor f, Ord k) => k -> (v -> f v) -> Map k v -> Maybe (f (Map k v))
maybeUpdate' k f m =
  m ^. at k <&> \v -> f v <&> \a -> m & at k .~ Just a

main = do
  print $ y & traverseAll "c" %~ (1000*)
  print $ y2 & traverseAll "c" %~ (1000*)
like image 35
K. A. Buhr Avatar answered Oct 18 '22 13:10

K. A. Buhr