-----------------------------------------------------------------------------
--
-- Module      :  Data.Table
-- Copyright   :  (c) 2014-16 Brian W Bush
-- License     :  MIT
--
-- Maintainer  :  Brian W Bush <consult@brianwbush.info>
-- Stability   :  Experimental
-- Portability :  Portable
--
-- | Tables of data.
--
-----------------------------------------------------------------------------


module Data.Table {-# DEPRECATED "This module will be replaced in a future release." #-} (
-- * Tables
  Tabulatable(..)
, labels1
, tabulation1
, labels2
, tabulation2
, labels3
, tabulation3
) where


import Codec.Compression.GZip (compress, decompress)
import Control.Monad (ap)
import Data.List (intercalate, transpose)
import Data.List.Split (splitOn)

import qualified Data.ByteString.Lazy.Char8 as BS (pack, readFile, unpack, writeFile)


-- | Class for tables with headers and records of fields.
class Tabulatable a where
  -- | Retrieve the header.
  labels :: a -> [String]
  -- | Retrieve the fields for a record.
  tabulation :: a -> [String]
  -- | Retrieve the fields for records.
  tabulations :: [a] -> [[String]]
  tabulations = ap ((:) . labels . head) (map tabulation)
  -- | Retrieve and transpose the fields for records.
  tabulationsT :: [a] -> [[String]]
  tabulationsT = transpose . tabulations
  -- | Retrieve the fields for records as tabbed lines.
  tabulations' :: [a] -> String
  tabulations' = unlines . map (intercalate "\t") . tabulations
  -- | Retrieve the fields for records as transposed tabbed lines.
  tabulationsT' :: [a] -> String
  tabulationsT' = unlines . map (intercalate "\t") . tabulationsT
  -- | Make a record from a string for the fields.
  untabulation :: [String] -> a
  -- | Make records from strings for the fields.
  untabulations :: [[String]] -> [a]
  untabulations = map untabulation . tail
  -- | Make records from tabbed lines for the fields.
  untabulations' :: String -> [a]
  untabulations' = untabulations . map (splitOn "\t") . lines
  -- | Sort the tabulation.
  sorted :: [a] -> [a]
  sorted = undefined
  -- | Find a field in the tabulation.
  find :: a -> [a] -> Maybe a
  find = undefined
  -- | Read from a file.
  readUncompressed :: FilePath -> IO [a]
  readUncompressed = fmap untabulations' . readFile
  -- | Read from a compressed file.
  readCompressed :: FilePath -> IO [a]
  readCompressed = fmap (untabulations' . BS.unpack . decompress) . BS.readFile
  -- | Write to a file.
  writeUncompressed :: FilePath -> [a] -> IO ()
  writeUncompressed = (. tabulations') . writeFile
  -- | Write to a compressed file.
  writeCompressed :: FilePath -> [a] -> IO ()
  writeCompressed = (. compress . BS.pack . tabulations') . BS.writeFile


-- | Collate the headers from a tabulation.
labels1 :: Tabulatable a
        => String        -- ^ An additional column label.
        -> a             -- ^ The first tabulation.
        -> [String]      -- ^ The collated header.
labels1 s x = labels x ++ [s]


-- | Collate the headers from two tabulations.
labels2 :: (Tabulatable a, Tabulatable b)
        => String                         -- ^ An additional column label.
        -> a                              -- ^ The first tabulation.
        -> b                              -- ^ The second tabulation.
        -> [String]                       -- ^ The collated header.
labels2 s x y = concat [labels x, labels y, [s]]


-- | Collate the headers from three tabulations.
labels3 :: (Tabulatable a, Tabulatable b, Tabulatable c)
        => String                                        -- ^ An additional column label.
        -> a                                             -- ^ The first tabulation.
        -> b                                             -- ^ The second tabulation.
        -> c                                             -- ^ The third tabulation.
        -> [String]                                      -- ^ The collated header.
labels3 s x y z = concat [labels x, labels y, labels z, [s]]


-- | Collate and show a tabulation.
tabulation1 :: (Tabulatable a, Show e)
            => a                       -- ^ The tabulation.
            -> e                       -- ^ An additional column.
            -> [String]                -- ^ The list of string representations.
tabulation1 x s = tabulation x ++ [show s]


-- | Collate and show two tabulations.
tabulation2 :: (Tabulatable a, Tabulatable b, Show e)
            => a                                      -- ^ The first tabulation.
            -> b                                      -- ^ The second tabulation.
            -> e                                      -- ^ An additional column.
            -> [String]                               -- ^ The list of string representations.
tabulation2 x y s = concat [tabulation x, tabulation y, [show s]]


-- | Collate and show three tabulations.
tabulation3 :: (Tabulatable a, Tabulatable b, Tabulatable c, Show e)
            => a                                                     -- ^ The first tabulation.
            -> b                                                     -- ^ The second tabulation.
            -> c                                                     -- ^ The third tabulation.
            -> e                                                     -- ^ An additional column.
            -> [String]                                              -- ^ The list of string representations.
tabulation3 x y z s = concat [tabulation x, tabulation y, tabulation z, [show s]]