Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Lens: zooming newtype

I'm interested in getting a zooming functionality for my monad transformer stack which is defined the following way:

newtype Awesome a = Awesome (StateT AwesomeState (ExceptT B.ByteString IO) a)
  deriving (Functor, Applicative, Monad
           , MonadIO, MonadError B.ByteString
           , MonadState AwesomeState)

My AwesomeState is deeply nested record, so using zoom would greatly help me in updating some of the fields. But the problem is that zoom doesn't work out of the box for my newtype.

Couldn't match type ‘Control.Lens.Internal.Zoom.Zoomed Awesome’ 
with ‘Control.Lens.Internal.Zoom.Zoomed m0’

I found an example of how to make a custom newtype RWST instance of Zoom but trying to adapt it to my newtype gave me no results

The RWST example can be found here: http://lpaste.net/87737

Is there a way I could start using zoom with my monad transformer stack? What would I need to do in order to achieve that? If I should implement the Zoomed/Zoom like in RWST example then I need a pointer of how to do that because I tried and failed to do so.

like image 425
ksaveljev Avatar asked Sep 28 '22 09:09

ksaveljev


1 Answers

I'd suggest to make state of Awesome explicit:

{-# LANGUAGE TemplateHaskell, GeneralizedNewtypeDeriving, TypeFamilies,
    FlexibleInstances, FunctionalDependencies #-}
import Control.Applicative
import Control.Monad.Error
import Control.Monad.State
import Control.Lens
import Control.Lens.Zoom
import Control.Lens.Internal.Zoom

data AwesomeState = AwesomeState
    { _someRecord :: String
    -- ...
    }

$(makeLenses ''AwesomeState)

newtype Awesome s a = Awesome (StateT s (ErrorT String IO) a)
  deriving ( Functor, Applicative, Monad
           , MonadIO, MonadError String
           , MonadState s)

Then you can define Zoom instance for it as follows:

type instance Zoomed (Awesome s) = Focusing (ErrorT String IO)

instance Zoom (Awesome s) (Awesome t) s t where
    zoom l (Awesome m) = Awesome (zoom l m)

Then you'll have

zoom someRecord :: Awesome String a -> Awesome AwesomeState a
like image 54
Petr Avatar answered Oct 15 '22 12:10

Petr