A lens for getting or setting a record field determined by a runtime argument - haskell

I have these types (and more):
data Player = PlayerOne | PlayerTwo deriving (Eq, Show, Read, Enum, Bounded)
data Point = Love | Fifteen | Thirty deriving (Eq, Show, Read, Enum, Bounded)
data PointsData =
PointsData { pointsToPlayerOne :: Point, pointsToPlayerTwo :: Point }
deriving (Eq, Show, Read)
I'm doing the Tennis kata, and as part of the implementation, I'd like to use some functions that enable me to get or set the points for an arbitrary player, only known at runtime.
Formally, I need functions like these:
pointFor :: PointsData -> Player -> Point
pointFor pd PlayerOne = pointsToPlayerOne pd
pointFor pd PlayerTwo = pointsToPlayerTwo pd
pointTo :: PointsData -> Player -> Point -> PointsData
pointTo pd PlayerOne p = pd { pointsToPlayerOne = p }
pointTo pd PlayerTwo p = pd { pointsToPlayerTwo = p }
As demonstrated, my problem isn't that I can't implement these functions.
They do, however, look lens-like to me, so I wonder if I could get that functionality via the lens library?
Most of the lens tutorials show how to get or set a particular, named part of a bigger data structure. This doesn't quite seem to fit what I'm trying to do here; rather, I'm trying to get or set a sub-part determined at runtime.

An excursion into somewhat abstract typeclasses. Your PointsData has a special relationship with the Player type. It's a bit like a Map Player Point, with the particularity that for every possible value of Player, there's always a corresponding Point. In a way, PointsData is like a "reified function" Player -> Point.
If we make PointsData polymorphic on the type of Points, it would fit with the Representable typeclass. We would say that PointsData is "represented" by Player.
Representable is often useful as an interface to tabular data, like in the grids package.
So one possible solution would be to turn PointsData into an actual Map, but hide the implementation behind a smart constructor that took a Player -> Point function to initialize it for all possible keys (it would correspond to the tabulate method of Representable).
The user should not be able to delete keys from the map. But we could piggyback on the Ixed instance of Map to provide traversals.
import Control.Lens
import Data.Map.Strict -- from "containers"
newtype PointsData = PointsData { getPoints :: Map Player Point }
init :: (Player -> Point) -> PointsData
init f = PointsData (Data.Map.Strict.fromList ((\p -> (p, f p)) <$> [minBound..maxBound]))
playerPoints :: Player -> Lens' PointsData Point
playerPoints pl = Control.Lens.singular (iso getPoints PointsData . ix pl)

You could create a function that produces a Lens given a Player, like this:
playerPoints :: Player -> Lens' PointsData Point
playerPoints PlayerOne = field #"pointsToPlayerOne"
playerPoints PlayerTwo = field #"pointsToPlayerTwo"
(this is using field from generic-lens)
Usage would be like this:
pts :: PointsData
pl1 = pts ^. playerPoints PlayerOne
pl2 = pts ^. playerPoints PlayerTwo
newPts = pts & playerPoints PlayerOne .~ 42
P.S. Or were you looking for picking a field of PointsData by matching field name to Player constructor name? That is also possible via Generic, but doesn't seem worth the trouble.

Based on the answer from Fyodor Soikin and comment from duplode, I ended up using makeLenses from lens and writing a function that returns the appropriate lens:
data PointsData =
PointsData { _pointsToPlayerOne :: Point, _pointsToPlayerTwo :: Point }
deriving (Eq, Show, Read)
makeLenses ''PointsData
playerPoint :: Player -> Lens' PointsData Point
playerPoint PlayerOne = pointsToPlayerOne
playerPoint PlayerTwo = pointsToPlayerTwo
It can be used like this fragment of a bigger function:
score :: Score -> Player -> Score
-- ..
score (Points pd) winner = Points $ pd & playerPoint winner %~ succ
-- ..

Related

`No instance for System.Random.Random` on a custom typeclass when using `choose`

