Moved headerShift from pandoc.hs to Shared.
This commit is contained in:
parent
5765ac2523
commit
cfb27ece34
2 changed files with 10 additions and 7 deletions
|
@ -62,6 +62,7 @@ module Text.Pandoc.Shared (
|
|||
hierarchicalize,
|
||||
uniqueIdent,
|
||||
isHeaderBlock,
|
||||
headerShift,
|
||||
-- * Writer options
|
||||
HTMLMathMethod (..),
|
||||
ObfuscationMethod (..),
|
||||
|
@ -439,6 +440,13 @@ isHeaderBlock :: Block -> Bool
|
|||
isHeaderBlock (Header _ _) = True
|
||||
isHeaderBlock _ = False
|
||||
|
||||
-- | Shift header levels up or down.
|
||||
headerShift :: Int -> Pandoc -> Pandoc
|
||||
headerShift n = processWith shift
|
||||
where shift :: Block -> Block
|
||||
shift (Header level inner) = Header (level + n) inner
|
||||
shift x = x
|
||||
|
||||
--
|
||||
-- Writer options
|
||||
--
|
||||
|
|
|
@ -31,7 +31,8 @@ writers.
|
|||
module Main where
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Writers.S5 (s5HeaderIncludes)
|
||||
import Text.Pandoc.Shared ( tabFilter, ObfuscationMethod (..), readDataFile )
|
||||
import Text.Pandoc.Shared ( tabFilter, ObfuscationMethod (..), readDataFile,
|
||||
headerShift )
|
||||
#ifdef _HIGHLIGHTING
|
||||
import Text.Pandoc.Highlighting ( languages )
|
||||
#endif
|
||||
|
@ -127,12 +128,6 @@ writers = [("native" , writeNative)
|
|||
isNonTextOutput :: String -> Bool
|
||||
isNonTextOutput = (`elem` ["odt","epub"])
|
||||
|
||||
headerShift :: Int -> Pandoc -> Pandoc
|
||||
headerShift n = processWith shift
|
||||
where shift :: Block -> Block
|
||||
shift (Header level inner) = Header (level + n) inner
|
||||
shift x = x
|
||||
|
||||
-- | Data structure for command line options.
|
||||
data Opt = Opt
|
||||
{ optTabStop :: Int -- ^ Number of spaces per tab
|
||||
|
|
Loading…
Reference in a new issue