aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/CSV.hs2
-rw-r--r--src/Text/Pandoc/Readers/CommonMark.hs12
-rw-r--r--src/Text/Pandoc/Readers/DocBook.hs6
-rw-r--r--src/Text/Pandoc/Readers/Docx.hs2
-rw-r--r--src/Text/Pandoc/Readers/DokuWiki.hs2
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs12
-rw-r--r--src/Text/Pandoc/Readers/Haddock.hs2
-rw-r--r--src/Text/Pandoc/Readers/JATS.hs6
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs20
-rw-r--r--src/Text/Pandoc/Readers/Man.hs5
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs4
-rw-r--r--src/Text/Pandoc/Readers/MediaWiki.hs6
-rw-r--r--src/Text/Pandoc/Readers/Muse.hs4
-rw-r--r--src/Text/Pandoc/Readers/Odt/ContentReader.hs4
-rw-r--r--src/Text/Pandoc/Readers/Org/Blocks.hs4
-rw-r--r--src/Text/Pandoc/Readers/RST.hs41
-rw-r--r--src/Text/Pandoc/Readers/TWiki.hs10
-rw-r--r--src/Text/Pandoc/Readers/Textile.hs2
-rw-r--r--src/Text/Pandoc/Readers/Txt2Tags.hs2
19 files changed, 74 insertions, 72 deletions
diff --git a/src/Text/Pandoc/Readers/CSV.hs b/src/Text/Pandoc/Readers/CSV.hs
index 8608a1a2c..a1272d47f 100644
--- a/src/Text/Pandoc/Readers/CSV.hs
+++ b/src/Text/Pandoc/Readers/CSV.hs
@@ -37,6 +37,6 @@ readCSV _opts s =
hdrs = map toplain r
rows = map (map toplain) rs
aligns = replicate numcols AlignDefault
- widths = replicate numcols Nothing
+ widths = replicate numcols ColWidthDefault
Right [] -> return $ B.doc mempty
Left e -> throwError $ PandocParsecError s e
diff --git a/src/Text/Pandoc/Readers/CommonMark.hs b/src/Text/Pandoc/Readers/CommonMark.hs
index 33afbe59f..d1f732bf1 100644
--- a/src/Text/Pandoc/Readers/CommonMark.hs
+++ b/src/Text/Pandoc/Readers/CommonMark.hs
@@ -111,13 +111,19 @@ addBlock opts (Node _ (LIST listAttrs) nodes) =
PAREN_DELIM -> OneParen
exts = readerExtensions opts
addBlock opts (Node _ (TABLE alignments) nodes) =
- (Table nullAttr (Caption Nothing []) (zip aligns widths) 0 headers rows [] :)
+ (Table
+ nullAttr
+ (Caption Nothing [])
+ (zip aligns widths)
+ (TableHead nullAttr headers)
+ [TableBody nullAttr 0 [] rows]
+ (TableFoot nullAttr []) :)
where aligns = map fromTableCellAlignment alignments
fromTableCellAlignment NoAlignment = AlignDefault
fromTableCellAlignment LeftAligned = AlignLeft
fromTableCellAlignment RightAligned = AlignRight
fromTableCellAlignment CenterAligned = AlignCenter
- widths = replicate numcols Nothing
+ widths = replicate numcols ColWidthDefault
numcols = if null rows'
then 0
else maximum $ map rowLength rows'
@@ -136,7 +142,7 @@ addBlock opts (Node _ (TABLE alignments) nodes) =
| isBlockNode n = fromSimpleCell $ addBlocks opts (n:ns)
| otherwise = fromSimpleCell [Plain (addInlines opts (n:ns))]
toCell (Node _ t _) = error $ "toCell encountered non-cell " ++ show t
- fromSimpleCell = Cell nullAttr Nothing 1 1
+ fromSimpleCell = Cell nullAttr AlignDefault 1 1
rowLength (Row _ body) = length body -- all cells are 1×1
addBlock _ (Node _ TABLE_ROW _) = id -- handled in TABLE
addBlock _ (Node _ TABLE_CELL _) = id -- handled in TABLE
diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs
index 6c56c1bd7..4001d647e 100644
--- a/src/Text/Pandoc/Readers/DocBook.hs
+++ b/src/Text/Pandoc/Readers/DocBook.hs
@@ -881,12 +881,12 @@ parseBlock (Elem e) =
[] -> replicate numrows AlignDefault
cs -> map toAlignment cs
let widths = case colspecs of
- [] -> replicate numrows Nothing
+ [] -> replicate numrows ColWidthDefault
cs -> let ws = map toWidth cs
in case sequence ws of
Just ws' -> let tot = sum ws'
- in Just . (/ tot) <$> ws'
- Nothing -> replicate numrows Nothing
+ in ColWidth . (/ tot) <$> ws'
+ Nothing -> replicate numrows ColWidthDefault
let headrows' = if null headrows
then replicate numrows mempty
else headrows
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs
index a5e8cb463..69aa18f73 100644
--- a/src/Text/Pandoc/Readers/Docx.hs
+++ b/src/Text/Pandoc/Readers/Docx.hs
@@ -676,7 +676,7 @@ bodyPartToBlocks (Tbl cap _ look parts@(r:rs)) = do
-- so should be possible. Alignment might be more difficult,
-- since there doesn't seem to be a column entity in docx.
let alignments = replicate width AlignDefault
- widths = replicate width Nothing
+ widths = replicate width ColWidthDefault
return $ table cap' (zip alignments widths) hdrCells cells'
bodyPartToBlocks (OMathPara e) =
diff --git a/src/Text/Pandoc/Readers/DokuWiki.hs b/src/Text/Pandoc/Readers/DokuWiki.hs
index 296c751a2..ee26eed84 100644
--- a/src/Text/Pandoc/Readers/DokuWiki.hs
+++ b/src/Text/Pandoc/Readers/DokuWiki.hs
@@ -470,7 +470,7 @@ table = do
let (headerRow, body) = if firstSeparator == '^'
then (head rows, tail rows)
else ([], rows)
- let attrs = (AlignDefault, Nothing) <$ transpose rows
+ let attrs = (AlignDefault, ColWidthDefault) <$ transpose rows
pure $ B.table mempty attrs headerRow body
tableRows :: PandocMonad m => DWParser m [[B.Blocks]]
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index 8de9ebc19..30b812913 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -513,12 +513,12 @@ pTable = try $ do
_ -> replicate cols AlignDefault
let widths = if null widths'
then if isSimple
- then replicate cols Nothing
- else replicate cols (Just (1.0 / fromIntegral cols))
+ then replicate cols ColWidthDefault
+ else replicate cols (ColWidth (1.0 / fromIntegral cols))
else widths'
return $ B.table caption (zip aligns widths) head' rows
-pCol :: PandocMonad m => TagParser m (Maybe Double)
+pCol :: PandocMonad m => TagParser m ColWidth
pCol = try $ do
TagOpen _ attribs' <- pSatisfy (matchTagOpen "col" [])
let attribs = toStringAttr attribs'
@@ -535,10 +535,10 @@ pCol = try $ do
fromMaybe 0.0 $ safeRead xs
_ -> 0.0
if width > 0.0
- then return $ Just $ width / 100.0
- else return Nothing
+ then return $ ColWidth $ width / 100.0
+ else return ColWidthDefault
-pColgroup :: PandocMonad m => TagParser m [Maybe Double]
+pColgroup :: PandocMonad m => TagParser m [ColWidth]
pColgroup = try $ do
pSatisfy (matchTagOpen "colgroup" [])
skipMany pBlank
diff --git a/src/Text/Pandoc/Readers/Haddock.hs b/src/Text/Pandoc/Readers/Haddock.hs
index 7303f9c32..5bef6f9fd 100644
--- a/src/Text/Pandoc/Readers/Haddock.hs
+++ b/src/Text/Pandoc/Readers/Haddock.hs
@@ -91,7 +91,7 @@ docHToBlocks d' =
else (toCells (head headerRows),
map toCells (tail headerRows ++ bodyRows))
colspecs = replicate (maximum (map length body))
- (AlignDefault, Nothing)
+ (AlignDefault, ColWidthDefault)
in B.table mempty colspecs header body
where inlineFallback = B.plain $ docHToInlines False d'
diff --git a/src/Text/Pandoc/Readers/JATS.hs b/src/Text/Pandoc/Readers/JATS.hs
index 3dfe9161b..24d2ef4a1 100644
--- a/src/Text/Pandoc/Readers/JATS.hs
+++ b/src/Text/Pandoc/Readers/JATS.hs
@@ -274,12 +274,12 @@ parseBlock (Elem e) =
[] -> replicate numrows AlignDefault
cs -> map toAlignment cs
let widths = case colspecs of
- [] -> replicate numrows Nothing
+ [] -> replicate numrows ColWidthDefault
cs -> let ws = map toWidth cs
in case sequence ws of
Just ws' -> let tot = sum ws'
- in Just . (/ tot) <$> ws'
- Nothing -> replicate numrows Nothing
+ in ColWidth . (/ tot) <$> ws'
+ Nothing -> replicate numrows ColWidthDefault
let headrows' = if null headrows
then replicate numrows mempty
else headrows
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 4b09f1402..ea5549543 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -2268,7 +2268,7 @@ splitWordTok = do
setInput $ map (Tok spos Symbol . T.singleton) (T.unpack t) <> rest
_ -> return ()
-parseAligns :: PandocMonad m => LP m [(Alignment, Maybe Double, ([Tok], [Tok]))]
+parseAligns :: PandocMonad m => LP m [(Alignment, ColWidth, ([Tok], [Tok]))]
parseAligns = try $ do
let maybeBar = skipMany
(try $ sp *> (() <$ symbol '|' <|> () <$ (symbol '@' >> braced)))
@@ -2319,7 +2319,11 @@ parseAligns = try $ do
spaces
egroup
spaces
- return aligns'
+ return $ map toSpec aligns'
+ where
+ toColWidth (Just w) | w > 0 = ColWidth w
+ toColWidth _ = ColWidthDefault
+ toSpec (x, y, z) = (x, toColWidth y, z)
parseTableRow :: PandocMonad m
=> Text -- ^ table environment name
@@ -2397,11 +2401,11 @@ simpTable envname hasWidthParameter = try $ do
addTableCaption :: PandocMonad m => Blocks -> LP m Blocks
addTableCaption = walkM go
- where go (Table attr c spec rhs th tb tf) = do
+ where go (Table attr c spec th tb tf) = do
st <- getState
let mblabel = sLastLabel st
capt <- case (sCaption st, mblabel) of
- (Just ils, Nothing) -> return $ Caption Nothing (mcap ils)
+ (Just ils, Nothing) -> return $ caption Nothing (plain ils)
(Just ils, Just lab) -> do
num <- getNextNumber sLastTableNum
setState
@@ -2409,15 +2413,11 @@ addTableCaption = walkM go
, sLabels = M.insert lab
[Str (renderDottedNum num)]
(sLabels st) }
- return $ Caption Nothing (mcap ils) -- add number??
+ return $ caption Nothing (plain ils) -- add number??
(Nothing, _) -> return c
return $ maybe id (\ident -> Div (ident, [], []) . (:[])) mblabel $
- Table attr capt spec rhs th tb tf
+ Table attr capt spec th tb tf
go x = return x
- mcap ils
- | isNull ils = []
- | otherwise = [Para $ toList ils]
-
block :: PandocMonad m => LP m Blocks
block = do
diff --git a/src/Text/Pandoc/Readers/Man.hs b/src/Text/Pandoc/Readers/Man.hs
index 50dbb5992..e175135da 100644
--- a/src/Text/Pandoc/Readers/Man.hs
+++ b/src/Text/Pandoc/Readers/Man.hs
@@ -107,9 +107,8 @@ parseTable = do
bodyRows <- mapM (mapM parseTableCell . snd) bodyRows'
isPlainTable <- tableCellsPlain <$> getState
let widths = if isPlainTable
- then repeat Nothing
- else repeat (Just (1.0 / fromIntegral (length alignments))
- :: Maybe Double)
+ then repeat ColWidthDefault
+ else repeat $ ColWidth (1.0 / fromIntegral (length alignments))
return $ B.table mempty (zip alignments widths)
headerRow bodyRows) <|> fallback pos
[] -> fallback pos
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 54d2752c7..222c227e2 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -1418,8 +1418,8 @@ table = try $ do
then widths
else map (/ totalWidth) widths
let strictPos w
- | w > 0 = Just w
- | otherwise = Nothing
+ | w > 0 = ColWidth w
+ | otherwise = ColWidthDefault
return $ do
caption' <- caption
heads' <- heads
diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs
index 5e9aecc49..0396c95de 100644
--- a/src/Text/Pandoc/Readers/MediaWiki.hs
+++ b/src/Text/Pandoc/Readers/MediaWiki.hs
@@ -221,9 +221,9 @@ table = do
let restwidth = tableWidth - sum widths
let zerocols = length $ filter (==0.0) widths
let defaultwidth = if zerocols == 0 || zerocols == length widths
- then Nothing
- else Just $ restwidth / fromIntegral zerocols
- let widths' = map (\w -> if w == 0 then defaultwidth else Just w) widths
+ then ColWidthDefault
+ else ColWidth $ restwidth / fromIntegral zerocols
+ let widths' = map (\w -> if w > 0 then ColWidth w else defaultwidth) widths
let cellspecs = zip (map fst cellspecs') widths'
rows' <- many $ try $ rowsep *> (map snd <$> tableRow)
optional blanklines
diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs
index 1cabfa112..34a9a7367 100644
--- a/src/Text/Pandoc/Readers/Muse.hs
+++ b/src/Text/Pandoc/Readers/Muse.hs
@@ -646,7 +646,7 @@ data MuseTableElement = MuseHeaderRow [Blocks]
museToPandocTable :: MuseTable -> Blocks
museToPandocTable (MuseTable caption headers body footers) =
B.table caption attrs headRow (rows ++ body ++ footers)
- where attrs = (AlignDefault, Nothing) <$ transpose (headers ++ body ++ footers)
+ where attrs = (AlignDefault, ColWidthDefault) <$ transpose (headers ++ body ++ footers)
(headRow, rows) = fromMaybe ([], []) $ uncons headers
museAppendElement :: MuseTableElement
@@ -694,7 +694,7 @@ museGridTable = try $ do
indices <- museGridTableHeader
fmap rowsToTable . sequence <$> many1 (museGridTableRow indent indices)
where rowsToTable rows = B.table mempty attrs [] rows
- where attrs = (AlignDefault, Nothing) <$ transpose rows
+ where attrs = (AlignDefault, ColWidthDefault) <$ transpose rows
-- | Parse a table.
table :: PandocMonad m => MuseParser m (F Blocks)
diff --git a/src/Text/Pandoc/Readers/Odt/ContentReader.hs b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
index 2afd8a66d..cbf7236d0 100644
--- a/src/Text/Pandoc/Readers/Odt/ContentReader.hs
+++ b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
@@ -921,8 +921,8 @@ post_process (Pandoc m blocks) =
Pandoc m (post_process' blocks)
post_process' :: [Block] -> [Block]
-post_process' (Table attr _ specs rhs th tb tf : Div ("", ["caption"], _) blks : xs)
- = Table attr (Caption Nothing blks) specs rhs th tb tf : post_process' xs
+post_process' (Table attr _ specs th tb tf : Div ("", ["caption"], _) blks : xs)
+ = Table attr (Caption Nothing blks) specs th tb tf : post_process' xs
post_process' bs = bs
read_body :: OdtReader _x (Pandoc, MediaBag)
diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs
index aef6ae210..5dbaa2a17 100644
--- a/src/Text/Pandoc/Readers/Org/Blocks.hs
+++ b/src/Text/Pandoc/Readers/Org/Blocks.hs
@@ -629,14 +629,14 @@ orgToPandocTable (OrgTable colProps heads lns) caption =
else Nothing
in B.table caption (map (convertColProp totalWidth) colProps) heads lns
where
- convertColProp :: Maybe Int -> ColumnProperty -> (Alignment, Maybe Double)
+ convertColProp :: Maybe Int -> ColumnProperty -> (Alignment, ColWidth)
convertColProp totalWidth colProp =
let
align' = fromMaybe AlignDefault $ columnAlignment colProp
width' = (\w t -> (fromIntegral w / fromIntegral t))
<$> columnRelWidth colProp
<*> totalWidth
- in (align', width')
+ in (align', maybe ColWidthDefault ColWidth width')
tableRows :: PandocMonad m => OrgParser m [OrgTableRow]
tableRows = try $ many (tableAlignRow <|> tableHline <|> tableContentRow)
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index 5db303d4d..0dadd5120 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -770,17 +770,17 @@ tableDirective :: PandocMonad m
tableDirective top fields body = do
bs <- parseFromString' parseBlocks body
case B.toList bs of
- [Table attr _ tspecs' rhs thead tbody tfoot] -> do
+ [Table attr _ tspecs' thead@(TableHead _ thrs) tbody tfoot] -> do
let (aligns', widths') = unzip tspecs'
title <- parseFromString' (trimInlines . mconcat <$> many inline) top
columns <- getOption readerColumns
- let numOfCols = case thead of
+ let numOfCols = case thrs of
[] -> 0
(r:_) -> rowLength r
let normWidths ws =
strictPos . (/ max 1.0 (fromIntegral (columns - numOfCols))) <$> ws
let widths = case trim <$> lookup "widths" fields of
- Just "auto" -> replicate numOfCols Nothing
+ Just "auto" -> replicate numOfCols ColWidthDefault
Just "grid" -> widths'
Just specs -> normWidths
$ map (fromMaybe (0 :: Double) . safeRead)
@@ -788,19 +788,16 @@ tableDirective top fields body = do
Nothing -> widths'
-- align is not applicable since we can't represent whole table align
let tspecs = zip aligns' widths
- return $ B.singleton $ Table attr (Caption Nothing (mpara title))
- tspecs rhs thead tbody tfoot
+ return $ B.singleton $ Table attr (B.caption Nothing (B.plain title))
+ tspecs thead tbody tfoot
_ -> return mempty
where
-- only valid on the very first row of a table section
rowLength (Row _ rb) = sum $ cellLength <$> rb
- cellLength (Cell _ _ _ w _) = if w < 0 then 0 else w
+ cellLength (Cell _ _ _ w _) = max 1 (getColSpan w)
strictPos w
- | w > 0 = Just w
- | otherwise = Nothing
- mpara t
- | B.isNull t = []
- | otherwise = [Para $ B.toList t]
+ | w > 0 = ColWidth w
+ | otherwise = ColWidthDefault
-- TODO: :stub-columns:.
-- Only the first row becomes the header even if header-rows: > 1,
@@ -821,10 +818,10 @@ listTableDirective top fields body = do
else ([], rows, length x)
_ -> ([],[],0)
widths = case trim <$> lookup "widths" fields of
- Just "auto" -> replicate numOfCols Nothing
+ Just "auto" -> replicate numOfCols ColWidthDefault
Just specs -> normWidths $ map (fromMaybe (0 :: Double) . safeRead) $
splitTextBy (`elem` (" ," :: String)) specs
- _ -> replicate numOfCols Nothing
+ _ -> replicate numOfCols ColWidthDefault
return $ B.table title
(zip (replicate numOfCols AlignDefault) widths)
headerRow
@@ -835,8 +832,8 @@ listTableDirective top fields body = do
takeCells _ = []
normWidths ws = strictPos . (/ max 1 (sum ws)) <$> ws
strictPos w
- | w > 0 = Just w
- | otherwise = Nothing
+ | w > 0 = ColWidth w
+ | otherwise = ColWidthDefault
csvTableDirective :: PandocMonad m
=> Text -> [(Text, Text)] -> Text
@@ -890,16 +887,16 @@ csvTableDirective top fields rawcsv = do
_ -> ([],[],0)
title <- parseFromString' (trimInlines . mconcat <$> many inline) top
let strictPos w
- | w > 0 = Just w
- | otherwise = Nothing
+ | w > 0 = ColWidth w
+ | otherwise = ColWidthDefault
let normWidths ws = strictPos . (/ max 1 (sum ws)) <$> ws
let widths =
case trim <$> lookup "widths" fields of
- Just "auto" -> replicate numOfCols Nothing
+ Just "auto" -> replicate numOfCols ColWidthDefault
Just specs -> normWidths
$ map (fromMaybe (0 :: Double) . safeRead)
$ splitTextBy (`elem` (" ," :: String)) specs
- _ -> replicate numOfCols Nothing
+ _ -> replicate numOfCols ColWidthDefault
return $ B.table title
(zip (replicate numOfCols AlignDefault) widths)
headerRow
@@ -1312,14 +1309,14 @@ simpleTable headless = do
sep simpleTableFooter
-- Simple tables get 0s for relative column widths (i.e., use default)
case B.toList tbl of
- [Table attr cap spec rhs th tb tf] -> return $ B.singleton $
- Table attr cap (rewidth spec) rhs th tb tf
+ [Table attr cap spec th tb tf] -> return $ B.singleton $
+ Table attr cap (rewidth spec) th tb tf
_ ->
throwError $ PandocShouldNeverHappenError
"tableWith returned something unexpected"
where
sep = return () -- optional (simpleTableSep '-')
- rewidth = fmap $ fmap $ const Nothing
+ rewidth = fmap $ fmap $ const ColWidthDefault
gridTable :: PandocMonad m
=> Bool -- ^ Headerless table
diff --git a/src/Text/Pandoc/Readers/TWiki.hs b/src/Text/Pandoc/Readers/TWiki.hs
index f14e3f710..b39e3303e 100644
--- a/src/Text/Pandoc/Readers/TWiki.hs
+++ b/src/Text/Pandoc/Readers/TWiki.hs
@@ -229,11 +229,11 @@ table = try $ do
where
buildTable caption rows (aligns, heads)
= B.table caption aligns heads rows
- align rows = replicate (columCount rows) (AlignDefault, Nothing)
+ align rows = replicate (columCount rows) (AlignDefault, ColWidthDefault)
columns rows = replicate (columCount rows) mempty
columCount rows = length $ head rows
-tableParseHeader :: PandocMonad m => TWParser m ((Alignment, Maybe Double), B.Blocks)
+tableParseHeader :: PandocMonad m => TWParser m ((Alignment, ColWidth), B.Blocks)
tableParseHeader = try $ do
char '|'
leftSpaces <- length <$> many spaceChar
@@ -245,9 +245,9 @@ tableParseHeader = try $ do
return (tableAlign leftSpaces rightSpaces, content)
where
tableAlign left right
- | left >= 2 && left == right = (AlignCenter, Nothing)
- | left > right = (AlignRight, Nothing)
- | otherwise = (AlignLeft, Nothing)
+ | left >= 2 && left == right = (AlignCenter, ColWidthDefault)
+ | left > right = (AlignRight, ColWidthDefault)
+ | otherwise = (AlignLeft, ColWidthDefault)
tableParseRow :: PandocMonad m => TWParser m [B.Blocks]
tableParseRow = many1Till tableParseColumn newline
diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs
index 3d2a962e9..a0680ac81 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -378,7 +378,7 @@ table = try $ do
let nbOfCols = maximum $ map length (headers:rows)
let aligns = map minimum $ transpose $ map (map (snd . fst)) (headers:rows)
return $ B.table caption
- (zip aligns (replicate nbOfCols Nothing))
+ (zip aligns (replicate nbOfCols ColWidthDefault))
(map snd headers)
(map (map snd) rows)
diff --git a/src/Text/Pandoc/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs
index 5d2f11864..fc1c8c5cf 100644
--- a/src/Text/Pandoc/Readers/Txt2Tags.hs
+++ b/src/Text/Pandoc/Readers/Txt2Tags.hs
@@ -268,7 +268,7 @@ table = try $ do
let rowsPadded = map (pad size) rows'
let headerPadded = if null tableHeader then mempty else pad size tableHeader
return $ B.table mempty
- (zip aligns (replicate ncolumns Nothing))
+ (zip aligns (replicate ncolumns ColWidthDefault))
headerPadded rowsPadded
pad :: (Monoid a) => Int -> [a] -> [a]