I am doing an exercise in Haskell Programming from First Principles. It asks me to generate equal probabilities, and 1/3, 2/3 probabilities from each of:
data Fool =
Fulse
| Frue
deriving (Eq, Show)
And my answer is
module Random where
-- import Test.Hspec
import Test.QuickCheck
data Fool =
Fulse
| Frue
deriving (Eq, Show)
genFool :: Gen Fool
genFool = choose (Fulse, Frue)
genFool' :: Gen Fool
genFool' = do
frequency [(2, return Fulse)
,(1, return Frue)]
but genFool is wrong. The error message is :
../chap14/random.hs:13:11: error:
• No instance for (System.Random.Random Fool)
arising from a use of ‘choose’
• In the expression: choose (Fulse, Frue)
In an equation for ‘genFool’: genFool = choose (Fulse, Frue)
|
13 | genFool = choose (Fulse, Frue)
| ^^^^^^^^^^^^^^^^^^^^
Previously I have some code like this:
genBool :: Gen Bool
genBool = choose (False, True)
which works properly. I think there may be some predefined instance of System.Random.Random Fool to make the choose work.
What should I do to make the my version of genFool compile?
And btw, why is the return Fulse in the second genFool' of type Gen Fool?
The Test.Quickcheck module's choose function has the following type signature:
choose :: Random a => (a, a) -> Gen a
So, if you are planning to use choose function on your Fool type, it has to be made instance of Random typeclass as seen in the above type signature.
This is where Random typeclass is defined. It needs either a minimal implementation of either randomR and random.
Since your type Fool has only two values, it's isomorphic to Bool type. So, you can define a function mapping the values appropriately:
mapBool :: Bool -> Fool
mapBool False = Fulse
mapBool True = Frue
And then you can define a typeclass instance for your type:
instance Random Fool where
random g = let (b :: Bool, g') = random g
in (mapBool b, g')
randomR _ g = (random g) -- Note that this doesn't work correctly. You need to pattern match and fix this.
The above code should make your module compile fine.

In Haskell how can I override the (==) and (/=) operators for a type class?

Say I have something like this
class Circle c where
x :: c -> Float
y :: c -> Float
radius :: c -> Float
data Location = Location { locationX :: Float
, locationY :: Float
} deriving (Show, Eq)
data Blob = Location { blobX :: Float
, blobY :: Float
, blobRadius :: Float,
, blobRating :: Int
} deriving (Show, Eq)
instance Circle Location where
x = locationX
y = locationY
radius = pure 0
instance Circle Blob where
x = blobX
y = blobY
radius = blobRadius
Say for example I want Circle types to be equal if their x and y points are equal. How can I compare instances of the type class with the (==) and (/=) operators. I know I can do something like this, but is it possible to overload the operators?
equal :: Circle a => Circle b => a -> b -> Bool
equal a b = (x a == x b && y a == y b)
I want to be able to compare with
(Location 5.0 5.0) == (Blob 5.0 5.0 ... ) should give me True
Zeroth, some standard imports:
import Data.Function (on)
import Control.Arrow ((&&&))
First, this is not a good idea. a==b should only be true if a and b are (for all purposes relevant to the user) interchangeable – that's clearly not the case for two circles which merely happen to share the same center point!
Second, it's probably not a good idea to make Circle a typeclass in the first place. A typeclass only makes sense when you want to abstract over something that can't directly be expressed with just a parameter. But if you just want to attach different “payloads” to points in space, a more sensible approach might be to define something like
data Located a = Located {x,y :: ℝ, payload :: a}
If, as seems to be the case, you actually want to allow different instances of Circle to coexist and be comparable at runtime, then a typeclass is entirely the wrong choice. That would be an OO class. Haskell doesn't have any built-in notion of those, but you could just use
data Blob = Blob
{ x,y :: ℝ
, radius :: ℝ
, rating :: Maybe Int }
and no other types.
https://lukepalmer.wordpress.com/2010/01/24/haskell-antipattern-existential-typeclass/
Third, the instance that you asked for can, theoretically speaking, be defined as
instance (Circle a) => Eq a where
(==) = (==)`on`(x &&& y)
But this would be a truely horrible idea. It would be a catch-all instance: whenever you compare anything, the compiler would check “is it of the form a?” (literally anything is of that form) “oh great, then said instance tells me how to compare this.” Only later would it look at the Circle requirement.
The correct solution is to not define any such Eq instance at all. Your types already have Eq instances individually, that should generally be the right thing to use – no need to express it through the Circle class at all, just give any function which needs to do such comparisons the constraint (Circle a, Eq a) => ....
Of course, these instances would then not just compare the location but the entire data, which, as I said, is a good thing. If you actually want to compare only part of the structure, well, make that explicit! Use not == itself, but extract the relevant parts and compare those. A useful helper for this could be
location :: Circle a => a -> Location
location c = Location (x c) (y c)
...then you can, for any Circle type, simply write (==)`on`location instead of (==), to disregard any other information except the location. Or write out (==)`on`(x &&& y) directly, which can easily be tweaked to other situations.
Two circles that share a common center aren't necessarily equal, but they are concentric; that's what you should write a function to check.
concentric :: (Circle a, Circle b) => a -> b -> Bool
concentric c1 c2 = x c1 == x c2 && y c1 == y c2

Haskell - Lenses, use of 'to' function

I have the following code. I'd like to be able to modify the active player's life when given a game state. I came up with an activePlayer lens, but when I try and use it in combination with the -= operator I receive the following error:
> over (activePlayer.life) (+1) initialState
<interactive>:2:7:
No instance for (Contravariant Mutator)
arising from a use of `activePlayer'
Possible fix:
add an instance declaration for (Contravariant Mutator)
In the first argument of `(.)', namely `activePlayer'
In the first argument of `over', namely `(activePlayer . life)'
In the expression: over (activePlayer . life) (+ 1) initialState``
and the code in question:
{-# LANGUAGE TemplateHaskell #-}
module Scratch where
import Control.Lens
import Control.Monad.Trans.Class
import Control.Monad.Trans.State
import Data.Sequence (Seq)
import qualified Data.Sequence as S
data Game = Game
{ _players :: (Int, Seq Player) -- active player, list of players
, _winners :: Seq Player
}
deriving (Show)
initialState = Game
{ _players = (0, S.fromList [player1, player2])
, _winners = S.empty
}
data Player = Player
{ _life :: Integer
}
deriving (Show, Eq)
player1 = Player
{ _life = 10
}
player2 = Player
{ _life = 10
}
makeLenses ''Game
makeLenses ''Player
activePlayer
:: (Functor f, Contravariant f) =>
(Player -> f Player) -> Game -> f Game
activePlayer = players.to (\(i, ps) -> S.index ps i)
Each player takes their turn in order. I need to keep track of all the players at once as well as which is currently active, which is the reason for how I structured that, although I am open to different structures since I probably don't have the right one yet.
When you compose various items in the lens library with (.) they may lose capabilities according to a kind of subtyping (see below). In this case, you've composed a Lens (players) with a Getter (to f for some function f) and thus the combination is just a Getter while over acts on lenses that can both get and set.
activePlayer should form a valid lens, though, so you can just write it manually as a getter/setter pair. I'm writing it partially below under the assumption that the index can never be invalid.
activePlayer :: Lens' Game Player
activePlayer = lens get set
where
get :: Game -> Player
get (Game { _players = (index, seq) }) = Seq.index seq index
set :: Game -> Player -> Game
set g#(Game { _players = (index, seq) }) player =
g { _players = (index, Seq.update index player seq) }
To better understand the subtyping that's occurring in the lens library we can use the Big Lattice Diagram from Hackage
Whenever you combine two lens types with (.) you end up with their first common descendent in that chart. So if you combine Lens and Prism you can see that their arrows converge on Traversal. If you combine Lens and Getter (of which to f is) then you get a Getter since Getter is a direct descendent of Lens.

Illegal instance declaration / Overlapping instances

Given class X and Y, what's the most idiomatic approach to creating instances of each other's class? e.g. -
instance (X a) => Y a where ...
instance (Y a) => X a where ...
I'd like to avoid extensions. Also, I am aware that this could cause some nasty infinite recursion, so I'm open to a completely different approach to accomplish the same thing and stay relatively DRY. Below gives some context as to the exact problem I am having -
data Dealer = Dealer Hand
data Player = Player Hand Cash
class HasPoints a where
getPoints :: a -> Int
class (HasPoints a) => CardPlayer a where
getHand :: a -> Hand
viewHand :: a -> TurnIsComplete -> Hand
hasBlackjack :: a -> Bool
hasBlackjack player = getPoints player == 21 &&
(length . getCards . getHand) player == 2
busts :: a -> Bool
busts player = getPoints player > 21
I'd like to do this -
instance (CardPlayer a) => HasPoints a where
getPoints = getPoints . getHand
But it seems I must do this -
instance HasPoints Dealer where
getPoints = getPoints . getHand
instance HasPoints Player where
getPoints = getPoints . getHand
EDIT
Seems my favorite approach is to keep the HasPoints typeclass and implement CardPlayer as data instead.
data CardPlayer = Dealer Hand | Player Hand Cash
instance HasPoints CardPlayer where
getPoints = getPoints . getHand
getCash :: CardPlayer -> Maybe Cash
getHand :: CardPlayer -> Hand
viewHand :: CardPlayer -> TurnIsComplete -> Hand
hasBlackjack :: CardPlayer -> Bool
busts :: CardPlayer -> Bool
-- I wanted HasPoints to be polymorphic
-- so it could handle Card, Hand, and CardPlayer
instance HasPoints Hand where
getPoints Hand { getCards = [] } = 0
getPoints hand = if base > 21 && numAces > 0
then maximum $ filter (<=21) possibleScores
else base
where base = sum $ map getPoints $ getCards hand
numAces = length $ filter ((Ace==) . rank) $ getCards hand
possibleScores = map ((base-) . (*10)) [1..numAces]
instance HasPoints Card where
-- You get the point
Given class X and Y, what's the most idiomatic approach to creating instances of each other's class?
The most idiomatic approach, given your example code, is to not use type classes in the first place when they're not doing anything useful. Consider the types of the class functions:
class HasPoints a where
getPoints :: a -> Int
class (HasPoints a) => CardPlayer a where
getHand :: a -> Hand
viewHand :: a -> TurnIsComplete -> Hand
hasBlackjack :: a -> Bool
busts :: a -> Bool
What do they have in common? They all take exactly one value of the class parameter type as their first argument, so given such a value we can apply each function to it and get all the same information without needing to bother with a class constraint.
So if you want a nice, idiomatic DRY approach, consider this:
data CardPlayer a = CardPlayer
{ playerPoints :: Int
, hand :: Hand
, viewHand :: TurnIsComplete -> Hand
, hasBlackjack :: Bool
, busts :: Bool
, player :: a
}
data Dealer = Dealer
data Player = Player Cash
In this version, the types CardPlayer Player and CardPlayer Dealer are equivalent to the Player and Dealer types you had. The player record field here is used to get the data specialized to the kind of player, and functions that would have been polymorphic with a class constraint in yours can simply operate on values of type CardPlayer a.
Though perhaps it would make more sense for hasBlackjack and busts to be regular functions (like your default implementations), unless you really need to model players who are immune to the standard rules of Blackjack.
From this version, you can now define a HasPoints class alone if you have very different types that should be instances of it, though I'm skeptical of the utility of that, or you can apply the same transformation to get another layer:
data HasPoints a = HasPoints
{ points :: Int
, pointOwner :: a
}
However, this approach quickly becomes unwieldy the further you nest specializations like this.
I would suggest droping HasPoints entirely. It only has one function, which just extracts an Int, so any code that handles HasPoints instances generically might as well just use Ints and be done with it.
In general, it's impossible to declare all instances of a class to also be instances of another class without making type checking undecidable. So your proposed definition will only work with UndecidableInstances enabled:
{-# LANGUAGE FlexibleInstances, UndecidableInstances #-}
instance (CardPlayer a) => HasPoints a where
getPoints = getPoints . getHand
Although it's possible to go that route, I'd suggest refactoring the code as follows instead:
data Hand = ...
handPoints :: Hand -> Int
handPoints = ...
data Dealer = Dealer Hand
data Player = Player Hand Cash
class CardPlayer a where
getHand :: a -> Hand
...
instance CardPlayer Dealer where ...
instance CardPlayer Player where ...
playerPoints :: (CardPlayer a) => a -> Int
playerPoints = handPoints . getHand

Haskell polymorphic functions with records and class types

this post is the following of this one.
I'm realizing a simple battle system as toy project, the typical system you can find in games like Final Fantasy et simila. I've solved the notorious "Namespace Pollution" problem with a class type + custom instances. For example:
type HitPoints = Integer
type ManaPoints = Integer
data Status = Sleep | Poison | .. --Omitted
data Element = Fire | ... --Omitted
class Targetable a where
name :: a -> String
level :: a -> Int
hp :: a -> HitPoints
mp :: a -> ManaPoints
status :: a -> Maybe [Status]
data Monster = Monster{monsterName :: String,
monsterLevel :: Int,
monsterHp :: HitPoints,
monsterMp :: ManaPoints,
monsterElemType :: Maybe Element,
monsterStatus :: Maybe [Status]} deriving (Eq, Read)
instance Targetable Monster where
name = monsterName
level = monsterLevel
hp = monsterHp
mp = monsterMp
status = monsterStatus
data Player = Player{playerName :: String,
playerLevel :: Int,
playerHp :: HitPoints,
playerMp :: ManaPoints,
playerStatus :: Maybe [Status]} deriving (Show, Read)
instance Targetable Player where
name = playerName
level = playerLevel
hp = playerHp
mp = playerMp
status = playerStatus
Now the problem: I have a spell type, and a spell can deal damage or inflict a status (like Poison, Sleep, Confusion, etc):
--Essentially the result of a spell cast
data SpellEffect = Damage HitPoints ManaPoints
| Inflict [Status] deriving (Show)
--Essentially a magic
data Spell = Spell{spellName :: String,
spellCost :: Integer,
spellElem :: Maybe Element,
spellEffect :: SpellEffect} deriving (Show)
--For example
fire = Spell "Fire" 20 (Just Fire) (Damage 100 0)
frogSong = Spell "Frog Song" 30 Nothing (Inflict [Frog, Sleep])
As suggested in the linked topic, I've created a generic "cast" function like this:
--cast function
cast :: (Targetable t) => Spell -> t -> t
cast s t =
case spellEffect s of
Damage hp mana -> t
Inflict statList -> t
As you can see the return type is t, here showed just for consistency. I want be able to return a new targetable (i.e. a Monster or a Player) with some field value altered (for example a new Monster with less hp, or with a new status). The problem is that i can't just to the following:
--cast function
cast :: (Targetable t) => Spell -> t -> t
cast s t =
case spellEffect s of
Damage hp' mana' -> t {hp = hp', mana = mana'}
Inflict statList -> t {status = statList}
because hp, mana and status "are not valid record selector". The problem is that I don't know a priori if t will be a monster or a player, and I don't want to specify "monsterHp" or "playerHp", I want to write a pretty generic function.
I know that Haskell Records are clumsy and not much extensibile...
Any idea?
Bye and happy coding,
Alfredo
Personally, I think hammar is on the right track with pointing out the similarities between Player and Monster. I agree you don't want to make them the same, but consider this: Take the type class you have here...
class Targetable a where
name :: a -> String
level :: a -> Int
hp :: a -> HitPoints
mp :: a -> ManaPoints
status :: a -> Maybe [Status]
...and replace it with a data type:
data Targetable = Targetable { name :: String
, level :: Int
, hp :: HitPoints
, mp :: ManaPoints
, status :: Maybe [Status]
} deriving (Eq, Read, Show)
Then factor out the common fields from Player and Monster:
data Monster = Monster { monsterTarget :: Targetable
, monsterElemType :: Maybe Element,
} deriving (Eq, Read, Show)
data Player = Player { playerTarget :: Targetable } deriving (Eq, Read, Show)
Depending on what you do with these, it might make more sense to turn it inside-out instead:
data Targetable a = Targetable { target :: a
, name :: String
-- &c...
}
...and then have Targetable Player and Targetable Monster. The advantage here is that any functions that work with either can take things of type Targetable a--just like functions that would have taken any instance of the Targetable class.
Not only is this approach nearly identical to what you have already, it's also a lot less code, and keeps the types simpler (by not having class constraints everywhere). In fact, the Targetable type above is roughly what GHC creates behind the scenes for the type class.
The biggest downside to this approach is that it makes accessing fields clumsier--either way, some things end up being two layers deep, and extending this approach to more complicated types can nest them deeper still. A lot of what makes this awkward is the fact that field accessors aren't "first class" in the language--you can't pass them around like functions, abstract over them, or anything like that. The most popular solution is to use "lenses", which another answer mentioned already. I've typically used the fclabels package for this, so that's my recommendation.
The factored-out types I suggest, combined with strategic use of lenses, should give you something that's simpler to use than the type class approach, and doesn't pollute the namespace the way having lots of record types does.
I can suggest three possible solutions.
1) Your types are very OO-like, but Haskell can also express "sum" types with parameters:
data Unit = UMon Monster | UPlay Player
cast :: Spell -> Unit -> Unit
cast s t =
case spellEffect s of
Damage hp' mana' -> case t of
UMon m -> UMon (m { monsterHp = monsterHp m - hp', monsterMana = undefined})
UPluy p -> UPlay (p { playerHp = playerHp p - hp'})
Inflict statList -> undefined
Thing that are similar in OO-design often become "sum" types with parameters in Haskell.
2) You can do what Carston suggests and add all your methods to type classes.
3) You can change your read-only methods in Targetable to be "lenses" that expose both getting and setting. See the stack overflow discussion. If your type class returned lenses then it would make your spell damage possible to apply.
Why don't you just include functions like
InflicteDamage :: a -> Int -> a
AddStatus :: a -> Status -> a
into your type-class?

Resources