问题
In the function test
, I traverse over a list, generate lenses from it's members, and then print some data. This works when I use a pointful call style. It fails to typecheck when I make it point-free.
Why is this the case, and how can I solve this problem?
It looks like to me that GHC is not retaining the information that the higher-ranked f
(in the lens) is a Functor
when using point-free style, but I'm not too sure.
I'm using GHC 7.8.3
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
import Control.Lens
import Control.Monad
import Data.List
import Data.Maybe
type PlayerHandle = String
data Player = Player { _playerHandle :: PlayerHandle }
makeLenses ''Player
data GameState = GameState { _gamePlayers :: [Player] }
makeLenses ''GameState
type PlayerLens = Lens' GameState Player
getPlayerLens :: PlayerHandle -> PlayerLens
getPlayerLens handle f st = fmap put' get'
where
players = st^.gamePlayers
put' player = let
g p = case p^.playerHandle == handle of
True -> player
False -> p
in set gamePlayers (map g players) st
get' = f $ fromJust $ find (\p -> p^.playerHandle == handle) players
printHandle :: GameState -> PlayerLens -> IO ()
printHandle st playerLens = do
let player = st^.playerLens
print $ player^.playerHandle
test :: GameState -> IO ()
test st = do
let handles = toListOf (gamePlayers.traversed.playerHandle) st
--
-- Works: Pointful
--forM_ handles $ \handle -> printHandle st $ getPlayerLens handle
--
-- Does not work: Point-free
forM_ handles $ printHandle st . getPlayerLens
main :: IO ()
main = test $ GameState [Player "Bob", Player "Joe"]
Test.hs:45:38:
Couldn't match type `(Player -> f0 Player)
-> GameState -> f0 GameState'
with `forall (f :: * -> *).
Functor f =>
(Player -> f Player) -> GameState -> f GameState'
Expected type: PlayerHandle -> PlayerLens
Actual type: PlayerHandle
-> (Player -> f0 Player) -> GameState -> f0 GameState
In the second argument of `(.)', namely `getPlayerLens'
In the second argument of `($)', namely
`printHandle st . getPlayerLens'
Failed, modules loaded: none.
回答1:
Lens'
is a higher ranked type, and type inference is very brittle with those, and basically only works when all functions that take higher-rank arguments have explicit signatures to do so. This works very badly with point-free code using .
and the like, which don't have such signatures. (Only $
has a special hack to sometimes work with this.)
The lens
library itself gets around this by making sure that all functions that use a lens argument don't have a fully general lens type for it, but only a type which indicates the precise lens feature they use.
In your case, it's the printHandle
function which is the culprit for this. Your code will compile if you change its signature to the more precise
printHandle :: s -> Getting Player s Player -> IO ()
I found this signature by deleting the original one and using :t printHandle
.
EDIT (and EDIT again to add ALens'
): If you think the "cure is worse than the illness", then depending on your needs another option, which doesn't require you to change your function signatures, but which does require you to do some explicit conversion, is to use the ALens'
type instead. You then need to change two lines:
type PlayerLens = ALens' GameState Player
...
printHandle st playerLens = do
let player = st^.cloneLens playerLens
...
ALens'
is a non-higher rank type that has been cleverly constructed so that it contains all the information needed to extract a general lens from it with cloneLens
. But it still is a special subtype of a lens (the Functor
has just been particularly cleverly chosen) so you only need explicit conversion from ALens'
to Lens'
, not the other way.
A third option, which may not be the best for lenses, but which usually works for higher-rank types in general, is to turn your PlayerLens
into a newtype
:
newtype PlayerLens = PL (Lens' GameState Player)
Of course this now needs both wrapping and unwrapping in several places in your code. getPlayerLens
was particularly disrupted:
getPlayerLens :: PlayerHandle -> PlayerLens
getPlayerLens handle = PL playerLens
where
playerLens f st = fmap put' get'
where
players = st^.gamePlayers
put' player = let
g p = case p^.playerHandle == handle of
True -> player
False -> p
in set gamePlayers (map g players) st
get' = f $ fromJust $ find (\p -> p^.playerHandle == handle) players
来源:https://stackoverflow.com/questions/29203844/point-free-lens-creation-does-not-type-check