How do I combine lenses and functors? - haskell

I'm trying to get used to the lens library for Haskell, and find myself struggling at some simple problems. For instance, let's say (for convenience) that at and _1 have the following types (this is how I understand them, at least):
at :: Ord k => k -> Lens' (Map k v) (Maybe v)
_1 :: Lens' (a, b) a
How do I combine these lenses into a lens with the following type:
maybeFst :: Ord k => k -> Lens' (Map k (a, b)) (Maybe a)

You'd like a lens like
Lens' (Maybe (a, b)) (Maybe a)
but that can't quite be a Lens since putting back Nothing affects the b as well. It can be a Getter
getA :: Getter (Maybe (a, b)) (Maybe a)
getA = to (fmap fst)
but then when you compose it you'll just wind up with a Getter as well, not a full Lens
maybeFst :: Ord k => k -> Getter (Map k (a, b)) (Maybe a)
maybeFst k = at k . getA
Probably better than that is to use a Traversal instead
maybeFstT :: Ord k => k -> Traversal' (Map k (a, b)) a
maybeFstT k = at k . _Just . _1
This will allow you to both get (using preview or toListOf) and set values at the fst of the values in your map, but you won't be able to modify its existence in the map: if the value does not exist you cannot add it and if it does exist you cannot remove it.
Finally, we can jury-rig a fake Lens which has the appropriate type, though we have to give it a default value for b
getA :: b -> Lens' (Maybe (a, b)) (Maybe a)
getA b inj Nothing = (\x -> (,b) <$> x) <$> inj Nothing
getA _ inj (Just (a, b)) = (\x -> (,b) <$> x) <$> inj (Just a)
but notice that it has some not-very-Lenslike behavior.
>>> Just (1, 2) & getA 0 .~ Nothing & preview (_Just . _2)
Nothing
>>> Nothing & getA 0 .~ Just 1
Just (1,0)
so often it's better to avoid these pseudolenses to prevent mishaps.

Related

How can I avoid explicit recursion in this case?

I wound up with this skeleton:
f :: (Monad m) => b -> m ()
f x = traverse_ (f . g x) =<< h x -- how avoid explicit recursion?
g :: b -> a -> b
-- h :: (Foldable t) => b -> m (t a) -- why "Could not deduce (Foldable t0) arising from a use of ‘traverse_’"
h :: b -> m [a]
How can I avoid the explicit recursion in f?
Bonus: When I try to generalize h from [] to Foldable, f does not type check (Could not deduce (Foldable t0) arising from a use of ‘traverse_’) -- what am I doing wrong?
UPDATE:
Here's the real code. The Right side is for recursing down directories of security camera footage whose names are integers. Left is the base case to process leaves whose names are not integers.
a <|||> b = left a . right b
doDir (Right d) = traverse_ (doDir . doInt) =<< listDirectory d
where doInt s = ((<|||>) <$> (,) <*> const) (d </> s) $ (TR.readEither :: String -> Either String Int) s
f = doDir and g ~ doInt but got refactored a little. h = listDirectory. to answer the bonus, i was just being silly and wasn't seeing that i had to combine all the definitions to bind the types together:
f :: (Monad m, Foldable t) => (b -> a -> b) -> (b -> m (t a)) -> b -> m ()
f g h x = traverse_ (f g h . g x) =<< h x
If you don't mind leaking a bit of memory building a Tree and then throwing it away, you can use unfoldTreeM:
f = unfoldTreeM (\b -> (\as -> ((), g b <$> as)) <$> h b)
I do not believe there is a corresponding unfoldTreeM_, but you could write one (using explicit recursion). To generalize beyond the Tree/[] connection, you might also like refoldM; you can find several similar functions if you search for "hylomorphism" on Hackage.

Combining two maps - is it this ugly?

