Hi Hans,
I think this code should work:
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TupleSections #-}
import Control.Applicative
import Control.Lens
dependingOn :: Lens s t (x,a) (x,b) -> (x -> Lens a b c d) -> Lens s t c d
dependingOn l depending f = l (\ (x,a) -> (x,) <$> depending x f a)
The trick here is that Lens s t a b
is just an type synonym for Functor f => (a -> f b) -> s -> f t
.
I think it should also be a speed improvement on more complex lenses, only going over the structure once whereas the use of lens
would examine the structure twice (first to get and then to set the value).
I hope this helps.
Felix
Hi all, I have been using this lens transformer http://lpaste.net/113159.However, I can't seem to find a way to implement the polymorphic case (i.e. Lens instead of Lens'). What am I missing?Hans
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe