{-# LANGUAGE FlexibleContexts    #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Text.Pandoc.Readers.CSV (
  readCSV,
  readTSV
) where
import qualified Data.Text as T
import Text.Pandoc.CSV (parseCSV, defaultCSVOptions, CSVOptions(..))
import Text.Pandoc.Definition
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class (PandocMonad)
import Text.Pandoc.Sources (ToSources(..), sourcesToText)
import Text.Pandoc.Options (ReaderOptions)
import Control.Monad.Except (throwError)
import Data.Text (Text)
import Data.List (intersperse)
import Text.Pandoc.Parsing (fromParsecError)
readCSV :: (PandocMonad m, ToSources a)
        => ReaderOptions 
        -> a
        -> m Pandoc
readCSV :: forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
ReaderOptions -> a -> m Pandoc
readCSV ReaderOptions
_opts a
s = do
  CSVOptions -> Text -> m Pandoc
forall (m :: * -> *).
PandocMonad m =>
CSVOptions -> Text -> m Pandoc
readCSVWith CSVOptions
defaultCSVOptions (Text -> m Pandoc) -> Text -> m Pandoc
forall a b. (a -> b) -> a -> b
$ Sources -> Text
sourcesToText (Sources -> Text) -> Sources -> Text
forall a b. (a -> b) -> a -> b
$ a -> Sources
forall a. ToSources a => a -> Sources
toSources a
s
readTSV :: (PandocMonad m, ToSources a)
        => ReaderOptions 
        -> a
        -> m Pandoc
readTSV :: forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
ReaderOptions -> a -> m Pandoc
readTSV ReaderOptions
_opts a
s = do
  CSVOptions -> Text -> m Pandoc
forall (m :: * -> *).
PandocMonad m =>
CSVOptions -> Text -> m Pandoc
readCSVWith CSVOptions
tsvOpts (Text -> m Pandoc) -> Text -> m Pandoc
forall a b. (a -> b) -> a -> b
$ Sources -> Text
sourcesToText (Sources -> Text) -> Sources -> Text
forall a b. (a -> b) -> a -> b
$ a -> Sources
forall a. ToSources a => a -> Sources
toSources a
s
 where
  tsvOpts :: CSVOptions
tsvOpts = CSVOptions{
    csvDelim :: Char
csvDelim = Char
'\t',
    csvQuote :: Maybe Char
csvQuote = Maybe Char
forall a. Maybe a
Nothing,
    csvKeepSpace :: Bool
csvKeepSpace = Bool
False,
    csvEscape :: Maybe Char
csvEscape = Maybe Char
forall a. Maybe a
Nothing }
readCSVWith :: PandocMonad m
            => CSVOptions
            -> Text
            -> m Pandoc
readCSVWith :: forall (m :: * -> *).
PandocMonad m =>
CSVOptions -> Text -> m Pandoc
readCSVWith CSVOptions
csvopts Text
txt = do
  case CSVOptions -> Text -> Either ParseError [[Text]]
parseCSV CSVOptions
csvopts Text
txt of
    Right ([Text]
r:[[Text]]
rs) -> Pandoc -> m Pandoc
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Pandoc -> m Pandoc) -> Pandoc -> m Pandoc
forall a b. (a -> b) -> a -> b
$ Blocks -> Pandoc
B.doc (Blocks -> Pandoc) -> Blocks -> Pandoc
forall a b. (a -> b) -> a -> b
$ Caption
-> [ColSpec] -> TableHead -> [TableBody] -> TableFoot -> Blocks
B.table Caption
capt
                                             ([Alignment] -> [ColWidth] -> [ColSpec]
forall a b. [a] -> [b] -> [(a, b)]
zip [Alignment]
aligns [ColWidth]
widths)
                                             (Attr -> [Row] -> TableHead
TableHead Attr
nullAttr [Row]
hdrs)
                                             [Attr -> RowHeadColumns -> [Row] -> [Row] -> TableBody
TableBody Attr
nullAttr RowHeadColumns
0 [] [Row]
rows]
                                             (Attr -> [Row] -> TableFoot
TableFoot Attr
nullAttr [])
       where capt :: Caption
capt = Caption
B.emptyCaption
             numcols :: Int
numcols = [Text] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Text]
r
             toplain :: Text -> Cell
toplain = Blocks -> Cell
B.simpleCell (Blocks -> Cell) -> (Text -> Blocks) -> Text -> Cell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Blocks
B.plain (Inlines -> Blocks) -> (Text -> Inlines) -> Text -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines) -> (Text -> [Inlines]) -> Text -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                       Inlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
intersperse Inlines
B.linebreak ([Inlines] -> [Inlines])
-> (Text -> [Inlines]) -> Text -> [Inlines]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Inlines) -> [Text] -> [Inlines]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Inlines
B.text ([Text] -> [Inlines]) -> (Text -> [Text]) -> Text -> [Inlines]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.lines
             toRow :: [Text] -> Row
toRow = Attr -> [Cell] -> Row
Row Attr
nullAttr ([Cell] -> Row) -> ([Text] -> [Cell]) -> [Text] -> Row
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Cell) -> [Text] -> [Cell]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Cell
toplain
             toHeaderRow :: [Text] -> [Row]
toHeaderRow [Text]
l = [[Text] -> Row
toRow [Text]
l | Bool -> Bool
not ([Text] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Text]
l)]
             hdrs :: [Row]
hdrs = [Text] -> [Row]
toHeaderRow [Text]
r
             rows :: [Row]
rows = ([Text] -> Row) -> [[Text]] -> [Row]
forall a b. (a -> b) -> [a] -> [b]
map [Text] -> Row
toRow [[Text]]
rs
             aligns :: [Alignment]
aligns = Int -> Alignment -> [Alignment]
forall a. Int -> a -> [a]
replicate Int
numcols Alignment
AlignDefault
             widths :: [ColWidth]
widths = Int -> ColWidth -> [ColWidth]
forall a. Int -> a -> [a]
replicate Int
numcols ColWidth
ColWidthDefault
    Right []     -> Pandoc -> m Pandoc
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Pandoc -> m Pandoc) -> Pandoc -> m Pandoc
forall a b. (a -> b) -> a -> b
$ Blocks -> Pandoc
B.doc Blocks
forall a. Monoid a => a
mempty
    Left ParseError
e       -> PandocError -> m Pandoc
forall a. PandocError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> m Pandoc) -> PandocError -> m Pandoc
forall a b. (a -> b) -> a -> b
$ Sources -> ParseError -> PandocError
fromParsecError ([(String, Text)] -> Sources
forall a. ToSources a => a -> Sources
toSources [(String
"",Text
txt)]) ParseError
e