Using a lens twice - haskell

I'm struggling with using the lens library for a particular problem. I'm trying to pass
an updated data structure
a lens focussed on part of that updated structure
to another function, g. I pass both the lens and the data structure because g needs some shared information from the data structure as well as a piece of information. (If it helps, the data structure contains information on a joint probability distribution, but g only works on either marginal and needs to know which marginal I'm looking at. The only difference between the two marginals is their mean with the rest of their definition being shared in the data structure).
My first attempt looked like this
f :: Functor f => Params -> ((Double -> f Double) -> Params -> f Params) -> a
f p l = g (l %~ upd $ p) l
where upd = ...
g p x = go p p^.x
but that fails during compilation because f gets inferred as being Identity for the update and Const Double for the getter.
What's the best way to accomplish what I want to do? I can imagine being able to do one of the following:
make a copy of the lens so that the type inference can be different in each case
rather than passing the updated structure and the lens, I pass the original structure and a lens which returns a modified value (if I only want to update the part of the structure that the lens looks at).
making a better design choice for my functions/data structure
something completely different
Thanks for any help!

András Kovács answer shows how to achieve this with RankNTypes. If you wish to avoid RankNTypes, then you can use ALens and cloneLens:
f :: a -> ALens' a Int -> (Int, a)
f a l = (newvalue, a & cloneLens l .~ newvalue)
where oldvalue = a^.cloneLens l
newvalue = if oldvalue == 0 then 0 else oldvalue - 1
Control.Lens.Loupe provides operators and functions that work on ALens instead of Lens.
Note that in many cases, you should also be able to use <<%~, which is like %~ but also returns the old value, or <%~, which returns the new value:
f :: a -> LensLike' ((,) Int) a Int -> (Int, a)
f a l = a & l <%~ g
where g oldvalue = if oldvalue == 0 then 0 else oldvalue - 1
This has the advantage that it can also work with Isos or sometimes also with Traversals (when the target type is a Monoid).

You want your type signature to look like this:
f :: Params -> Lens Params Params Double Double -> ...
-- alternatively, instead of the long Lens form you can write
-- Lens' Params Double
This is not equivalent to what you wrote out in the signature, because the functor parameter is quantified inside Lens:
type Lens s t a b = forall f. Functor f => (a -> f b) -> (s -> f t)
The correct signature translates to :
f :: Params -> (forall f. Functor f => (Double -> f Double) -> Params -> f Params) -> ...
This prevents the compiler from unifying the different f parameters of different lens usages, i. e. you can use the lens polymorphically. Note that you need the RankNTypes or Rank2Types GHC extension in order to be able to write out the signature.

Benno gave the best general purpose answer.
There is two other options, however, which I offer here for completeness.
1.)
There are several Loupe combinators in Lens.
http://hackage.haskell.org/package/lens-4.1.2/docs/Control-Lens-Loupe.html
They all have names that involve #.
^# and #%= both take ALens which is a lens instantiated at a particular concrete choice of functor.
This can be useful if you need to pass around lists of lenses, or if you really really need multiple passes.
2.)
Another option, and my preferred tactic, is to figure out how to do both operations a the same time.
Here you are modifying, but want the value you just set. Well, yes can give you that by using <%~ instead of %~.
Now you only instantiate the lens at one choice of functor and your code gets faster.

Related

The Monad Challenges - A Missed Generalization

