diff options
Diffstat (limited to 'src/Text/Pandoc/Citeproc')
-rw-r--r-- | src/Text/Pandoc/Citeproc/BibTeX.hs | 11 | ||||
-rw-r--r-- | src/Text/Pandoc/Citeproc/Locator.hs | 13 | ||||
-rw-r--r-- | src/Text/Pandoc/Citeproc/Util.hs | 14 |
3 files changed, 15 insertions, 23 deletions
diff --git a/src/Text/Pandoc/Citeproc/BibTeX.hs b/src/Text/Pandoc/Citeproc/BibTeX.hs index 9dcefb8d3..75990f0a7 100644 --- a/src/Text/Pandoc/Citeproc/BibTeX.hs +++ b/src/Text/Pandoc/Citeproc/BibTeX.hs @@ -34,7 +34,7 @@ import Text.Pandoc.Class (runPure) import qualified Text.Pandoc.Walk as Walk import Citeproc.Types import Citeproc.Pandoc () -import Text.Pandoc.Citeproc.Util (toIETF) +import Text.Pandoc.Citeproc.Util (toIETF, splitStrWhen) import Text.Pandoc.Citeproc.Data (biblatexStringMap) import Data.Default import Data.Text (Text) @@ -1256,15 +1256,6 @@ toName opts ils = do , nameStaticOrdering = False } --- Split Str elements so that characters satisfying the --- predicate each have their own Str. -splitStrWhen :: (Char -> Bool) -> [Inline] -> [Inline] -splitStrWhen p = foldr go [] - where - go (Str t) = (map Str (T.groupBy goesTogether t) ++) - go x = (x :) - goesTogether c d = not (p c || p d) - ordinalize :: Locale -> Text -> Text ordinalize locale n = let terms = localeTerms locale diff --git a/src/Text/Pandoc/Citeproc/Locator.hs b/src/Text/Pandoc/Citeproc/Locator.hs index f8931d7b5..ce606197b 100644 --- a/src/Text/Pandoc/Citeproc/Locator.hs +++ b/src/Text/Pandoc/Citeproc/Locator.hs @@ -5,6 +5,7 @@ module Text.Pandoc.Citeproc.Locator ( parseLocator ) where import Citeproc.Types +import Text.Pandoc.Citeproc.Util (splitStrWhen) import Data.Text (Text) import qualified Data.Text as T import Data.List (foldl') @@ -247,18 +248,6 @@ isLocatorSep ',' = True isLocatorSep ';' = True isLocatorSep _ = False -splitStrWhen :: (Char -> Bool) -> [Inline] -> [Inline] -splitStrWhen _ [] = [] -splitStrWhen p (Str xs : ys) = go (T.unpack xs) ++ splitStrWhen p ys - where - go [] = [] - go s = case break p s of - ([],[]) -> [] - (zs,[]) -> [Str $ T.pack zs] - ([],w:ws) -> Str (T.singleton w) : go ws - (zs,w:ws) -> Str (T.pack zs) : Str (T.singleton w) : go ws -splitStrWhen p (x : ys) = x : splitStrWhen p ys - -- -- Locator Map -- diff --git a/src/Text/Pandoc/Citeproc/Util.hs b/src/Text/Pandoc/Citeproc/Util.hs index 6d8e01bc9..8bffc0f32 100644 --- a/src/Text/Pandoc/Citeproc/Util.hs +++ b/src/Text/Pandoc/Citeproc/Util.hs @@ -1,9 +1,21 @@ {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedStrings #-} module Text.Pandoc.Citeproc.Util - ( toIETF ) + ( splitStrWhen + , toIETF ) where +import qualified Data.Text as T import Data.Text (Text) +import Text.Pandoc.Definition + +-- Split Str elements so that characters satisfying the +-- predicate each have their own Str. +splitStrWhen :: (Char -> Bool) -> [Inline] -> [Inline] +splitStrWhen p = foldr go [] + where + go (Str t) = (map Str (T.groupBy goesTogether t) ++) + go x = (x :) + goesTogether c d = not (p c || p d) toIETF :: Text -> Text toIETF "english" = "en-US" -- "en-EN" unavailable in CSL |