-->

Pass a lens into a funciton

2019-05-21 08:53发布

问题:

How to pass properly a lens into a function with state? Let us consider the next code:

{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleContexts #-}

import Control.Lens
import Control.Monad.State

data Game = Game { _armies :: [Army]
                 } deriving (Show)

data Army = Army { _troops :: Int
                 } deriving (Show)

makeLenses ''Game
makeLenses ''Army

data BattleResult = Win | Defeat deriving (Show)

offend offender defender = do
  Just ot <- preuse $ offender.troops
  Just dt <- preuse $ defender.troops
  defender.troops.=0 -- doesn't work
  let eval a b
        | a >= b    = return Win
        | otherwise = return Defeat
  eval ot dt

game :: State Game ()
game = do
    armies %= (:) (Army 100)
    armies %= (:) (Army 200)
    q <- offend (armies.ix 0) (armies.ix 1)
    return ()

The marked line leads to the next error:

Lens.hs:21:3:
    Couldn't match type ‘Const (Data.Monoid.First Int) s’
                   with ‘Identity s’
    Expected type: (Army -> Const (Data.Monoid.First Int) Army)
                   -> s -> Identity s
      Actual type: (Army -> Const (Data.Monoid.First Int) Army)
                   -> s -> Const (Data.Monoid.First Int) s
    Relevant bindings include
      defender :: (Army -> Const (Data.Monoid.First Int) Army)
                  -> s -> Const (Data.Monoid.First Int) s
        (bound at Lens.hs:18:17)
      offender :: (Army -> Const (Data.Monoid.First Int) Army)
                  -> s -> Const (Data.Monoid.First Int) s
        (bound at Lens.hs:18:8)
      offend :: ((Army -> Const (Data.Monoid.First Int) Army)
                 -> s -> Const (Data.Monoid.First Int) s)
                -> ((Army -> Const (Data.Monoid.First Int) Army)
                    -> s -> Const (Data.Monoid.First Int) s)
                -> m BattleResult
        (bound at Lens.hs:18:1)
    In the first argument of ‘(.)’, namely ‘defender’
    In the first argument of ‘(.=)’, namely ‘defender . troops’

Lens.hs:21:12:
    Couldn't match type ‘Identity Integer’
                   with ‘Const (Data.Monoid.First Int) Int’
    Expected type: (Int -> Identity Integer)
                   -> Army -> Const (Data.Monoid.First Int) Army
      Actual type: (Int -> Const (Data.Monoid.First Int) Int)
                   -> Army -> Const (Data.Monoid.First Int) Army
    In the second argument of ‘(.)’, namely ‘troops’
    In the first argument of ‘(.=)’, namely ‘defender . troops’

If replace the line with something like armies.ix 0.troops.=0 the code is normally compiled. Are there some standard tools to walk around the problem? And could the same algorithm be implemented without using FlexibleContexts?

回答1:

Just use type signatures!

What's going on here: if you don't supply a signature, GHC will only be able to infer a Rank-1 type. In this example, you're using defender.troops as a getter; the compiler therefore infers a getter type for defender. This is the ugly thing in the error message with Const in it.

However, you also want to use it as a setter. This is only possible if defender is polymorphic (so you can use an Identity functor instead of Const), and for an argument to be polymorphic you need Rank-2 polymorphism.

You don't really need to worry about this kind of category-theory magic though, since the lens library supplies easy to use synonyms. Just write the signature as you should always do anyway,

offend :: Traversal' Game Army -> Traversal' Game Army -> State Game BattleResult

and you get the proper polymorphic arguments. Ah, and of course you need the -XRankNTypes extension. -XFlexibleContexts is actually not required (it is completely harmless though, no reason not to use it).


Hindley-Milner is quite a marvel anyway if you ask me, but it only works because there's a well-defined most general possible signature for any expression. This is only the case for Rank-1 code though: with Rank-N, you could always toss in yet another layer of universal quantification. The compiler can't know when to end this!

Actually a Getting, which is a traversal-getter. The difference beteween Getter and Getting is that the latter can be partial (which is necessary because you use ix; the compiler can't prove there is actually an element at index 1 in the armies list).