------------------------------------------------------------------------------

-- Table.hs
-- created: Sat Oct 16 02:03:17 JST 2010

------------------------------------------------------------------------------

module Sound.Conductive.Table ( asciiTable
                               ,displayPlayers 
                               ) where

import Data.List
import Data.Maybe
import Sound.Conductive.ConductiveBaseData
import Sound.Conductive.MusicalEnvironment
import Sound.Conductive.MutableMap
import Sound.Conductive.Player

-- | This function creates a text table suitable for printing in ghci or the terminal.
--
-- For example:
--
-- asciiTable ["this","is","a","test"] "=" [["hi","hi","hi","hi"],["a","a","a","a"],["m","m","m","m"],["k","k","k","k"]] "   "
--
-- > this   is   a   test
-- > ====   ==   =   ====
-- > hi     a    m   k   
-- > hi     a    m   k   
-- > hi     a    m   k   
-- > hi     a    m   k   

join :: [a] -> [[a]] -> [a]
join delim l = concat (intersperse delim l)

asciiTable :: [[Char]] -- ^ a list of column headers
            -> [Char] -- ^ a string containing the character used to separate the data in the columns from the header
            -> [[[Char]]] -- ^ a list of lists containing column data
            -> [Char] -- ^ a string containing the character used to pad between columns
            -> IO ()
asciiTable columnHeaders headerSeparator d spacer = let 
    buildColumn (a,b) = a++b
    padStrings ss = let
        longestString ss = maximum $ map length ss
        l = longestString ss
        toPad s longest = longest - (length s)
        padder longest s = concat $ s:(replicate (toPad s longest) " ")
        in map (padder l) ss
    separator x = replicate (length x ) $ head headerSeparator
    tupleToList (x,y) = x:[y]
    headers = map tupleToList $ zip columnHeaders $ map separator columnHeaders
    preChart = transpose $ map padStrings $ map buildColumn $ zip headers d
    in sequence_ [ putStrLn "\n"
                 , mapM_ putStrLn $ map (join spacer) preChart
                 , putStrLn "\n"
                 ]


playerChartData e = do
    ps <- players e
    ss <- withPlayers e playerStatus ps
    cs <- withPlayers e playerClock ps
    as <- withPlayers e playerAction ps
    is <- withPlayers e playerIOI ps
    let sss = map show ss
    let datum = sss:(map (map fromJust) [cs,as,is])
    return $ ps:datum

-- | Uses the asciiTablefunction to create a five-column table of information about players in a MusicalEnvironment. That information is the player name, its status, the clock it follows, and the action and IOI function it uses when played.

displayPlayers :: MusicalEnvironment -> IO ()
displayPlayers e = let
    pc = "player"
    sc = "status"
    cc = "clock"
    ac = "action function"
    ic = "IOI function"
    columnHeaders = [pc,sc,cc,ac,ic]
    in do d <- playerChartData e
          asciiTable columnHeaders "=" d "   "