Today I had two maps I needed to combine: consMaps :: Map k a -> Map k b -> Map k (a, b). Seeing nothing in Data.Map, I set out to implement this and came up with something unexpectedly ugly:
consMaps :: Map k a -> Map k b -> Map k (a, b)
consMaps ma mb = mapMapMaybe g (Map.unionWith f a' b')
where
a' :: Map k (Maybe (Maybe a, Maybe b))
a' = fmap (\a -> Just (Just a, Nothing)) ma
b' :: Map k (Maybe (Maybe a, Maybe b))
b' = fmap (\b -> Just (Nothing, Just b)) mb
f :: Maybe (Maybe a, Maybe b) -> Maybe (Maybe a, Maybe b) -> Maybe (Maybe a, Maybe b)
f (Just (Just a, _)) (Just (_, Just b)) = Just (Just a, Just b)
f (Just (_, Just b)) (Just (Just a, _)) = Just (Just a, Just b)
-- f (Just a, Just b) _ = Just (a, b) -- impossible in this context
-- f _ (Just a, Just b) = Just (a, b) -- impossible in this context
f _ _ = Nothing
g :: Maybe (Maybe a, Maybe b) -> Maybe (a, b)
g (Just (Just a, Just b)) = Just (a, b)
g _ = Nothing
mapMapMaybe :: (a -> Maybe b) -> Map k a -> Map k b
mapMapMaybe f mp = snd (mapEither (maybe (Left ()) Right . f) mp)
Am I missing something? Is this as good as this gets?
It looks like your consMaps implementation, with the signature you've given, is just
consMaps :: Map k a -> Map k b -> Map k (a, b)
consMaps = intersectionWith (,)
If instead you wanted a Map k (Maybe a, Maybe b), I might write that as
consMaps :: Map k a -> Map k b -> Map k (Maybe a, Maybe b)
consMaps ma mb = unionWith combine ma' mb' where
ma' = fmap (\ a -> (Just a, Nothing)) ma
mb' = fmap (\ b -> (Nothing, Just b)) mb
combine (a, _) (_, b) = (a, b)
If you want Map (a, b) out then use the other answer (intersectionWith). If you want a Map (Maybe a, Maybe b) then that specialized function won't work. Instead, containers has a merge function, which covers "basically all" ways to combine Maps. It takes three strategies: what to do if a key is only in the left map, what to do if a key is only in the right map, and what to do if a key is in both. The strategies are built using helper functions. The idea is that merge does exactly one traversal of the inputs, so is more efficient than e.g. mapping the inputs and then combining.
import Data.Map.Merge.Lazy
catMaps :: Ord k => Map k a -> Map k b -> Map k (Maybe a, Maybe b)
catMaps = merge left right both
where left = mapMissing $ \_ a -> (Just a, Nothing)
right = mapMissing $ \_ b -> (Nothing, Just b)
both = zipWithMatched $ \_ a b -> (Just a, Just b)
Note that the "right" type for the output in this version is actually Map k (These a b), where These models "inclusive or":
data These a b = This a | That b | These a b
theseMaps :: Ord k => Map k a -> Map k b -> Map k (These a b)
theseMaps = merge left right both
where left = mapMissing $ const This
right = mapMissing $ const That
both = zipWithMatched $ const These

Using lenses to update RandomGen inside state struct in Haskell

