aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Citeproc/Util.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Citeproc/Util.hs')
-rw-r--r--src/Text/Pandoc/Citeproc/Util.hs14
1 files changed, 13 insertions, 1 deletions
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