{-# LANGUAGE FlexibleContexts #-}
+-- © 2008 Joachim Breitner
+
-- | This module provides a versatile framework to write contestant in the party
-- programming game introduced at the GPN7 in Karlsruhe by dividuum.
+--
+-- It uses a callback pattern, that is it runs /\"most of the time\"/ and user code will
+-- only be called upon certain events.
module Partty
( -- * Invoking Partty
type Day = Int
type Place = Int
-data Hint = PartyAt Place
- | NoPartyAt Place
- | Liar Player
- | NoLiar Player
+-- | A 'Hint' is a message that can be sent or received. It is either
+data Hint = PartyAt Place -- ^ A statement where the party will be
+ | NoPartyAt Place -- ^ A statement where no party will be
+ | Liar Player -- ^ A claim that someone is a liar
+ | NoLiar Player -- ^ A claim of trustworthiness
deriving (Show)
-data Score = NoScore | ToFew | Scored
+-- | A 'Score' gives information about the success of a party
+data Score = NoScore -- ^ You were not at the party
+ | ToFew -- ^ There were not enough people at the party
+ | Scored -- ^ The party was great
deriving (Show)
data IncomingMessage = InternalMessage InternalMessage
show (NightMessage m) = "NightMessage ("++ show m ++")"
show (ComplexInput _) = "<ComplexInput>"
--- Events that we want to send to the user code and that
--- can be reacted upon
-data DayMessage = DayStarts Int
- | DayEndsIn Int
- | DayEnds
- | GotHint Player Hint
- | PlayerEnter Player Place
- | PlayerLeave Player Place
+-- | A 'DayMessage' is recevied by the server and given to the user via the 'DayCallback',
+-- so it can be reacted upon. It can be one of these:
+data DayMessage = DayStarts Int -- ^ The day (with a number) starts
+ | DayEndsIn Int -- ^ The day finishes in so many seconds
+ | DayEnds -- ^ The day ends
+ | GotHint Player Hint -- ^ A 'Hint' was recevied by this 'Player'
+ | PlayerEnter Player Place -- ^ A 'Player' (maybe you) has entered 'Place'
+ | PlayerLeave Player Place -- ^ A 'Player' (maybe you) has left 'Place'
deriving (Show)
+-- | A 'NightMessage' is given to the 'NightCallback' after each night has ended. It carries
+-- these pieces of information:
data NightResult = NightResult
- { nrDay :: Day
- , nrPartyAt :: Place
- , nrPlayersAt :: [(Player, Place)]
- , nrScore :: Score
+ { nrDay :: Day -- ^ The number of the day
+ , nrPartyAt :: Place -- ^ Where the party was
+ , nrPlayersAt :: [(Player, Place)] -- ^ Where the players were
+ , nrScore :: Score -- ^ Your score
}
deriving (Show)
| LostContact Player
deriving (Show)
-data ClientMessage = Tell Player Hint
- | Goto Place
+-- | A 'ClientMessage' is what you can send to the server. It is one of:
+data ClientMessage = Tell Player Hint -- ^ Giving a 'Hint' to a 'Player'
+ | Goto Place -- ^ Go to 'Place'
deriving (Show)
+-- | The 'ParttyState' contains all information that this module has obtained about the game.
+data ParttyState = ParttyState
+ { psMyName :: Player -- ^ The current player id
+ , psLoginName :: String -- ^ The loginname
+ , psDay :: Day -- ^ The current day
+ , psHistory :: [NightResult] -- ^ The results of the previous days
+ , psHintHistory :: [(Day, Player, Hint)] -- ^ All hints received by players, and when
+ , psPlace :: Place -- ^ Where we are
+ , psPlayers :: [String] -- ^ The login names of all present players
+ , psPlayersHere :: [Player] -- ^ Who is were we are
+ , psActionsLeft :: Int -- ^ How many actions are left before the callback
+ , psPartyPlace :: Maybe Place -- ^ If we know where the party is today, this is 'Just' the 'Place'
+ , psFriends :: [Player] -- ^ People we have partied with
+ }
+
+-- | The 'DayCallback' type alias refers to the argument of 'runPartty'. It is a function
+-- that takes an incoming 'DayMessage' and reacts on it, using the 'DayMonad'.
type DayCallback d = DayMessage -> DayMonad d ()
+
+-- | The 'NightCallback' type alias refers to the argument of 'runPartty'. It is a function
+-- that takes the 'NightResult' that is emitted after each day and reacts on it, using the
+-- 'NightMonad'.
type NightCallback d = NightResult -> NightMonad d ()
-data ParttyState = ParttyState
- { psMyName :: Player
- , psLoginName :: String
- , psDay :: Day
- , psHistory :: [NightResult]
- , psHintHistory :: [(Day, Player, Hint)]
- , psPlace :: Place
- , psPlayers :: [Player]
- , psPlayersHere :: [Player]
- , psActionsLeft :: Int
- , psPartyPlace :: Maybe Place
- , psFriends :: [Player]
- }
+-- | The 'DayMonad' is where the day callback runs in. Besides direct IO, which can be used using
+-- the 'liftIO' function, it provides:
+--
+-- * A 'MonadWriter' interface to send a 'ClientMessage' to the server. This should be used
+-- with the 'send' function.
+--
+-- * A 'MonadReader' 'ParttyState' interface to query the state of the game. To access this,
+-- use the standard 'ask' or 'asks' functions.
+--
+-- * A 'StateT' monad containing the custom user state. To query and modify this, use the
+-- standard 'get', 'put' and 'modify' functions.
type DayMonad d = WriterT [ClientMessage] (ReaderT ParttyState (StateT d IO))
+
+-- | The 'NightMonad' is where the night callbacks run in. It provides the same featuers as the
+-- 'DayMonad', only that you can not send a 'ClientMessage'.
type NightMonad d = ReaderT ParttyState (StateT d IO)
-- Interaction:
+-- | The 'send' function can be used in the 'DayMonad' to send a 'ClientMessage' to the server.
+-- Note that all messages will be sent when the callback returns.
send :: (MonadWriter [ClientMessage] m) => ClientMessage -> m ()
send msg = tell [msg]
-- Output
-
+--
+-- | Convenvience alternative to @'liftIO' $ 'putStrLn'@. It also prepends the username to the output.
say :: (MonadIO m, MonadReader ParttyState m) => String -> m ()
say s = do
name <- asks psLoginName
liftIO $ putStrLn $ "[" ++ name ++ "] " ++ s
-
+-- | Since the server does not keep permanent statistics, this will log in to the hostname and
+-- port, with the username and password, all given on the command line, do nothing in the game
+-- but record the events. It will output to the given file a @[[('String','Int')]]@ datum which
+-- lists for all games (in reverse order) the players and their score.
statsMain :: FilePath -> IO ()
statsMain file = do
[host,port_s,username,password] <- getArgs