I'm using a StdGen inside a larger state struct and want to implement the RandomGen class on the state struct. Using lenses I came up with the following implementation:
module Test
( StateData(..)
, randomGen
) where
import Lens.Micro.Platform
import System.Random
data StateData = StateData
{ _randomGen :: StdGen
} deriving (Show)
randomGen :: Lens' StateData StdGen
randomGen = lens _randomGen (\ s x -> s { _randomGen = x })
instance RandomGen StateData where
next s = r & _2 .~ (s & randomGen .~ (r ^. _2))
where r = (s ^. randomGen ^. to next)
split s = r & _1 .~ (s & randomGen .~ (r ^. _1))
& _2 .~ (s & randomGen .~ (r ^. _2))
where r = (s ^. randomGen ^. to split)
To simplify this definition (and future definitions like it) I would like to generalise the pattern as follows:
reinsert :: (a -> b) -> Lens' s a -> [Lens b b' a s] -> a -> b'
reinsert f a bs s
= foldr (&) r [b .~ (s & a .~ (r ^. b)) | b <- bs]
where r = (s ^. a ^. to f)
instance RandomGen StateData where
next = reinsert next randomGen [_2]
split = reinsert split randomGen [_1, _2]
There is a problem with this approach though. The type declaration of reinsert is an "Illegal polymorphic type". I understand this as the type being to complex for Haskell to deal with. If I remove the type declaration the first use of the a lens turns it into a class Getting, making the second use as ASetter illegal; the same happens to b inside the list comprehension.
Is there a way to fix this? Or alternatively, is there a better way to implement the RandomGen instance on StateData?
Cheers, Johan
Edit: a bit simpler, but not solving the core issue:
instance RandomGen StateData where
next s = (s ^. randomGen ^. to next)
& _2 %~ (\ x -> s & randomGen .~ x)
split s = (s ^. randomGen ^. to split)
& _1 %~ (\ x -> s & randomGen .~ x)
& _2 %~ (\ x -> s & randomGen .~ x)
As a general rule, avoid taking Lens / Getter / Setter etc.. as arguments to functions, take ALens / Getting / ASetter instead. These are basically the “specialised to one use scenario” versions, which doesn't require pesky Rank-N polymorphism etc.. Rank-N by itself is merely tricky for the type checker, but if you also have these types in a list, it breaks down completely (this would be impredicative polymorphism, which GHC has never supported properly).
So in this case, it is ALens. The only slight problem is, .~ actually wants ASetter, which is a strictly more special, but (in Haskell) distinct type. Likewise for ^.. There are two solutions:
“Clone” the lens, to get in the function a polymorphic version again.
Use the “lensy” getter and setter operators, i.e. #~ for .~.
One possible problem with your definition of reinsert is that it ties the structure of the final result to the structure of the transformed field.
How about this alternative definition of reinsert?
-- Pry apart a field from a value,
-- returning a pair of the value and a function to reconstruct the original value.
pry :: Lens' r x -> Iso' r (x -> r,x)
pry l = iso (\r -> (\x -> set l x r, view l r)) (uncurry ($))
-- Given
-- a lens into a field
-- a transformation of the field
-- a function that takes a reconstructor and the transformed field, and returns other thing
-- a starting value
-- return the other thing
reinsert :: Lens' a b -> (b -> b') -> ((b -> a) -> b' -> c) -> a -> c
reinsert l transform packer =
view $ pry l . alongside id (to transform) . to (uncurry packer)
It uses the alongside combinator. (The pry isn't strictly needed, you could simply view and set in reinsert.)
With it, we could define the RandomGen instance like this:
instance RandomGen StateData where
next = reinsert randomGen next fmap
split = reinsert randomGen split (\f (s1,s2) -> (f s1, f s2))

Haskell type inference (ReaderT and tuple)

Exploring this material: Lens over tea I've encountered an interesting (simple at first) point:
ex3 :: (a, b) -> (b, a)
ex3 = do
a <- fst
b <- snd
return (b, a)
Everything's fine, but what type of monad does this function use (since we have a do-block inside). After a few attempts I arrived to this conclusion:
ex2 :: ReaderT (a, b) ((,) b) a
ex2 = ReaderT $ do
a <- fst
b <- snd
return (b, a)
ex3 :: (a, b) -> (b, a)
ex3 = runReaderT ex2
So, we have ReaderT that uses inner monad ((,) b). Interestingly enough - I got not enough satisfaction with this and decided to rewrite ex2 not using do-notation. This is what I got:
ex2 :: Monoid b => ReaderT (a, b) ((,) b) a
ex2 = ReaderT $
\pair -> return (fst pair) >>=
\a -> return (snd pair) >>=
\b -> (b, a)
or even:
ex2 :: Monoid b => ReaderT (a, b) ((,) b) a
ex2 = ReaderT $
\pair -> (mempty, fst pair) >>=
\a -> (mempty, snd pair) >>=
\b -> (b, a)
Both variants require b to have a Monoid type restriction.
The question is: can I write this functions with (>>=) only and without using a Monoid restriction - like we have with do-notation variant? Apparently we do the same with or without do-notation. Maybe the even difference, that we have to construct monads at every step in the second and thirst fuctions and this requires us to state that "b" should be a monoid - some monoid. And in the first case we just extract our values from some monad - not constructing them. Can anybody explain am I thinking in the right direction?
Thank you!!
You have not quite desugared this from do notation to (>>=) calls. A direct translation would look like this:
ex2 :: ReaderT (a, b) ((,) b) a
ex2 = ReaderT $
fst >>= (\a -> -- a <- fst
snd >>= (\b -> -- b <- snd
return (b, a))) -- return (b, a)
Also, you aren't actually using the monadness of (,) b, even though it fits into the slot here for the "inner monad" of ReaderT.
ex3 :: (a, b) -> (b, a)
means, in prefix notation
ex3 :: (->) (a, b) (b, a)
-----------m
------t
Hence the monad is m = (->) (a, b) which is the Reader monad (up to isomorphism) with a pair as its implicit argument / read-only state.
You don't need a monoid. The plain reader monad is enough. If you want to use ReaderT, use the identity monad as the inner monad.
ex2 :: Monoid b => ReaderT (a, b) Identity (b, a)
ex2 = ReaderT $
\pair -> Identity (fst pair) >>=
\a -> Identity (snd pair) >>=
\b -> Identity (b, a)
Of course, the code above could be simplified.
So to summarize:
Type of monad is (->) r - just function or simple reader;
How to desugar the initial function without do:
ex3' :: (a, b) -> (b, a)
ex3' = fst >>=
\a -> snd >>=
\b -> return (b, a)

How to write a Traversable instance for function, in Haskell?

How do I write the Traversable instance for ((->) a)?
I think I could do it, if I could generically unwrap an Applicative Functor:
instance Traversable ((->) k) where
-- traverse :: (a -> f b) -> (k -> a) -> f (k -> b)
-- traverse h t = ?
-- h :: Applicative f => a -> f b
-- t :: k -> a
-- h . t :: k -> f b
-- unwrap . h . t :: k -> b
-- pure $ unwrap . h . t :: f (k -> b)
traverse h t = pure $ unwrap . h . t
unwrap :: (Functor f, Applicative f) => f a -> a
unwrap y#(pure x) = x
But, alas, GHC won't let me get away with that:
Parse error in pattern: pure
Generally there is no such thing as unwrap, consider f being the list functor [] what should unwrap return for [_, _, _] or better yet for the empty list []? Similar thing with Maybe, suppose h is const Nothing, you would expect to get Nothing. But your line of thought would fail upon trying to unwrap the Nothing into a value a. You can notice that trying to apply pure (to re-pack the result in the functor) means that you expect the result to be always Just for Maybe functor, non-empty for [] etc.
There is little hope for Traversable instance for a reader functor ((->) k). While it is not proof, a good evidence in that direction is that such an instance is missing from the Prelude. Also to traverse a function and produce a final container ([] or Maybe) you would need to apply your function h to any thinkable output of the function, that is a lot of potential values, in general infinitely many.
Prelude> traverse (\n -> if n == 42 then Nothing else Just n) [1, 2, 3]
Just [1,2,3]
Prelude> traverse (\n -> if n == 42 then Nothing else Just n) [1..]
Nothing
suppose that k is Int, so the functor is Int ->, suppose you have a value g :: Int -> Int, let it be \n -> if n == 42 then 0 else n, suppose you wanted to traverse that value with the above function, that traversal would be Nothing if g outputs 42 for any input, but it doesn't. The traversal cannot know that though (it has no access to the code of the function), so it would have to try all outputs.
If k were finite, then you could traverse a function by tabulating it. After traversing the table you could possibly produce a result. This may not be what you are after but:
import Data.Char
import Data.Maybe
import Data.Word
instance ( Enum k, Bounded k ) => Foldable ((->) k) where
foldMap h f = foldMap (h . f) domain
instance ( Enum k, Bounded k, Eq k ) => Traversable ((->) k) where
traverse h f = fmap (\vs k -> fromJust $ k `lookup` zip domain vs) (traverse (h . f) domain)
domain :: ( Enum k, Bounded k ) => [k]
domain = enumFromTo minBound maxBound
tabulate :: ( Enum k, Bounded k ) => (k -> a) -> [(k, a)]
tabulate f = zip domain (map f domain)
f1 :: Bool -> Int
f1 b = if b then 42 else 666
f2 :: Ordering -> Char
f2 LT = 'l'
f2 EQ = 'e'
f2 GT = 'g'
f3 :: Word8 -> Bool
f3 n = fromIntegral n < 256
f4 :: Word16 -> Bool
f4 n = fromIntegral n < 256
main = do
print (tabulate f1)
print (tabulate <$> traverse (\n -> [n, 2*n]) f1)
putStrLn ""
print (tabulate f2)
print (tabulate <$> traverse (\c -> [c, toUpper c]) f2)
putStrLn ""
print (tabulate f3)
print (tabulate <$> traverse (\b -> if b then Just b else Nothing) f3)
putStrLn ""
print (tabulate <$> traverse (\b -> if b then Just b else Nothing) f4)
But, alas, GHC won't let me get away with that:
It seems your error is that you tried to use a function (pure) as a pattern. Haskell only allows constructors to appear in patterns. So
unwrap (Just x) = x
is valid, while
unwrap (pure x) = x
is not.

Resources