implemented Player and PlayerStats
This commit is contained in:
@@ -21,6 +21,8 @@ description: Please see the README on GitHub at <https://github.com/jlam
|
|||||||
|
|
||||||
dependencies:
|
dependencies:
|
||||||
- base >= 4.7 && < 5
|
- base >= 4.7 && < 5
|
||||||
|
- microlens-th >= 0.4.2.3 && < 0.5
|
||||||
|
- microlens
|
||||||
|
|
||||||
library:
|
library:
|
||||||
source-dirs: src
|
source-dirs: src
|
||||||
|
|||||||
82
src/Mtlstats/Types.hs
Normal file
82
src/Mtlstats/Types.hs
Normal file
@@ -0,0 +1,82 @@
|
|||||||
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
|
|
||||||
|
module Mtlstats.Types (
|
||||||
|
-- * Types
|
||||||
|
Player (..),
|
||||||
|
PlayerStats (..),
|
||||||
|
-- * Lenses
|
||||||
|
-- ** Player Lenses
|
||||||
|
pNumber,
|
||||||
|
pName,
|
||||||
|
pPosition,
|
||||||
|
pYtd,
|
||||||
|
pLifetime,
|
||||||
|
-- ** PlayerStats Lenses
|
||||||
|
psGoals,
|
||||||
|
psAssists,
|
||||||
|
psPMin,
|
||||||
|
-- * Constructors
|
||||||
|
newPlayer,
|
||||||
|
newPlayerStats,
|
||||||
|
-- * Helper functions
|
||||||
|
pPoints
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Lens.Micro ((^.))
|
||||||
|
import Lens.Micro.TH (makeLenses)
|
||||||
|
|
||||||
|
-- | Represents a (non-goalie) player
|
||||||
|
data Player = Player
|
||||||
|
{ _pNumber :: Int
|
||||||
|
-- ^ The player's number
|
||||||
|
, _pName :: String
|
||||||
|
-- ^ The player's name
|
||||||
|
, _pPosition :: String
|
||||||
|
-- ^ The player's position
|
||||||
|
, _pYtd :: PlayerStats
|
||||||
|
-- ^ The Player's year-to-date stats
|
||||||
|
, _pLifetime :: PlayerStats
|
||||||
|
-- ^ The player's lifetime stats
|
||||||
|
} deriving (Eq, Show)
|
||||||
|
|
||||||
|
-- | Represents a (non-goalie) player's stats
|
||||||
|
data PlayerStats = PlayerStats
|
||||||
|
{ _psGoals :: Int
|
||||||
|
-- ^ The number of goals
|
||||||
|
, _psAssists :: Int
|
||||||
|
-- ^ The number of assists
|
||||||
|
, _psPMin :: Int
|
||||||
|
-- ^ The number of penalty minutes
|
||||||
|
} deriving (Eq, Show)
|
||||||
|
|
||||||
|
makeLenses ''Player
|
||||||
|
makeLenses ''PlayerStats
|
||||||
|
|
||||||
|
-- | Constructor for a 'Player'
|
||||||
|
newPlayer
|
||||||
|
:: Int
|
||||||
|
-- ^ The player's number
|
||||||
|
-> String
|
||||||
|
-- ^ The player's name
|
||||||
|
-> String
|
||||||
|
-- ^ The player's position
|
||||||
|
-> Player
|
||||||
|
newPlayer num name pos = Player
|
||||||
|
{ _pNumber = num
|
||||||
|
, _pName = name
|
||||||
|
, _pPosition = pos
|
||||||
|
, _pYtd = newPlayerStats
|
||||||
|
, _pLifetime = newPlayerStats
|
||||||
|
}
|
||||||
|
|
||||||
|
-- | Constructor for a 'PlayerStats' value
|
||||||
|
newPlayerStats :: PlayerStats
|
||||||
|
newPlayerStats = PlayerStats
|
||||||
|
{ _psGoals = 0
|
||||||
|
, _psAssists = 0
|
||||||
|
, _psPMin = 0
|
||||||
|
}
|
||||||
|
|
||||||
|
-- | Calculates a player's points
|
||||||
|
pPoints :: PlayerStats -> Int
|
||||||
|
pPoints s = s^.psGoals + s^.psAssists
|
||||||
@@ -1,4 +1,6 @@
|
|||||||
import Test.Hspec (hspec)
|
import Test.Hspec (hspec)
|
||||||
|
|
||||||
|
import qualified TypesSpec as Types
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = hspec $ return ()
|
main = hspec Types.spec
|
||||||
|
|||||||
26
test/TypesSpec.hs
Normal file
26
test/TypesSpec.hs
Normal file
@@ -0,0 +1,26 @@
|
|||||||
|
module TypesSpec (spec) where
|
||||||
|
|
||||||
|
import Lens.Micro ((&), (.~))
|
||||||
|
import Test.Hspec (Spec, context, describe, it, shouldBe)
|
||||||
|
|
||||||
|
import Mtlstats.Types
|
||||||
|
|
||||||
|
spec :: Spec
|
||||||
|
spec = describe "Mtlstats.Types" pPointsSpec
|
||||||
|
|
||||||
|
pPointsSpec = describe "pPoints" $ mapM_
|
||||||
|
(\(goals, assists, points) -> let
|
||||||
|
desc = "goals: " ++ show goals ++
|
||||||
|
", assists: " ++ show assists
|
||||||
|
stats = newPlayerStats &
|
||||||
|
psGoals .~ goals &
|
||||||
|
psAssists .~ assists
|
||||||
|
in context desc $
|
||||||
|
it ("should be " ++ show points) $
|
||||||
|
pPoints stats `shouldBe` points)
|
||||||
|
-- goals, assists, points
|
||||||
|
[ ( 0, 0, 0 )
|
||||||
|
, ( 1, 0, 1 )
|
||||||
|
, ( 0, 1, 1 )
|
||||||
|
, ( 2, 3, 5 )
|
||||||
|
]
|
||||||
Reference in New Issue
Block a user