pip
pip

Reputation: 75

Haskell Constructor Type Pattern Matching

I have a simple type and function below, but seems a lot of boilerplate there, so wonder is there a better way to do it. My real question I guess is if I know the input is of type Ability, so any one of the Str/Dex etc, what is the easiest way to extract the Integer from it without pattern match each one of them?

data Ability = StrAbi Integer
         | DexAbi Integer
         | ConAbi Integer
         | IntAbi Integer
         | WisAbi Integer
         | ChaAbi Integer
         deriving (Show)

data Modifier = Modifier Integer deriving (Show)

setModifier :: Ability -> (Ability, Modifier)
setModifier abi@(StrAbi s) = (abi, Modifier $ modifier' s)
setModifier abi@(DexAbi s) = (abi, Modifier $ modifier' s)
setModifier abi@(ConAbi s) = (abi, Modifier $ modifier' s)
setModifier abi@(IntAbi s) = (abi, Modifier $ modifier' s)
setModifier abi@(WisAbi s) = (abi, Modifier $ modifier' s)
setModifier abi@(ChaAbi s) = (abi, Modifier $ modifier' s)

Thanks, //

Upvotes: 3

Views: 1174

Answers (3)

Thomas M. DuBuisson
Thomas M. DuBuisson

Reputation: 64740

Answering the comment-question about using Lens (with MicroLens-platform in this answer but for these operations its the exact same code as full Lens with smaller dependencies):

{-# LANGUAGE TemplateHaskell #-}
import Lens.Micro.Platform
data Ability
         = StrAbi { _abilityValue :: Integer }
         | DexAbi { _abilityValue :: Integer }
         | ConAbi { _abilityValue :: Integer }
         | IntAbi { _abilityValue :: Integer }
         | WisAbi { _abilityValue :: Integer }
         | ChaAbi { _abilityValue :: Integer }
         deriving (Show)
makeLenses ''Ability

-- Just some examples
getAbilityValue :: Ability -> Integer
getAbilityValue ab = ab ^. abilityValue

setAbilityValue :: Ability -> Integer -> Ability
setAbilityValue ab val = ab & abilityValue .~ val

modifyAbilityValue :: Ability -> (Integer -> Integer) -> Ability
modifyAbilityValue ab f = ab & abilityValue %~ f

-- Edit after reading the question instead of just the comment:
data Modifier = Modifier Integer deriving (Show)

setModifier :: Ability -> (Ability, Modifier)
setModifier ab = (ab,Modifier (ab ^. abilityValue))
-- or import Control.Arrow and
-- setModifier = id &&& Modifier . (^. abilityValue)

Upvotes: 2

Li-yao Xia
Li-yao Xia

Reputation: 33389

Can you refactor the datatype?

data Ability = Ability { abilityType :: AbilityType, abilityValue :: Integer }
data AbilityType = Str | Dec | Con | Int | Wis | Cha

setModifier would have the same definition as Willem Van Onsem.

Upvotes: 13

willeM_ Van Onsem
willeM_ Van Onsem

Reputation: 476574

Usually if you have a datastructure where each possible constructor has a fields that has the same semantical meaning, you can use record syntax, and thus give that child a name:

data Ability = StrAbi { abilityValue :: Integer }
         | DexAbi { abilityValue :: Integer }
         | ConAbi { abilityValue :: Integer }
         | IntAbi { abilityValue :: Integer }
         | WisAbi { abilityValue :: Integer }
         | ChaAbi { abilityValue :: Integer }
         deriving (Show)

The nice thing is, you automatically have constructed a function abilityValue :: Ability -> Integer that thus has access to that field.

Next we can simply write:

setModifier :: Ability -> (Ability, Modifier)
setModifier abi = (abi, Modifier $ modifier' $ abilityValue abi)

There is of course some effort in specifying the name of the fields, but if these values have a "similar semantical meaning", then it will usually pay off since you have introduced a "getter" (and you can use record notation for "setters").

Upvotes: 3

Related Questions