How to use IORef with lenses?
Asked Answered
T

2

5

Wondering how best to combine the Control.Lens package with IORefs. Specifically I'd like to be able to use atomicModifyIORef with lenses so that i can supply a function of type a -> (a, b) and return a value from the operation. Code snippet:

let inc x = (x+1, x)
ior <- newIORef ((1, 1) :: (Int, Int))
thisShouldBe1 <- ior & atomicModifyIORef ?? _1 inc -- this is the bit I'm stuck on
Tableware answered 21/8, 2014 at 10:18 Comment(0)
P
6

In principle, the lens operator needed is actually %%~, which is just a convenience synonym for id. However, due to an annoying incompatibility in the tuple orderings used in atomicModifyIORef and the (,) a Functor, it needs some swapping around to work. I don't think the resulting operator is predefined, but I've given it the preliminary name swappedId below.

Note that the Lens type is defined as

type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t

It turns out that if you let f be the (,) a Functor, this almost perfectly fits the type you want to use to transform your inc, except that you'd really have wanted the a to be the last element of the tuple instead of the first. After fixing this up, here is what I ended up with:

import Data.IORef
import Control.Lens

l `swappedId` f = f & mapping swapped %~ l

main = do
    let inc x = (x+1, x)
    ior <- newIORef ((1, 1) :: (Int, Int))
    thisShouldBe1 <- atomicModifyIORef ior $ _1 `swappedId` inc
    print thisShouldBe1
    print =<< readIORef ior
Planoconcave answered 21/8, 2014 at 13:17 Comment(0)
L
3

I found it convenient to define a helper function for manipulating IORefs using Lenses. As mentioned by Ørjan Johansen, atomicModifyIORef uses a different pair order than the Functor instance of (,), so we need to swap. And since you'd like have the function of type a -> (a, b), we need to swap this function as well.

{-# LANGUAGE RankNTypes #-}
import Control.Lens
import Data.IORef
import Data.Tuple (swap)

-- | Atomically modifies an 'IORef' using a lens
atomicModifyWithLens :: IORef a -> Lens a a b c -> (b -> (c, r)) -> IO r
atomicModifyWithLens ref l f =
    atomicModifyIORef ref (swap . traverseOf l (swap . f))

main = do
    let inc x = (x+1, x)
    ior <- newIORef ((1, 1) :: (Int, Int))
    thisShouldBe1 <- atomicModifyWithLens ior _1 inc
    print thisShouldBe1
Libbielibbna answered 21/8, 2014 at 18:33 Comment(0)

© 2022 - 2024 — McMap. All rights reserved.