As a voluntary exercise I try to implement van Laarhoven lenses, prisms, traversals, folds and isos. For me, it’s all very abstract, but I feel like I’m making slow progress. Sometimes the intuition doesn’t work for me, then I try to let me guide by the types. When implementing toListOf I get stuck because “type tetris” doesn’t help anymore:
They start with
toListOf :: Traversal s s a a -> (s -> [a])
where a Traversal s t a b s is a function
forall f. Applicative f => (a -> f b) -> (s -> f t)
Then, they generalize Traversal s s a a to
(a -> Const (Endo [a]) a) -> (s -> Const (Endo [a]) s)
and this is the resulting function I try to implement:
toListOf :: ((a -> K (Endo [a]) a) -> (s -> K (Endo [a]) s)) -> (s -> [a])
toListOf t x = undefined
t is the “Traversal”, x is of type s and we expect a result of type [a].
My baby steps:
t expects a function from a to Const (Endo [a]) a, the only one I could think of is Const . Endo . map . const.
After applying t to it, I get a function
foo = t $ Const . Endo . map . const :: s -> Const (Endo [a]) s
Then I have x as a value of type s and apply foo x, extract the value with getConst and finally get an
Endo [a]
I have no idea how an Endo [a], a function [a] -> [a] helps me to get a final [a] value without having an initial list of a values. Can somebody give me some hints or point out mistakes I made before?
My bad, I had a typo in toListOf's type. K is of course Const. Here’s a running but failing test, trying to prove that toListOf . elements = id on [Int]. It fails with the first non-empty list [0]:
module TinyLens where
import Data.Functor.Const ( Const(Const), getConst )
import Data.Semigroup ( Endo(Endo), appEndo )
import Test.QuickCheck ( quickCheck )
elements :: (Traversable t, Applicative f) => (a -> f b) -> (t a -> f (t b))
elements = traverse
toListOf :: ((a -> Const (Endo [a]) a) -> (s -> Const (Endo [a]) s)) -> (s -> [a])
toListOf t x = let foo = t $ Const . Endo . map . const
bar = getConst $ foo x
in appEndo bar []
propSameList :: [Int] -> Bool
propSameList xs = toListOf elements xs == xs
main = quickCheck propSameList
Yes, your choice of foo is wrong! I think perhaps the Endo is throwing you off. Endo is just used to get some increased performance here, it’s not essential. Try writing
toListOf :: ((a -> Const [a] a) -> (s -> Const [a] s)) -> (s -> [a])
and when you have that working you can try the version that uses Endo.
Thank you, I think I saw difference lists before in LYAH. The signature is defined elsewhere so I can’t change it, but I’ll try to think it through with difference lists instead of lists!
Thinking of lists instead of arbitrary Endo [a] functions via difference lists did the trick. Thank you so much, @tomjaguarpaw, @jaror and @Solid for helpful hints!
toListOf :: ((a -> Const (Endo [a]) a) -> (s -> Const (Endo [a]) s)) -> (s -> [a])
toListOf t x = let aToFa = Const . Endo . (:)
sToFs = t aToFa
sEndo = getConst $ sToFs x
in appEndo sEndo []
You’re going into the right direction with appEndo bar []. It’s the a -> Const (Endo [a]) a function that you should look into again.
Ignoring all of the newtype wrappers, what’s the most natural way to
turn an a into an arrow a -> [a] -> [a]? There’s a function I would
wager you know very well that has exactly that type signature!
EDIT: Mailing lists are slow; sorry for the noise on an already answered question