shortened describePlayer output
This commit is contained in:
parent
e8b850c23a
commit
26a90a5ed9
|
@ -25,6 +25,7 @@ import Data.Maybe (fromMaybe)
|
||||||
import Lens.Micro ((^.))
|
import Lens.Micro ((^.))
|
||||||
import qualified UI.NCurses as C
|
import qualified UI.NCurses as C
|
||||||
|
|
||||||
|
import Mtlstats.Helpers.Player
|
||||||
import Mtlstats.Menu
|
import Mtlstats.Menu
|
||||||
import Mtlstats.Prompt
|
import Mtlstats.Prompt
|
||||||
import Mtlstats.Prompt.EditPlayer
|
import Mtlstats.Prompt.EditPlayer
|
||||||
|
@ -92,4 +93,4 @@ header :: ProgState -> C.Update ()
|
||||||
header s = C.drawString $ fromMaybe "" $ do
|
header s = C.drawString $ fromMaybe "" $ do
|
||||||
pid <- s^.progMode.editPlayerStateL.epsSelectedPlayer
|
pid <- s^.progMode.editPlayerStateL.epsSelectedPlayer
|
||||||
player <- nth pid $ s^.database.dbPlayers
|
player <- nth pid $ s^.database.dbPlayers
|
||||||
Just $ playerDetails player
|
Just $ playerDetails player ++ "\n"
|
||||||
|
|
|
@ -26,8 +26,13 @@ module Mtlstats.Format
|
||||||
, centre
|
, centre
|
||||||
, overlay
|
, overlay
|
||||||
, month
|
, month
|
||||||
|
, labelTable
|
||||||
|
, numTable
|
||||||
|
, tableWith
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
import Data.List (transpose)
|
||||||
|
|
||||||
-- | Pad an 'Int' with leading zeroes to fit a certain character width
|
-- | Pad an 'Int' with leading zeroes to fit a certain character width
|
||||||
padNum
|
padNum
|
||||||
:: Int
|
:: Int
|
||||||
|
@ -101,3 +106,44 @@ month 10 = "OCT"
|
||||||
month 11 = "NOV"
|
month 11 = "NOV"
|
||||||
month 12 = "DEC"
|
month 12 = "DEC"
|
||||||
month _ = ""
|
month _ = ""
|
||||||
|
|
||||||
|
-- | Creates a two-column table with labels
|
||||||
|
labelTable :: [(String, String)] -> [String]
|
||||||
|
labelTable xs = let
|
||||||
|
labelWidth = maximum $ map (length . fst) xs
|
||||||
|
in map
|
||||||
|
(\(label, val) -> right labelWidth label ++ ": " ++ val)
|
||||||
|
xs
|
||||||
|
|
||||||
|
-- | Creates a variable column table of numbers with two axes
|
||||||
|
numTable
|
||||||
|
:: [String]
|
||||||
|
-- ^ The top column labels
|
||||||
|
-> [(String, [Int])]
|
||||||
|
-- ^ The rows with their labels
|
||||||
|
-> [String]
|
||||||
|
numTable headers rows = tableWith right $ header : body
|
||||||
|
where
|
||||||
|
header = "" : headers
|
||||||
|
body = map
|
||||||
|
(\(label, row) ->
|
||||||
|
label : map show row)
|
||||||
|
rows
|
||||||
|
|
||||||
|
-- | Creates a table from a two-dimensional list with a specified
|
||||||
|
-- padding function
|
||||||
|
tableWith
|
||||||
|
:: (Int -> String -> String)
|
||||||
|
-- ^ The padding function
|
||||||
|
-> [[String]]
|
||||||
|
-- ^ The cells
|
||||||
|
-> [String]
|
||||||
|
tableWith func tdata = let
|
||||||
|
widths = map (map length) tdata
|
||||||
|
colWidths = map maximum $ transpose widths
|
||||||
|
fitted = map
|
||||||
|
(\row -> map
|
||||||
|
(\(str, len) -> func len str) $
|
||||||
|
zip row colWidths)
|
||||||
|
tdata
|
||||||
|
in map unwords fitted
|
||||||
|
|
|
@ -0,0 +1,45 @@
|
||||||
|
{- |
|
||||||
|
|
||||||
|
mtlstats
|
||||||
|
Copyright (C) 2019 Rhéal Lamothe
|
||||||
|
<rheal.lamothe@gmail.com>
|
||||||
|
|
||||||
|
This program is free software: you can redistribute it and/or modify
|
||||||
|
it under the terms of the GNU General Public License as published by
|
||||||
|
the Free Software Foundation, either version 3 of the License, or (at
|
||||||
|
your option) any later version.
|
||||||
|
|
||||||
|
This program is distributed in the hope that it will be useful, but
|
||||||
|
WITHOUT ANY WARRANTY; without even the implied warranty of
|
||||||
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
|
||||||
|
General Public License for more details.
|
||||||
|
|
||||||
|
You should have received a copy of the GNU General Public License
|
||||||
|
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
|
-}
|
||||||
|
|
||||||
|
module Mtlstats.Helpers.Player (playerDetails) where
|
||||||
|
|
||||||
|
import Lens.Micro ((^.))
|
||||||
|
|
||||||
|
import Mtlstats.Format
|
||||||
|
import Mtlstats.Types
|
||||||
|
|
||||||
|
-- | Provides a detailed string describing a 'Player'
|
||||||
|
playerDetails :: Player -> String
|
||||||
|
playerDetails p = unlines $ top ++ [""] ++ table
|
||||||
|
where
|
||||||
|
top = labelTable
|
||||||
|
[ ( "Number", show $ p^.pNumber )
|
||||||
|
, ( "Name", p^.pName )
|
||||||
|
, ( "Position", p^.pPosition )
|
||||||
|
]
|
||||||
|
|
||||||
|
table = numTable ["YTD", "Lifetime"] $ map
|
||||||
|
(\(label, lens) ->
|
||||||
|
(label, [p^.pYtd.lens, p^.pLifetime.lens]))
|
||||||
|
[ ( "Goals", psGoals )
|
||||||
|
, ( "Assists", psAssists )
|
||||||
|
, ( "Penalty mins", psPMin )
|
||||||
|
]
|
|
@ -161,7 +161,6 @@ module Mtlstats.Types (
|
||||||
playerSearchExact,
|
playerSearchExact,
|
||||||
modifyPlayer,
|
modifyPlayer,
|
||||||
playerSummary,
|
playerSummary,
|
||||||
playerDetails,
|
|
||||||
playerIsActive,
|
playerIsActive,
|
||||||
-- ** PlayerStats Helpers
|
-- ** PlayerStats Helpers
|
||||||
psPoints,
|
psPoints,
|
||||||
|
@ -917,20 +916,6 @@ playerSummary :: Player -> String
|
||||||
playerSummary p =
|
playerSummary p =
|
||||||
p^.pName ++ " (" ++ show (p^.pNumber) ++ ") " ++ p^.pPosition
|
p^.pName ++ " (" ++ show (p^.pNumber) ++ ") " ++ p^.pPosition
|
||||||
|
|
||||||
-- | Provides a detailed string describing a 'Player'
|
|
||||||
playerDetails :: Player -> String
|
|
||||||
playerDetails p = unlines
|
|
||||||
[ " Number: " ++ show (p^.pNumber)
|
|
||||||
, " Name: " ++ p^.pName
|
|
||||||
, " Position: " ++ p^.pPosition
|
|
||||||
, " YTD goals: " ++ show (p^.pYtd.psGoals)
|
|
||||||
, " YTD assists: " ++ show (p^.pYtd.psAssists)
|
|
||||||
, " YTD penalty mins: " ++ show (p^.pYtd.psPMin)
|
|
||||||
, " Lifetime goals: " ++ show (p^.pLifetime.psGoals)
|
|
||||||
, " Lifetime assists: " ++ show (p^.pLifetime.psAssists)
|
|
||||||
, "Lifetime penalty mins: " ++ show (p^.pLifetime.psPMin)
|
|
||||||
]
|
|
||||||
|
|
||||||
-- | Determines whether or not a player has been active in the current
|
-- | Determines whether or not a player has been active in the current
|
||||||
-- season/year
|
-- season/year
|
||||||
playerIsActive :: Player -> Bool
|
playerIsActive :: Player -> Bool
|
||||||
|
|
|
@ -33,6 +33,9 @@ spec = describe "Mtlstats.Format" $ do
|
||||||
centreSpec
|
centreSpec
|
||||||
overlaySpec
|
overlaySpec
|
||||||
monthSpec
|
monthSpec
|
||||||
|
labelTableSpec
|
||||||
|
numTableSpec
|
||||||
|
tableWithSpec
|
||||||
|
|
||||||
padNumSpec :: Spec
|
padNumSpec :: Spec
|
||||||
padNumSpec = describe "padNum" $ do
|
padNumSpec = describe "padNum" $ do
|
||||||
|
@ -111,3 +114,63 @@ monthSpec = describe "month" $ do
|
||||||
context "invalid" $
|
context "invalid" $
|
||||||
it "should return an empty string" $
|
it "should return an empty string" $
|
||||||
month 0 `shouldBe` ""
|
month 0 `shouldBe` ""
|
||||||
|
|
||||||
|
labelTableSpec :: Spec
|
||||||
|
labelTableSpec = describe "labelTable" $
|
||||||
|
it "should format the table" $ let
|
||||||
|
input =
|
||||||
|
[ ( "foo", "bar" )
|
||||||
|
, ( "baz", "quux" )
|
||||||
|
, ( "longer", "x" )
|
||||||
|
]
|
||||||
|
|
||||||
|
expected =
|
||||||
|
[ " foo: bar"
|
||||||
|
, " baz: quux"
|
||||||
|
, "longer: x"
|
||||||
|
]
|
||||||
|
|
||||||
|
in labelTable input `shouldBe` expected
|
||||||
|
|
||||||
|
numTableSpec :: Spec
|
||||||
|
numTableSpec = describe "numTable" $
|
||||||
|
it "should format the table" $ let
|
||||||
|
headers = ["foo", "bar", "baz"]
|
||||||
|
|
||||||
|
rows =
|
||||||
|
[ ( "quux", [ 1, 2, 3 ] )
|
||||||
|
, ( "xyzzy", [ 9, 99, 999 ] )
|
||||||
|
]
|
||||||
|
|
||||||
|
expected =
|
||||||
|
[ " foo bar baz"
|
||||||
|
, " quux 1 2 3"
|
||||||
|
, "xyzzy 9 99 999"
|
||||||
|
]
|
||||||
|
|
||||||
|
in numTable headers rows `shouldBe` expected
|
||||||
|
|
||||||
|
tableWithSpec :: Spec
|
||||||
|
tableWithSpec = describe "tableWith" $ let
|
||||||
|
vals =
|
||||||
|
[ [ "foo", "bar", "baz" ]
|
||||||
|
, [ "quux", "xyzzy", "x" ]
|
||||||
|
]
|
||||||
|
|
||||||
|
in mapM_
|
||||||
|
(\(label, func, expected) -> context label $
|
||||||
|
it "should format the table" $
|
||||||
|
tableWith func vals `shouldBe` expected)
|
||||||
|
[ ( "align left"
|
||||||
|
, left
|
||||||
|
, [ "foo bar baz"
|
||||||
|
, "quux xyzzy x "
|
||||||
|
]
|
||||||
|
)
|
||||||
|
, ( "align right"
|
||||||
|
, right
|
||||||
|
, [ " foo bar baz"
|
||||||
|
, "quux xyzzy x"
|
||||||
|
]
|
||||||
|
)
|
||||||
|
]
|
||||||
|
|
|
@ -0,0 +1,61 @@
|
||||||
|
{-
|
||||||
|
|
||||||
|
mtlstats
|
||||||
|
Copyright (C) 2019 Rhéal Lamothe
|
||||||
|
<rheal.lamothe@gmail.com>
|
||||||
|
|
||||||
|
This program is free software: you can redistribute it and/or modify
|
||||||
|
it under the terms of the GNU General Public License as published by
|
||||||
|
the Free Software Foundation, either version 3 of the License, or (at
|
||||||
|
your option) any later version.
|
||||||
|
|
||||||
|
This program is distributed in the hope that it will be useful, but
|
||||||
|
WITHOUT ANY WARRANTY; without even the implied warranty of
|
||||||
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
|
||||||
|
General Public License for more details.
|
||||||
|
|
||||||
|
You should have received a copy of the GNU General Public License
|
||||||
|
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
|
-}
|
||||||
|
|
||||||
|
module Helpers.PlayerSpec (spec) where
|
||||||
|
|
||||||
|
import Lens.Micro ((&), (.~))
|
||||||
|
import Test.Hspec (Spec, describe, it, shouldBe)
|
||||||
|
|
||||||
|
import Mtlstats.Helpers.Player
|
||||||
|
import Mtlstats.Types
|
||||||
|
|
||||||
|
spec :: Spec
|
||||||
|
spec = describe "Player"
|
||||||
|
playerDetailsSpec
|
||||||
|
|
||||||
|
playerDetailsSpec :: Spec
|
||||||
|
playerDetailsSpec = describe "playerDetails" $
|
||||||
|
it "should give a detailed description" $ let
|
||||||
|
|
||||||
|
p = newPlayer 1 "Joe" "centre"
|
||||||
|
& pYtd .~ PlayerStats
|
||||||
|
{ _psGoals = 2
|
||||||
|
, _psAssists = 3
|
||||||
|
, _psPMin = 4
|
||||||
|
}
|
||||||
|
& pLifetime .~ PlayerStats
|
||||||
|
{ _psGoals = 5
|
||||||
|
, _psAssists = 6
|
||||||
|
, _psPMin = 7
|
||||||
|
}
|
||||||
|
|
||||||
|
expected = unlines
|
||||||
|
[ " Number: 1"
|
||||||
|
, " Name: Joe"
|
||||||
|
, "Position: centre"
|
||||||
|
, ""
|
||||||
|
, " YTD Lifetime"
|
||||||
|
, " Goals 2 5"
|
||||||
|
, " Assists 3 6"
|
||||||
|
, "Penalty mins 4 7"
|
||||||
|
]
|
||||||
|
|
||||||
|
in playerDetails p `shouldBe` expected
|
|
@ -0,0 +1,30 @@
|
||||||
|
{-
|
||||||
|
|
||||||
|
mtlstats
|
||||||
|
Copyright (C) 2019 Rhéal Lamothe
|
||||||
|
<rheal.lamothe@gmail.com>
|
||||||
|
|
||||||
|
This program is free software: you can redistribute it and/or modify
|
||||||
|
it under the terms of the GNU General Public License as published by
|
||||||
|
the Free Software Foundation, either version 3 of the License, or (at
|
||||||
|
your option) any later version.
|
||||||
|
|
||||||
|
This program is distributed in the hope that it will be useful, but
|
||||||
|
WITHOUT ANY WARRANTY; without even the implied warranty of
|
||||||
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
|
||||||
|
General Public License for more details.
|
||||||
|
|
||||||
|
You should have received a copy of the GNU General Public License
|
||||||
|
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
|
-}
|
||||||
|
|
||||||
|
module HelpersSpec (spec) where
|
||||||
|
|
||||||
|
import Test.Hspec (Spec, describe)
|
||||||
|
|
||||||
|
import qualified Helpers.PlayerSpec as Player
|
||||||
|
|
||||||
|
spec :: Spec
|
||||||
|
spec = describe "Helper"
|
||||||
|
Player.spec
|
|
@ -24,6 +24,7 @@ import Test.Hspec (hspec)
|
||||||
import qualified ActionsSpec as Actions
|
import qualified ActionsSpec as Actions
|
||||||
import qualified FormatSpec as Format
|
import qualified FormatSpec as Format
|
||||||
import qualified HandlersSpec as Handlers
|
import qualified HandlersSpec as Handlers
|
||||||
|
import qualified HelpersSpec as Helpers
|
||||||
import qualified ReportSpec as Report
|
import qualified ReportSpec as Report
|
||||||
import qualified TypesSpec as Types
|
import qualified TypesSpec as Types
|
||||||
import qualified UtilSpec as Util
|
import qualified UtilSpec as Util
|
||||||
|
@ -31,6 +32,7 @@ import qualified UtilSpec as Util
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = hspec $ do
|
main = hspec $ do
|
||||||
Types.spec
|
Types.spec
|
||||||
|
Helpers.spec
|
||||||
Actions.spec
|
Actions.spec
|
||||||
Format.spec
|
Format.spec
|
||||||
Handlers.spec
|
Handlers.spec
|
||||||
|
|
|
@ -72,7 +72,6 @@ spec = describe "Mtlstats.Types" $ do
|
||||||
playerSearchExactSpec
|
playerSearchExactSpec
|
||||||
modifyPlayerSpec
|
modifyPlayerSpec
|
||||||
playerSummarySpec
|
playerSummarySpec
|
||||||
playerDetailsSpec
|
|
||||||
playerIsActiveSpec
|
playerIsActiveSpec
|
||||||
psPointsSpec
|
psPointsSpec
|
||||||
addPlayerStatsSpec
|
addPlayerStatsSpec
|
||||||
|
@ -636,36 +635,6 @@ playerSummarySpec = describe "playerSummary" $
|
||||||
it "should be \"Joe (2) center\"" $
|
it "should be \"Joe (2) center\"" $
|
||||||
playerSummary joe `shouldBe` "Joe (2) center"
|
playerSummary joe `shouldBe` "Joe (2) center"
|
||||||
|
|
||||||
playerDetailsSpec :: Spec
|
|
||||||
playerDetailsSpec = describe "playerDetails" $
|
|
||||||
it "should give a detailed description" $ let
|
|
||||||
|
|
||||||
p = newPlayer 1 "Joe" "centre"
|
|
||||||
& pYtd .~ PlayerStats
|
|
||||||
{ _psGoals = 2
|
|
||||||
, _psAssists = 3
|
|
||||||
, _psPMin = 4
|
|
||||||
}
|
|
||||||
& pLifetime .~ PlayerStats
|
|
||||||
{ _psGoals = 5
|
|
||||||
, _psAssists = 6
|
|
||||||
, _psPMin = 7
|
|
||||||
}
|
|
||||||
|
|
||||||
expected = unlines
|
|
||||||
[ " Number: 1"
|
|
||||||
, " Name: Joe"
|
|
||||||
, " Position: centre"
|
|
||||||
, " YTD goals: 2"
|
|
||||||
, " YTD assists: 3"
|
|
||||||
, " YTD penalty mins: 4"
|
|
||||||
, " Lifetime goals: 5"
|
|
||||||
, " Lifetime assists: 6"
|
|
||||||
, "Lifetime penalty mins: 7"
|
|
||||||
]
|
|
||||||
|
|
||||||
in playerDetails p `shouldBe` expected
|
|
||||||
|
|
||||||
playerIsActiveSpec :: Spec
|
playerIsActiveSpec :: Spec
|
||||||
playerIsActiveSpec = describe "playerIsActive" $ do
|
playerIsActiveSpec = describe "playerIsActive" $ do
|
||||||
let
|
let
|
||||||
|
|
Loading…
Reference in New Issue
Block a user