Skip to content

Instantly share code, notes, and snippets.

@phadej
Created January 21, 2018 18:07
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save phadej/4ce2a0b608126349f7f176b3a05fdd07 to your computer and use it in GitHub Desktop.
Save phadej/4ce2a0b608126349f7f176b3a05fdd07 to your computer and use it in GitHub Desktop.
{-
About
> Also, there is something strange about abstracting lens accessors in local variables. I will want to extract a common subexpression into a let or where, but when that subexpression is a composition of lenses, the polymorphism doesn't work nicely, and I can only fix it by adding a usually highly obscure type signature.
Let's not blame `lens`, it's `MonomorphismRestriction`, because `Lens` is a polymorphic type:
-}
{-# LANGUAGE TemplateHaskell #-}
import Control.Lens
data Foo = Foo { _fooInt :: Int, _fooBar :: Bar } deriving Show
data Bar = Bar { _barInt :: Int, _barQuu :: Quu } deriving Show
data Quu = Quu { _quuInt :: Int, _quuStr :: String } deriving Show
makeLenses ''Foo
makeLenses ''Bar
makeLenses ''Quu
-- | >>> foo
-- Foo {_fooInt = 1, _fooBar = Bar {_barInt = 2, _barQuu = Quu {_quuInt = 3, _quuStr = "lens example"}}}
foo :: Foo
foo = Foo 1 $ Bar 2 $ Quu 3 "lens example"
-- | >>> example1
-- Foo {_fooInt = 1, _fooBar = Bar {_barInt = 2, _barQuu = Quu {_quuInt = 12, _quuStr = "lens example"}}}
example1 :: Foo
example1 = foo
& fooBar . barQuu . quuInt .~ (foo ^. fooBar . barQuu . quuStr . to length)
-- This doesn't work:
-- Couldn't match type ‘Identity Foo’ with ‘Const Int Foo’
{-
example2a :: Foo
example2a = foo
& l . quuInt .~ (foo ^. l . quuStr . to length)
where
l = fooBar . barQuu
-}
-- | This works, we eta-expand `f` (even HLint says we shouldn't :)
--
-- In example2a l :: (Quu -> Identity Quu) -> Foo -> Identity Foo
-- here l :: forall f. Functor f => (Quu -> f Quu) -> Foo -> f Foo
--
-- >>> example2
-- Foo {_fooInt = 1, _fooBar = Bar {_barInt = 2, _barQuu = Quu {_quuInt = 12, _quuStr = "lens example"}}}
--
-- You can make example2a work using NoMonomorphismRestriction too. Try it!
--
-- MonomorphismRestriction is a trade-off,
--
-- from: https://wiki.haskell.org/Monomorphism_restriction
--
-- So why is the restriction imposed? The reasoning behind it is fairly subtle,
-- and is fully explained in section 4.5.5 of the Haskell 2010 Report.
-- Basically, it solves one practical problem (without the restriction, there
-- would be some ambiguous types) and one semantic problem (without the
-- restriction, there would be some repeated evaluation where a programmer
-- might expect the evaluation to be shared). Those who are for the restriction
-- argue that these cases should be dealt with correctly. Those who are against
-- the restriction argue that these cases are so rare that it's not worth
-- sacrificing the type-independence of eta reduction.
example2 :: Foo
example2 = foo
& l . quuInt .~ (foo ^. l . quuStr . to length)
where
l f = (fooBar . barQuu) f
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment