{-# LANGUAGE LambdaCase #-}
module Text.Pandoc.Extended
( module Text.Pandoc
, plainToPara
, newlineToSpace
, readPlainText
) where
import Data.Char (isSpace)
import Data.Data.Extended (grecT)
import qualified Data.Text as T
import Prelude
import Text.Pandoc
plainToPara :: [Block] -> [Block]
plainToPara :: [Block] -> [Block]
plainToPara = (Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
map ((Block -> Block) -> [Block] -> [Block])
-> (Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> a -> b
$ \case
Plain [Inline]
inlines -> [Inline] -> Block
Para [Inline]
inlines
Block
block -> Block
block
newlineToSpace :: [Inline] -> [Inline]
newlineToSpace :: [Inline] -> [Inline]
newlineToSpace = (Inline -> Inline) -> [Inline] -> [Inline]
forall a b. (Data a, Data b) => (a -> a) -> b -> b
grecT ((Inline -> Inline) -> [Inline] -> [Inline])
-> (Inline -> Inline) -> [Inline] -> [Inline]
forall a b. (a -> b) -> a -> b
$ \case
Inline
SoftBreak -> Inline
Space
Inline
LineBreak -> Inline
Space
Inline
inline -> Inline
inline
readPlainText :: T.Text -> Pandoc
readPlainText :: Text -> Pandoc
readPlainText = Meta -> [Block] -> Pandoc
Pandoc Meta
forall a. Monoid a => a
mempty ([Block] -> Pandoc) -> (Text -> [Block]) -> Text -> Pandoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Block -> [Block]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Block -> [Block]) -> (Text -> Block) -> Text -> [Block]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Block
Plain ([Inline] -> Block) -> (Text -> [Inline]) -> Text -> Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Inline]
go
where
go :: Text -> [Inline]
go Text
txt0 = case Text -> Maybe (Char, Text)
T.uncons Text
txt0 of
Maybe (Char, Text)
Nothing -> []
Just (Char
' ', Text
txt1) -> Inline
Space Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: Text -> [Inline]
go Text
txt1
Just (Char
'\r', Text
txt1) -> Text -> [Inline]
go Text
txt1
Just (Char
'\n', Text
txt1) -> Inline
SoftBreak Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: Text -> [Inline]
go Text
txt1
Just (Char
c, Text
txt1) ->
let (Text
pre, Text
post) = (Char -> Bool) -> Text -> (Text, Text)
T.break Char -> Bool
isSpace Text
txt1 in
Text -> Inline
Str (Char -> Text -> Text
T.cons Char
c Text
pre) Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: Text -> [Inline]
go Text
post