{-# LANGUAGE OverloadedStrings #-}
module Main where
import System.Environment
import Data.Char (isSpace)
import qualified Network.HTTP.Client as HTTP
import Network.HTTP.Client.Internal
import qualified Network.HTTP.Client.TLS as TLS
import Network.URI
import qualified Data.ByteString.Lazy.Char8 as C8
import qualified Text.HTML.DOM as HTML
import qualified Text.XML as XML
import Data.Text as Txt (pack, unpack, Text(..), append,
words, unwords, head, last, stripStart, stripEnd)
import qualified Data.CSS.Syntax.StyleSheet as CSS
import qualified Data.CSS.Style as Style
import qualified Data.CSS.Syntax.Tokens as CSSTok
import qualified Data.HTML2CSS as H2C
import qualified Data.List as L
import qualified Data.Map as M
import Data.Scientific (toRealFloat)
import DefaultCSS
import StyleTree
main :: IO ()
main = do
url:_ <- getArgs
-- TODO support more URI schemes, and do nonblocking networking. This could be it's own module.
request <- HTTP.parseRequest url
manager <- HTTP.newManager TLS.tlsManagerSettings
response <- HTTP.httpLbs request manager
let html = XML.documentRoot $ HTML.parseLBS $ HTTP.responseBody response
style <- retreiveStyles html manager request
let transcript = stylize style html
C8.putStrLn $ renderElLBS $ styleToSSML transcript
retreiveStyles html manager base = do
style <- H2C.externalStyles authorStyle testMedia html loadURL
return style
where
emptyStyle :: Style.QueryableStyleSheet StyleTree
emptyStyle = Style.queryableStyleSheet
agentStyle = H2C.cssPriorityAgent emptyStyle `CSS.parse` Txt.pack userAgentCSS
authorStyle = H2C.internalStyles testMedia agentStyle html
loadURL url = do -- TODO parallelise.
request <- setUriRelative base url
response <- HTTP.httpLbs request manager
return $ Txt.pack $ C8.unpack $ HTTP.responseBody response
testMedia attrs = media == Nothing || media == Just "speech"
where media = "media" `M.lookup` attrs
stylize styles html = H2C.traverseStyles buildNode buildText styles html
where
buildNode self children = self {children = children}
buildText _ txt = Style.temp {content = txt}
styleToSSML StyleTree {speak = False} =
XML.Element (XML.Name "blank" Nothing Nothing) M.empty []
styleToSSML self = buildEl0 "prosody" [
("volume", volume self),
("rate", rate self),
("pitch", serializePitch $ pitch self),
("range", serializePitch $ range self)
] $ buildEl0 "emphasis" [("level", stress self)] $
buildEl0 "say-as" [("interpret-as", speakAs self)] $
buildEl0 "tts:style" [
("field", maybeBool (punctuation self) "punctuation" "punctuation"),
("mode", maybeBool (punctuation self) "all" "none")
] $ buildVoices (voice self) (
XML.NodeContent (content self) :
map (\node -> XML.NodeElement $ styleToSSML node) (children self)
)
serializePitch Inherit = Nothing
serializePitch (Pitch kw) = Just kw
serializePitch (Absolute "khz" n) = serializePitch $ Absolute "hz" (1000 * n)
serializePitch (Absolute _ n) | n < 0 = Nothing
| otherwise = Just $ Txt.pack (show n ++ "hz")
serializePitch (Relative "khz" n) = serializePitch $ Relative "hz" (1000 * n)
serializePitch (Relative _ n) | n < 0 = Just $ Txt.pack (show n ++ "hz")
| otherwise = Just $ Txt.pack ("+" ++ show n ++ "hz")
maybeBool (Just True) truthy _ = Just truthy
maybeBool (Just False) _ falsy = Just falsy
maybeBool Nothing _ _ = Nothing
maybeCast (Just n) = Just $ Txt.pack $ show n
maybeCast Nothing = Nothing
buildVoice (Voice name) children = buildEl "voice" [("name", Just name)] children
buildVoice (VoicePattern age gender variant) children = buildEl "voice" [
("age", maybeCast age),
("gender", Just gender),
("variant", maybeCast variant)
] children
buildVoices Nothing = buildEl "blank" []
buildVoices (Just voice) = buildVoice voice
--------
---- XML Output Utils
--------
buildEl name attrs elChildren =
XML.Element (XML.Name name Nothing Nothing) (attrsFromList attrs) elChildren
buildEl0 name attrs child = buildEl name attrs [XML.NodeElement child]
attrsFromList ((name, Just value):attrs) =
M.insert (XML.Name name Nothing Nothing) value $ attrsFromList attrs
attrsFromList ((_, Nothing):attrs) = attrsFromList attrs
attrsFromList [] = M.empty
stripEmptyEls (XML.Element name attrs elChildren) =
XML.Element name attrs $ stripEmptyNodes elChildren
stripEmptyNodes (XML.NodeElement el@(XML.Element _ attrs elChildren ):nodes)
| M.null attrs = stripEmptyNodes (elChildren ++ nodes)
| otherwise = XML.NodeElement (stripEmptyEls el) : stripEmptyNodes nodes
stripEmptyNodes (XML.NodeContent txt : nodes) = -- strip whitespace
XML.NodeContent (collapseSpaces txt) : stripEmptyNodes nodes
stripEmptyNodes (node:nodes) = stripEmptyNodes nodes
stripEmptyNodes [] = []
collapseSpaces txt
| txt == "" = "" -- Avoids errors from head/tail tests.
| isSpace $ Txt.head txt = " " `Txt.append` collapseSpaces (Txt.stripStart txt)
| isSpace $ Txt.last txt = collapseSpaces (Txt.stripEnd txt) `Txt.append` " "
| otherwise = Txt.unwords $ Txt.words txt
renderElLBS el = XML.renderLBS XML.def $ XML.Document {
XML.documentPrologue = XML.Prologue [] Nothing [],
XML.documentRoot = stripEmptyEls el,
XML.documentEpilogue = []
}