aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/Textile.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers/Textile.hs')
-rw-r--r--src/Text/Pandoc/Writers/Textile.hs30
1 files changed, 15 insertions, 15 deletions
diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs
index 26d5ec6d7..e3711911b 100644
--- a/src/Text/Pandoc/Writers/Textile.hs
+++ b/src/Text/Pandoc/Writers/Textile.hs
@@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.Writers.Textile
Copyright : Copyright (C) 2010 John MacFarlane
- License : GNU GPL, version 2 or above
+ License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
Stability : alpha
@@ -31,7 +31,7 @@ Textile: <http://thresholdstate.com/articles/4312/the-textile-reference-manual>
-}
module Text.Pandoc.Writers.Textile ( writeTextile ) where
import Text.Pandoc.Definition
-import Text.Pandoc.Shared
+import Text.Pandoc.Shared
import Text.Pandoc.Templates (renderTemplate)
import Text.Pandoc.XML ( escapeStringForXML )
import Data.List ( intercalate )
@@ -46,9 +46,9 @@ data WriterState = WriterState {
-- | Convert Pandoc to Textile.
writeTextile :: WriterOptions -> Pandoc -> String
-writeTextile opts document =
- evalState (pandocToTextile opts document)
- (WriterState { stNotes = [], stListLevel = [], stUseTags = False })
+writeTextile opts document =
+ evalState (pandocToTextile opts document)
+ (WriterState { stNotes = [], stListLevel = [], stUseTags = False })
-- | Return Textile representation of document.
pandocToTextile :: WriterOptions -> Pandoc -> State WriterState String
@@ -90,14 +90,14 @@ escapeCharForTextile x = case x of
escapeStringForTextile :: String -> String
escapeStringForTextile = concatMap escapeCharForTextile
--- | Convert Pandoc block element to Textile.
+-- | Convert Pandoc block element to Textile.
blockToTextile :: WriterOptions -- ^ Options
-> Block -- ^ Block element
- -> State WriterState String
+ -> State WriterState String
blockToTextile _ Null = return ""
-blockToTextile opts (Plain inlines) =
+blockToTextile opts (Plain inlines) =
inlineListToTextile opts inlines
blockToTextile opts (Para [Image txt (src,tit)]) = do
@@ -236,7 +236,7 @@ listItemToTextile opts items = do
-- | Convert definition list item (label, list of blocks) to Textile.
definitionListItemToTextile :: WriterOptions
- -> ([Inline],[[Block]])
+ -> ([Inline],[[Block]])
-> State WriterState String
definitionListItemToTextile opts (label, items) = do
labelText <- inlineListToTextile opts label
@@ -294,8 +294,8 @@ tableRowToTextile opts alignStrings rownum cols' = do
0 -> "header"
x | x `rem` 2 == 1 -> "odd"
_ -> "even"
- cols'' <- sequence $ zipWith
- (\alignment item -> tableItemToTextile opts celltype alignment item)
+ cols'' <- sequence $ zipWith
+ (\alignment item -> tableItemToTextile opts celltype alignment item)
alignStrings cols'
return $ "<tr class=\"" ++ rowclass ++ "\">\n" ++ unlines cols'' ++ "</tr>"
@@ -320,7 +320,7 @@ tableItemToTextile opts celltype align' item = do
-- | Convert list of Pandoc block elements to Textile.
blockListToTextile :: WriterOptions -- ^ Options
-> [Block] -- ^ List of block elements
- -> State WriterState String
+ -> State WriterState String
blockListToTextile opts blocks =
mapM (blockToTextile opts) blocks >>= return . vcat
@@ -332,11 +332,11 @@ inlineListToTextile opts lst =
-- | Convert Pandoc inline element to Textile.
inlineToTextile :: WriterOptions -> Inline -> State WriterState String
-inlineToTextile opts (Emph lst) = do
+inlineToTextile opts (Emph lst) = do
contents <- inlineListToTextile opts lst
return $ if '_' `elem` contents
then "<em>" ++ contents ++ "</em>"
- else "_" ++ contents ++ "_"
+ else "_" ++ contents ++ "_"
inlineToTextile opts (Strong lst) = do
contents <- inlineListToTextile opts lst
@@ -377,7 +377,7 @@ inlineToTextile opts (Cite _ lst) = inlineListToTextile opts lst
inlineToTextile _ (Code _ str) =
return $ if '@' `elem` str
then "<tt>" ++ escapeStringForXML str ++ "</tt>"
- else "@" ++ str ++ "@"
+ else "@" ++ str ++ "@"
inlineToTextile _ (Str str) = return $ escapeStringForTextile str