reformatting and refectoring

This commit is contained in:
Dennis Frieberg 2020-08-25 04:02:51 +02:00
parent ddd42c1914
commit e38b240178

View file

@ -2,10 +2,9 @@
-- Module: TickLeiste -- Module: TickLeiste
-- Description: Short Implementation of Splittermonds Tickleiste -- Description: Short Implementation of Splittermonds Tickleiste
-- Stability: experimental -- Stability: experimental
module Data.TickLeiste ( module Data.TickLeiste
TickLeiste, ( TickLeiste,
newTickLeiste, newTickLeiste,
addPlayer,
addTicksToPlayer, addTicksToPlayer,
isAbwarten, isAbwarten,
isBereithalten, isBereithalten,
@ -13,102 +12,134 @@ module Data.TickLeiste (
getPlayerTick, getPlayerTick,
getTickPlayers, getTickPlayers,
getTickValue, getTickValue,
Tick (..) setPlayerTick,
) where toList,
import Data.Maybe (fromMaybe) fromList,
import qualified Data.Map.Strict as M toMap,
import qualified Data.Text as T fromMap,
Tick (..),
)
where
-- |A Tick is just a number import qualified Data.Map.Strict as M
data Tick = Abwarten | Bereithalten | Tick Int import Data.Maybe (fromMaybe)
import qualified Data.Text as T
-- | A Tick is just a number
data Tick = Abwarten | Bereithalten | Tick Int
deriving (Show, Eq, Ord) deriving (Show, Eq, Ord)
isAbwarten :: Tick -> Bool -- | test if 'Tick' is constructed using 'Abwarten'
isAbwarten Abwarten = True isAbwarten :: Tick -> Bool
isAbwarten _ = False isAbwarten Abwarten = True
isAbwarten _ = False
isBereithalten :: Tick -> Bool -- | test if 'Tick' is constructed using 'Bereithalten'
isBereithalten Bereithalten = True isBereithalten :: Tick -> Bool
isBereithalten _ = False isBereithalten Bereithalten = True
isBereithalten _ = False
getTickValue :: Tick -> Maybe Int -- | if 'Tick' is costructed with 'Tick' we get the 'Int' value, else 'Nothing'
getTickValue (Tick n) = Just n getTickValue :: Tick -> Maybe Int
getTickValue _ = Nothing getTickValue (Tick n) = Just n
-- |A Player has a name as identifier getTickValue _ = Nothing
type Player = T.Text
-- |The TickLeiste consists of a List of Ticks and for each Tick a -- | A Player has a name as identifier
-- Queue of players, that play at that turn. type Player = T.Text
-- This is a bit wierd as it introduces redundancy, but I don't have a -- | The TickLeiste consists of a List of Ticks and for each Tick a
-- better idea. -- Queue of players, that play at that turn.
-- NOTE: the first player in the list is the first to move.
data TickLeiste = TickLeiste { leiste :: M.Map Tick [Player], player :: M.Map Player Tick } -- This is a bit wierd as it introduces redundancy, but I don't have a
-- better idea.
-- NOTE: the first player in the list is the first to move.
data TickLeiste = TickLeiste {leiste :: M.Map Tick [Player], player :: M.Map Player Tick}
deriving (Show) deriving (Show)
-- |Empty Tickleiste -- | Empty Tickleiste
newTickLeiste :: TickLeiste newTickLeiste :: TickLeiste
newTickLeiste = TickLeiste M.empty M.empty newTickLeiste = TickLeiste M.empty M.empty
-- |Add a 'Player' to the 'TickLeiste' -- | Adds a number of ticks to the player, if the player is not on
addPlayer :: Player -- ^ the Player to add -- the TickLeiste, Abwarten or Bereithalten then this function returns
-> Tick -- ^ the Tick we add the Player to -- Nothing
-> TickLeiste -- ^ the TickLeiste we add the player to
-> TickLeiste -- ^ the resulting TickLeiste
addPlayer p t (TickLeiste l pl) = TickLeiste tlm pm
where
tlm :: M.Map Tick [Player]
tlm = insertPlayerToLeiste p t l
pm :: M.Map Player Tick
pm = setPlayerTickToPlayer p t pl
-- | Adds a number of ticks to the player, if the player is not on -- Would it be better to return the original 'TickLeiste' instead of 'Nothing'?
-- the TickLeiste, Abwarten or Bereithalten then this function returns addTicksToPlayer ::
-- Nothing -- | the Player we want to add ticks to
Player ->
-- Would it be better to return the original 'TickLeiste' instead of 'Nothing'? -- | the number of Ticks we want to add
addTicksToPlayer :: Player -- ^ the Player we want to add ticks to Int ->
-> Int -- ^ the number of Ticks we want to add -- | the TickLeiste we want to modify
-> TickLeiste -- ^ the TickLeiste we want to modify TickLeiste ->
-> Maybe TickLeiste -- ^ the result -- | the result
Maybe TickLeiste
addTicksToPlayer p t tl@(TickLeiste l pl) = {- fromMaybe tl $ -}do addTicksToPlayer p t tl = {- fromMaybe tl $ -} do
pt <- pl M.!? p pt <- getPlayerTick p tl
ptv <- getTickValue pt ptv <- getTickValue pt
let npt = Tick $ ptv + t let nt = Tick $ ptv + t
tlm = (insertPlayerToLeiste p npt . removePlayerFromLeiste p pt) l return $ setPlayerTick p nt tl
pm = setPlayerTickToPlayer p npt pl
return $ TickLeiste tlm pm
-- | We get the tick a 'Player' is on
getPlayerTick ::
Player ->
TickLeiste ->
Maybe Tick
getPlayerTick p (TickLeiste _ pl) = pl M.!? p
-- |We get the tick a 'Player' is on -- | get a list of 'Player' that move at a tick in order.
getPlayerTick :: Player -- ^ the 'Player' getTickPlayers ::
-> TickLeiste Tick ->
-> Maybe Tick TickLeiste ->
getPlayerTick p (TickLeiste _ pl) = pl M.!? p [Player]
getTickPlayers t (TickLeiste l _) = fromMaybe [] $ l M.!? t
-- |get a list of 'Player' that move at a tick in order. -- | set the tick of a 'Player', if the 'Player' is does not exist we add them.
getTickPlayers :: Tick setPlayerTick ::
-> TickLeiste Player ->
-> [Player] Tick ->
getTickPlayers t (TickLeiste l _) = fromMaybe [] $ l M.!? t TickLeiste ->
TickLeiste
setPlayerTick p t tl@(TickLeiste l pl) = TickLeiste (insertPlayerToLeiste p t l') (setPlayerTickToPlayer p t pl)
where
l' :: M.Map Tick [Player]
l' = fromMaybe l $ do
ot <- getPlayerTick p tl
return $ removePlayerFromLeiste p ot l
-- | convert the Tick[eiste to a list of 'Tick' and 'Player' list pairs. These list are ordered
toList :: TickLeiste -> [(Tick, [Player])]
toList (TickLeiste l _) = M.toAscList l
-- | convert from list to TickLeiste, if a player is at multiple 'Tick' this returns
-- 'Nothing'
-- this is just an internal helper -- TODO
-- it removes a player from a specific tick, if the player fromList :: [(Tick, [Player])] -> Maybe TickLeiste
-- wasn't at the tick it is the identity. fromList = error "not implemented"
removePlayerFromLeiste :: Player -> Tick -> M.Map Tick [Player] -> M.Map Tick [Player]
removePlayerFromLeiste p t l = fromMaybe l $ do -- | convert from 'TickLeiste' to a map from 'Tick' to list of 'Player'
toMap :: TickLeiste -> M.Map Tick [Player]
toMap = leiste
-- TODO
fromMap :: M.Map Tick [Player] -> Maybe TickLeiste
fromMap = error "not implemented"
-- these are just internal helpers
-- it removes a player from a specific tick, if the player
-- wasn't at the tick it is the identity.
removePlayerFromLeiste :: Player -> Tick -> M.Map Tick [Player] -> M.Map Tick [Player]
removePlayerFromLeiste p t l = fromMaybe l $ do
list <- l M.!? t list <- l M.!? t
let list' = filter ( /= p) list let list' = filter (/= p) list
if null list' then if null list'
return $ M.delete t l then return $ M.delete t l
else else return $ M.insert t list' l
return $ M.insert t list' l
insertPlayerToLeiste :: Player -> Tick -> M.Map Tick [Player] -> M.Map Tick [Player] insertPlayerToLeiste :: Player -> Tick -> M.Map Tick [Player] -> M.Map Tick [Player]
insertPlayerToLeiste p t l = M.insert t (M.findWithDefault [] t l ++ [p]) l insertPlayerToLeiste p t l = M.insert t (M.findWithDefault [] t l ++ [p]) l
setPlayerTickToPlayer :: Player -> Tick -> M.Map Player Tick -> M.Map Player Tick setPlayerTickToPlayer :: Player -> Tick -> M.Map Player Tick -> M.Map Player Tick
setPlayerTickToPlayer = M.insert setPlayerTickToPlayer = M.insert