I'm going through The Monad Challenges.
At the section A Missed Generalization, I'm supposed to have at least this code (I've removed parts not relevant to the question), where Gen looks a lot like the State Monad,
-- Imports and other stuff that hide Prelude
-- For instance, the do notation is NOT available at this stage of the challenges
type Gen a = Seed -> (a,Seed)
genTwo :: Gen a -> (a -> Gen b) -> Gen b
genTwo g f s = let (a,s') = g s
in f a s'
mkGen :: a -> Gen a
mkGen a s = (a,s)
generalB :: (a -> b -> c) -> Gen a -> Gen b -> Gen c
-- I've implemented it as follows and it works
generalB f a b s = let (x,s') = a s
(y,s'') = b s'
in (f x y,s'')
The text of the "assignment" reads
[…] you might not have implemented generalB in terms of genTwo. Go back and look at your generalB implementation and if you didn’t write it in terms of genTwo, do that now and call it generalB2. Doing this should get rid of the state threading between generators.
Is unclear to me what the solution to this should be, especially in view of the fact that the paragraph above doesn't mention mkGen. Assuming I'm able to apply f to the inside of a and b, I would still get something of type c, which I have to shove in a Gen, and I don't see how I can do that without mkGen or, alternatively, without using (,) explicitly (as I did in the above implementation).
Even assuming that the text implies that I should use mkGen, how should I go about it to get rid of the state threading?
With some editing I was able to come up with this
generalB2' f a b = genTwo a (genTwo b . (mkGen .) . f)
but I hardly believe this is the intended solution, because it's far from being readable, in my opinion. Also, getting to this form was a bit harder than anything else so far in the challenges, but it was after all just mechanical, so it didn't really pose a difficulty from the point of view of understanding monads, I believe, so I really think I took a wrong turn here, and I'd like some help.
I wonder whether the authors of the challenges hang out here on StackOverflow.
Your solution is probably close to the intended solution, although you might be able to make it more readable by eta-expanding it. You might even consider writing it using do notation, but still use genTwo and mkGen.
As far as I can tell, mkGen is a 'disguised' return function, and genTwo likewise is a 'disguised' monadic bind (i.e. >>=).
The type of generalB (and generalB2) is equivalent to liftM2, which is implemented like this:
liftM2 :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 f m1 m2 = do { x1 <- m1; x2 <- m2; return (f x1 x2) }
That is, in terms of return and >>= (which you don't see, because it's using do syntax).

Generate injective functions with QuickCheck?

I'm using QuickCheck to generate arbitrary functions, and I'd like to generate arbitrary injective functions (i.e. f a == f b if and only if a == b).
I thought I had it figured out:
newtype Injective = Injective (Fun Word Char) deriving Show
instance Arbitrary Injective where
arbitrary = fmap Injective fun
where
fun :: Gen (Fun Word Char)
fun = do
a <- arbitrary
b <- arbitrary
arbitrary `suchThat` \(Fn f) ->
(f a /= f b) || (a == b)
But I'm seeing cases where the generated function maps distinct inputs to the same output.
What I want:
f such that for all inputs a and b, either f a does not equal f b or a equals b.
What I think I have:
f such that there exist inputs a and b where either f a does not equal f b or a equals b.
How can I fix this?
You've correctly identified the problem: what you're generating is functions with the property ∃ a≠b. f a≠f b (which is readily true for most random functions anyway), whereas what you want is ∀ a≠b. f a≠f b. That is a much more difficult property to ensure, because you need to know about all the other function values for generating each individual one.
I don't think this is possible to ensure for general input types, however for word specifically what you can do is “fake” a function by precomputing all the output values sequentially, making sure that you don't repeat one that has already been done, and then just reading off from that predetermined chart. It requires a bit of laziness fu to actually get this working:
import qualified Data.Set as Set
newtype Injective = Injective ([Char] {- simply a list without duplicates -})
deriving Show
instance Arbitrary Injective where
arbitrary = Injective . lazyNub <$> arbitrary
lazyNub :: Ord a => [a] -> [a]
lazyNub = go Set.empty
where go _ [] = []
go forbidden (x:xs)
| x `Set.member` forbidden = go forbidden xs
| otherwise = x : go (Set.insert x forbidden) xs
This is not very efficient, and may well not be ok for your application, but it's probably the best you can do.
In practice, to actually use Injective as a function, you'll want to wrap the values in a suitable structure that has only O (log n) lookup time. Unfortunately, Data.Map.Lazy is not lazy enough, you may need to hand-bake something like a list of exponentially-growing maps.
There's also the concern that for some insufficiently big result types, it is just not possible to generate injective functions because there aren't enough values available. In fact as Joseph remarked, this is the case here. The lazyNub function will go into an infinite loop in this case. I'd say for a QuickCheck this is probably ok though.

Hidden forall quantified types in ReifiedTraversal

This question really is more generic, since while I was asking it I found out how to fix it in this particular case (even though I don't like it) but I'll phrase it in my particular context.
Context:
I'm using the lens library and I found it particularly useful to provide functionality for "adding" traversals (conceptually, a traversal that traverses all the elements in both original traversals). I did not find a default implementation so I did it using Monoid. In order to be able to implement an instance, I had to use the ReifiedTraversal wrapper, which I assume is in the library precisely for this purpose:
-- Adding traversals
add_traversals :: Semigroup t => Traversal s t a b -> Traversal s t a b -> Traversal s t a b
add_traversals t1 t2 f s = liftA2 (<>) (t1 f s) (t2 f s)
instance Semigroup t => Semigroup (ReifiedTraversal s t a b) where
a1 <> a2 = Traversal (add_traversals (runTraversal a1) (runTraversal a2))
instance Semigroup s => Monoid (ReifiedTraversal' s a) where
mempty = Traversal (\_ -> pure . id)
The immediate application I want to extract from this is being able to provide a traversal for a specified set of indices in a list. Therefore, the underlying semigroup is [] and so is the underlying Traversable. First, I implemented a lens for an individual index in a list:
lens_idx :: Int -> Lens' [a] a
lens_idx _ f [] = error "No such index in the list"
lens_idx 0 f (x:xs) = fmap (\rx -> rx:xs) (f x)
lens_idx n f (x:xs) = fmap (\rxs -> x:rxs) (lens_idx (n-1) f xs)
All that remains to be done is to combine these two things, ideally to implement a function traversal_idxs :: [Int] -> Traversal' [a] a
Problem:
I get type checking errors when I try to use this. I know it has to do with the fact that Traversal is a type that includes a constrained forall quantifier in its definition. In order to be able to use the Monoid instance, I need to first reify the lenses provided by lens_idx (which are, of course, also traversals). I try to do this by doing:
r_lens_idx :: Int -> ReifiedTraversal' [a] a
r_lens_idx = Traversal . lens_idx
But this fails with two errors (two versions of the same error really):
Couldn't match type ‘f’ with ‘f0’...
Ambiguous type variable ‘f0’ arising from a use of ‘lens_idx’
prevents the constraint ‘(Functor f0)’ from being solved...
I understand this has to do with the hidden forall f. Functor f => in the Traversal definition. While writing this, I realized that the following does work:
r_lens_idx :: Int -> ReifiedTraversal' [a] a
r_lens_idx idx = Traversal (lens_idx idx)
So, by giving it the parameter it can make the f explicit to itself and then it can work with it. However, this feels extremely ad-hoc. Specially because originally I was trying to build this r_lens_idx inline in a where clause in the definition of the traversal_idxs function (in fact... on a function defining this function inline because I'm not really going to use it that often).
So, sure, I guess I can always use lambda abstraction, but... is this really the right way to deal with this? It feels like a hack, or rather, that the original error is an oversight by the type-checker.
The "adding" of traversals that you want was added in the most recent lens release, you can find it under the name adjoin. Note that it is unsound to use if your traversals overlap at all.
I am replying to my own question, although it is only pointing out that what I was trying to do with traversals was not actually possible in that shape and how I overcame it. There is still the underlying problem of the hidden forall quantified variables and how is it possible that lambda abstraction can make code that does not type check suddenly type check (or rather, why it did not type check to start with).
It turns out my implementation of Monoid for Traversal was deeply flawed. I realized when I started debugging it. For instance, I was trying to combine a list of indices, and a function that would return a lens for each index, mapping to that index in a list, to a traversal that would map to exactly those indices. That is possible, but it relies on the fact that List is a Monad, instead of just using the Applicative structure.
The function that I had written originally for add_traversal used only the Applicative structure, but instead of mapping to those indices in the list, it would duplicate the list for each index, concatenating them, each version of the list having applied its lens.
When trying to fix it, I realized I needed to use bind to implement what I really wanted, and then I stumbled upon this: https://www.reddit.com/r/haskell/comments/4tfao3/monadic_traversals/
So the answer was clear: I can do what I want, but it's not a Monoid over Traversal, but instead a Monoid over MTraversal. It still serves my purposes perfectly.
This is the resulting code for that:
-- Monadic traversals: Traversals that only work with monads, but they allow other things that rely on the fact they only need to work with monads, like sum.
type MTraversal s t a b = forall m. Monad m => (a -> m b) -> s -> m t
type MTraversal' s a = MTraversal s s a a
newtype ReifiedMTraversal s t a b = MTraversal {runMTraversal :: MTraversal s t a b}
type ReifiedMTraversal' s a = ReifiedMTraversal s s a a
-- Adding mtraversals
add_mtraversals :: Semigroup t => MTraversal r t a b -> MTraversal s r a b -> MTraversal s t a b
add_mtraversals t1 t2 f s = (t2 f s) >>= (t1 f)
instance Semigroup s => Semigroup (ReifiedMTraversal' s a) where
a1 <> a2 = MTraversal (add_mtraversals (runMTraversal a1) (runMTraversal a2))
instance Semigroup s => Monoid (ReifiedMTraversal' s a) where
mempty = MTraversal (\_ -> return . id)
Note that MTraversal is still a LensLike and an ASetter, so you can use many operators from the lens package, like .~.
As I mentioned, though, I still have to use lambda abstraction when using this for my purposes due to the forall quantifier being in an uncomfortable place, and I'd love if someone could clarify what the heck is up with the type checker in that regard.

How can a function be "transparently augmented" in Haskell?

Situation
I have function f, which I want to augment with function g, resulting in function named h.
Definitions
By "augment", in the general case, I mean: transform either input (one or more arguments) or output (return value) of function f.
By "augment", in the specific case, (specific to my current situation) I mean: transform only the output (return value) of function f while leaving all the arguments intact.
By "transparent", in the context of "augmentation", (both the general case and the specific case) I mean: To couple g's implementation as loosely to f's implementation as possible.
Specific case
In my current situation, this is what I need to do:
h a b c = g $ f a b c
I am interested in rewriting it to something like this:
h = g . f -- Doesn't type-check.
Because from the perspective of h and g, it doesn't matter what arguments f take, they only care about the return value, hence it would be tight coupling to mention the arguments in any way. For instance, if f's argument count changes in the future, h will also need to be changed.
So far
I asked lambdabot on the #haskell IRC channel: #pl h a b c = g $ f a b c to which I got the response:
h = ((g .) .) . f
Which is still not good enough since the number of (.)'s is dependent on the number of f's arguments.
General case
I haven't done much research in this direction, but erisco on #haskell pointed me towards http://matt.immute.net/content/pointless-fun which hints to me that a solution for the general case could be possible.
So far
Using the functions defined by Luke Palmer in the above article this seems to be an equivalent of what we have discussed so far:
h = f $. id ~> id ~> id ~> g
However, it seems that this method sadly also suffers from being dependent on the number of arguments of f if we want to transform the return value of f -- just as the previous methods.
Working example
In JavaScript, for instance, it is possible to achieve transparent augmentation like this:
function h () { return g(f.apply(this, arguments)) }
Question
How can a function be "transparently augmented" in Haskell?
I am mainly interested in the specific case, but it would be also nice to know how to handle the general case.
You can sort-of do it, but since there is no way to specify a behavior for everything that isn't a function, you'll need a lot of trivial instances for all the other types you care about.
{-# LANGUAGE TypeFamilies, DefaultSignatures #-}
class Augment a where
type Result a
type Result a = a
type Augmented a r
type Augmented a r = r
augment :: (Result a -> r) -> a -> Augmented a r
default augment :: (a -> r) -> a -> r
augment g x = g x
instance Augment b => Augment (a -> b) where
type Result (a -> b) = Result b
type Augmented (a -> b) r = a -> Augmented b r
augment g f x = augment g (f x)
instance Augment Bool
instance Augment Char
instance Augment Integer
instance Augment [a]
-- and so on for every result type of every function you want to augment...
Example:
> let g n x ys = replicate n x ++ ys
> g 2 'a' "bc"
"aabc"
> let g' = augment length g
> g' 2 'a' "bc"
4
> :t g
g :: Int -> a -> [a] -> [a]
> :t g'
g' :: Int -> a -> [a] -> Int
Well, technically, with just enough IncoherentInstances you can do pretty much anything:
{-# LANGUAGE MultiParamTypeClasses, TypeFamilies,
FlexibleInstances, UndecidableInstances, IncoherentInstances #-}
class Augment a b f h where
augment :: (a -> b) -> f -> h
instance (a ~ c, h ~ b) => Augment a b c h where
augment = ($)
instance (Augment a b d h', h ~ (c -> h')) => Augment a b (c -> d) h where
augment g f = augment g . f
-- Usage
t1 = augment not not
r1 = t1 True
t2 = augment (+1) (+)
r2 = t2 2 3
t3 = augment (+1) foldr
r3 = t3 (+) 0 [2,3]
The problem is that the real return value of something like a -> b -> c isn't
c, but b -> c. What you want require some kind of test that tells you if a type isn't
a function type. You could enumerate the types you are interested in, but that's not so
nice. I think HList solve this problem somehow, look at the paper. I managed to understand a bit of the solution with overlapping instances, but the rest goes a bit over my head I'm afraid.
JavaScript works, because its arguments are a sequence, or a list, so there is just one argument, really. In that sense it is the same as a curried version of the functions with a tuple representing the collection of arguments.
In a strongly typed language you need a lot more information to do that "transparently" for a function type - for example, dependent types can express this idea, but require the functions to be of specific types, not a arbitrary function type.
I think I saw a workaround in Haskell that can do this, too, but, again, that works only for specific types, which capture the arity of the function, not any function.

Match Data constructor functions

I'm trying to match data constructors in a generic way, so that any Task of a certain type will be executed.
data Task = TaskTypeA Int | TaskTypeB (Float,Float)
genericTasks :: StateLikeMonad s
genericTasks = do
want (TaskTypeA 5)
TaskTypeA #> \input -> do
want (TaskTypeB (1.2,4.3))
runTaskTypeA input
TaskTypeB #> \(x,y) -> runTaskTypeB x y
main = runTask genericTasks
In this, the genericTasks function goes through the do-instructions, building a list of stuff to do from want handled by some sort of state monad, and a list of ways to do it, via the (#>) function. The runTask function will run the genericTasks, use the resulting list of to-do and how-to-do, and do the computations.
However, I'm having quite some trouble figuring out how to extract the "type" (TaskTypeA,B) from (#>), such that one can call it later. If you do a :t TaskTypeA, you get a Int -> Task.
I.e., How to write (#>)?
I'm also not entirely confident that it's possible to do what I'm thinking here in such a generic way. For reference, I'm trying to build something similar to the Shake library, where (#>) is similar to (*>). However Shake uses a String as the argument to (*>), so the matching is done entirely using String matching. I'd like to do it without requiring strings.
Your intuition is correct, it's not possible to write (#>) as you have specified. The only time a data constructor acts as a pattern is when it is in pattern position, namely, appearing as a parameter to a function
f (TaskTypeA z) = ...
as one of the alternatives of a case statement
case tt of
TaskTypeA z -> ...
or in a monadic or pattern binding
do TaskTypeA z <- Just tt
return z
When used in value position (e.g. as an argument to a function), it loses its patterny nature and becomes a regular function. That means, unfortunately, that you cannot abstract over patterns this easily.
There is, however, a simple formalization of patterns:
type Pattern d a = d -> Maybe a
It's a little bit of work to make them.
taskTypeA :: Pattern Task Int
taskTypeA (TaskTypeA z) = Just z
taskTypeA _ = Nothing
If you also need need to use the constructor "forwards" (i.e. a -> d), then you could pair the two together (plus some functions to work with it):
data Constructor d a = Constructor (a -> d) (d -> Maybe a)
apply :: Constructor d a -> a -> d
apply (Constructor f _) = f
match :: Constructor d a -> d -> Maybe a
match (Constructor _ m) = m
taskTypeA :: Constructor Task Int
taskTypeA = Constructor TaskTypeA $ \case TaskTypeA z -> Just z
_ -> Nothing
This is known as a "prism", and (a very general form of) it is implemented in lens.
There are advantages to using an abstraction like this -- namely, that you can construct prisms which may have more structure than data types are allowed to (e.g. d can be a function type), and you can write functions that operate on constructors, composing simpler ones to make more complex ones generically.
If you are using plain data types, though, it is a pain to have to implement the Constructor objects for each constructor like I did for TaskTypeA above. If you have a lot of these to work with, you can use Template Haskell to write your boilerplate for you. The necessary Template Haskell routine is already implemented in lens -- it may be worth it to learn how to use the lens library because of that. (But it can be a bit daunting to navigate)
(Style note: the second Constructor above and its two helper functions can be written equivalently using a little trick:
data Constructor d a = Constructor { apply :: a -> d, match :: d -> Maybe a }
)
With this abstraction in place, it is now possible to write (#>). A simple example would be
(#>) :: Constructor d a -> (a -> State d ()) -> State d ()
cons #> f = do
d <- get
case match cons d of
Nothing -> return ()
Just a -> f a
or perhaps something more sophisticated, depending on what precisely you want.

Resources