module Data.Text.Util
( readInt
, renderFeed
, renderFeedWith
) where
import Prelude.Compat
import Data.Text
import Data.Text.Read
import qualified Data.Text.Lazy as TL
import qualified Data.XML.Types as XT
import qualified Text.XML as XC
readInt :: Text -> Maybe Integer
readInt :: Text -> Maybe Integer
readInt Text
s =
case Reader Integer
forall a. Integral a => Reader a
decimal Text
s of
Right (Integer
x, Text
_) -> Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
x
Either String (Integer, Text)
_ -> Maybe Integer
forall a. Maybe a
Nothing
renderFeed :: (a -> XT.Element) -> a -> Maybe TL.Text
renderFeed :: (a -> Element) -> a -> Maybe Text
renderFeed = RenderSettings -> (a -> Element) -> a -> Maybe Text
forall a. RenderSettings -> (a -> Element) -> a -> Maybe Text
renderFeedWith RenderSettings
forall a. Default a => a
XC.def
renderFeedWith :: XC.RenderSettings -> (a -> XT.Element) -> a -> Maybe TL.Text
renderFeedWith :: RenderSettings -> (a -> Element) -> a -> Maybe Text
renderFeedWith RenderSettings
opts a -> Element
cf a
f =
let e :: Element
e = a -> Element
cf a
f
d :: Maybe Document
d = Element -> Maybe Document
elToDoc Element
e
in RenderSettings -> Document -> Text
XC.renderText RenderSettings
opts (Document -> Text) -> Maybe Document -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Document
d
elToDoc :: XT.Element -> Maybe XC.Document
elToDoc :: Element -> Maybe Document
elToDoc Element
el =
let txd :: Document
txd = Prologue -> Element -> [Miscellaneous] -> Document
XT.Document ([Miscellaneous] -> Maybe Doctype -> [Miscellaneous] -> Prologue
XC.Prologue [] Maybe Doctype
forall a. Maybe a
Nothing []) Element
el []
cxd :: Either (Set Text) Document
cxd = Document -> Either (Set Text) Document
XC.fromXMLDocument Document
txd
in (Set Text -> Maybe Document)
-> (Document -> Maybe Document)
-> Either (Set Text) Document
-> Maybe Document
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe Document -> Set Text -> Maybe Document
forall a b. a -> b -> a
const Maybe Document
forall a. Maybe a
Nothing) Document -> Maybe Document
forall a. a -> Maybe a
Just Either (Set Text) Document
cxd