{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FlexibleContexts, ScopedTypeVariables #-}
{-|
Module      : Data.Spreadsheet
Description : Least common denominator of spreadsheet formats
Copyright   : (c) Olaf Klinke
License     : GPL-3
Maintainer  : olaf.klinke@phymetric.de
Stability   : experimental

Various formats for spreadsheet exist, e.g. 
the open office (xlsx) format, 
the Microsoft SpreadsheetML format, 
the binary Microsoft xls format 
and CSV. 

This module defines the least common denominator of static cell data. 
The intention is to use chunks of rows as alternative representation type 
in your ProvenienceT transformer. 
After performing the computation, extract all the spreasheet chunks 
and combine into a worksheet using 'chunksToSheet'. 

For example, in order to use the types of the <http://hackage.haskell.org/package/xlsx xlsx> package 
which exports the @Cell@ and @CellMap@ types, you should provide the following instances. 

@
instance ToCell Cell where
instance ToSheet 'StaticRow' CellMap where
   rowMap = Data.Map.fromList . foldMap (\\(rowidx,row) -> map (\\(colidx,val) -> ((fromIntegral rowidx,fromIntegral colidx),'staticCell' val)) row)
@

where the first instance aids in writing the second instance. 
Then you can use 'SheetChunk' as alternative representation and 
produce a @CellMap@ using 'chunksToSheet'.
-}
module Data.Spreadsheet (
    -- * Speadsheet type classes
    ToCell(..),ToRow(..),ToSheet(..),
    -- * Concrete spreadsheet types
    StaticCellValue(..),
    cellBool,cellNumber,cellText,cellTime,
    StaticRow,StaticSheet,SheetChunk,
    chunksToSheet) where
import Data.Time
import Data.Traversable
import Data.Foldable
import Data.Word
import Data.Sequence (Seq)
import qualified Data.Text as T
import Control.Arrow (second)

-- | A static cell value, the initial object of the 'ToCell' class.
data StaticCellValue = CellBool Bool
    | CellNumber Rational
    | CellText String
    | CellTime ZonedTime deriving (Show)

-- | generic row type: list of cells with column numbers
type StaticRow = [(Word64,StaticCellValue)]
-- | generic sheet type: list of rows with row numbers
type StaticSheet = [(Word64,StaticRow)]
-- | Part of a spreadsheet which does not yet know 
-- its absolute row numbers. 
type SheetChunk = Seq StaticRow
-- | Combine several chunks into a worksheet, e.g. 
-- 
-- @
-- 'chunksToSheet' :: ['SheetChunk'] -> 'StaticSheet'
-- @
chunksToSheet :: (Traversable f, Traversable chunk, Monoid (chunk (Word64,row)), ToSheet row sheet) =>
    f (chunk row) -> sheet
chunksToSheet = rowMap . foldMap id . snd . mapAccumL (\n chunk -> addIndexFrom n chunk) 1

-- | Cell type supporting static values: Booleans, Numbers, Text and Time. 
class ToCell cell where
    staticCell :: StaticCellValue -> cell
instance ToCell StaticCellValue where
    staticCell = id
-- | for building CSV data
instance ToCell T.Text where
    staticCell (CellBool b)   = T.pack . quote . show $ b
    staticCell (CellNumber n) = T.pack . show . (fromRational :: Rational -> Double) $ n
    staticCell (CellText s)   = T.pack . quote . escapeSemicolon $ s
    staticCell (CellTime t)   = T.pack . quote . show $ t

escapeSemicolon :: String -> String
escapeSemicolon = (=<<) e where
    e ';' = "\\;"
    e '\\' = "\\\\"
    e c = [c]
quote :: String -> String
quote = (flip (++) "\"").('"':)

cellBool :: ToCell cell => Bool -> cell
cellBool = staticCell . CellBool
cellNumber :: ToCell cell => Rational -> cell
cellNumber = staticCell . CellNumber
cellText :: ToCell cell => String -> cell
cellText = staticCell . CellText
cellTime :: ToCell cell => ZonedTime -> cell
cellTime = staticCell . CellTime

-- | A @row@ holding several @cell@s
class ToRow cell row where
    cellList :: Traversable f => f cell -> row
    -- ^ default is to number consecutively from 1
    cellList = cellMap . snd . addIndexFrom 1
    cellMap :: Traversable f => f (Word64,cell) -> row
instance ToRow cell [(Word64,cell)] where
    cellMap = Data.Foldable.toList
-- | separates cells with semicolons
instance ToRow T.Text T.Text where
    cellMap = concatWithFrom (T.pack ";") 1
instance ToRow StaticCellValue T.Text where
    cellMap = concatWithFrom (T.pack ";") 1 . fmap (second staticCell)

-- | A worksheet @sheet@ holding several @row@s. 
-- Assemble a worksheet from cells using e.g. either of 
-- 
-- @
-- import Control.Arrow (second)
-- 'rowMap'  . 'fmap' (second 'cellMap')
-- 'rowList' . 'fmap' 'cellList'
-- @
class ToSheet row sheet where
    rowList :: Traversable f => f row -> sheet
    -- ^ default is to number consecutively from 1
    rowList = rowMap . snd . addIndexFrom 1
    rowMap :: Traversable f => f (Word64,row) -> sheet
instance ToSheet row [(Word64,row)] where
    rowMap = Data.Foldable.toList
-- | separates rows by newlines
instance ToSheet T.Text T.Text where
    rowMap = concatWithFrom (T.pack "\n") 1

addIndexFrom :: Traversable f => Word64 -> f b -> (Word64, f (Word64,b))
addIndexFrom i = mapAccumL (\n x -> (n+1,(n,x))) i

-- concat with the right number of separators
concatWithFrom :: (Traversable t, Monoid a) => a -> Int -> t (Word64,a) -> a
concatWithFrom sep i = foldMap id . snd . mapAccumL f i where
    f i (j,x) = let j' = fromIntegral j in (j',mconcat (replicate (j'-i) sep) `mappend` x)