~alcinnz/rhapsode

ref: c900dfa44910044796d0fa99bc987d4d7c2dbd4e rhapsode/src/Main.hs -rw-r--r-- 6.8 KiB
c900dfa4 — Adrian Cochrane Add new URL & commandline arguments input interface. 4 years ago
                                                                                
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
{-# 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 Data.ByteString.Lazy as B

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, intercalate)

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.CSS.Preprocessor.Conditions as CSSCond
import qualified Data.HTML2CSS as H2C

import qualified Data.List as L
import qualified Data.Map as M
import Data.Scientific (toRealFloat)
import Data.Maybe (fromJust, fromMaybe)
import System.Directory as Dir
import Control.Monad

import DefaultCSS
import StyleTree
import SSML
import Input
import Links

main :: IO ()
main = do
    http <- HTTP.newManager TLS.tlsManagerSettings
    ProgramCtl docs outSSML <- parseArgs http
    forM docs $ \(uri, doc) -> do
        let html = XML.documentRoot doc
        style <- retreiveStyles uri doc http uri
        let transcript = stylize style html
        C8.putStrLn $ renderElLBS $ styleToSSML $ applyCounters transcript
    return ()

renderElLBS el = XML.renderLBS XML.def $ XML.Document {
        XML.documentPrologue = XML.Prologue [] Nothing [],
        XML.documentRoot = el,
        XML.documentEpilogue = []
    }

retreiveStyles uri html manager base = do
    userStyle <- loadUserStyles agentStyle
    importedStyle <- CSSCond.loadImports loadURL lowerVars lowerToks userStyle []
    return $ CSSCond.resolve lowerVars lowerToks Style.queryableStyleSheet importedStyle
  where
    agentStyle = H2C.cssPriorityAgent authorStyle `CSS.parse` Txt.pack userAgentCSS
    authorStyle :: CSSCond.ConditionalStyles StyleTree
    authorStyle = H2C.html2css html base

    loadURL url = do
        response <- fetchURL manager "text/css" url
        return $ case response of
            ("text/css", Left text) -> text
            ("text/css", Right bytes) -> applyCSScharset charsets $ B.toStrict bytes
            (_, _) -> ""

    lowerVars "speech" = CSSCond.B True
    lowerVars "-rhapsode" = CSSCond.B True
    lowerVars _ = CSSCond.B False
    lowerToks _ = CSSCond.B False

applyCSScharset (charset:charsets) bytes | cssCharset (CSSTok.tokenize text) == charset = text
        | otherwise = applyCSScharset charsets bytes
    where text = convertCharset charset bytes
cssCharset toks | (CSSTok.AtKeyword "charset":toks') <- skipCSSspace toks,
        (CSSTok.String charset:_) <- skipCSSspace toks' = charset
    | otherwise = ""
skipCSSspace (CSSTok.Whitespace:toks) = skipCSSspace toks
skipCSSspace toks = toks

loadUserStyles styles = do
    dir <- Dir.getXdgDirectory Dir.XdgConfig "rhapsode"
    exists <- Dir.doesDirectoryExist dir
    loadDirectory dir exists
  where
    loadDirectory _ False = return styles
    loadDirectory dir True = do
        files <- Dir.listDirectory dir
        loadFiles (H2C.cssPriorityUser styles) files
    loadFiles style (file:files) = do
        source <- readFile file
        CSS.parse style (Txt.pack source) `loadFiles` files
    loadFiles style [] = return style


stylize styles html = H2C.traversePrepopulatedStyles buildChild buildNode buildText styles html
    where
        buildChild (Style.VarParser _ self) _ | content self == [] = Nothing
            | otherwise = Just [Style.temp {content = content self}]
        buildNode (Style.VarParser _ self) children = self {children = children}
        buildText _ txt = Style.temp {content = [Content txt]}

--------
---- Counters
--------
treeOrder :: (c -> c -> [Integer] -> StyleTree -> (c, StyleTree)) ->
        c -> c -> [Integer] -> [StyleTree] -> (c, [StyleTree])
treeOrder cb prevContext context (num:path) (node:nodes) = (tailContext, node' {children = children'} : nodes')
    where
        (selfContext, node') = cb prevContext context (num:path) node
        (childContext, children') = treeOrder cb selfContext selfContext (0:num:path) $ children node
        (tailContext, nodes') = treeOrder cb selfContext childContext (num + 1:path) nodes
treeOrder _ _ context _ [] = (context, [])
treeOrder _ _ _ [] _ = error "Invalid path during tree traversal!"

inheritCounters path counterSource valueSource = M.intersectionWith cb valueSource counterSource -- indexed by name & el-path
    where cb val source = [counter | path `elem` [p | (p, _) <- source], counter@(path, _) <- val]
instantiateCounter counters path name val = M.insertWith appendCounter name [(path, val)] counters
    where
        appendCounter new (old@((_:oldPath), _):olds)
            | oldPath == tail path = new ++ olds
            | otherwise =  new ++ (old:olds)
instantiateCounters path instruct counters = foldl cb counters instruct
    where cb counters' (name, value) = instantiateCounter counters' path name value
incrementCounter counters path name val = M.insertWith addCounter name [(path, val)] counters
    where addCounter ((_, new):_) ((path, old):rest) = (path, new + old):rest
incrementCounters path instruct counters = foldl cb counters instruct
    where cb counters' (name, value) = incrementCounter counters' path name value
setCounter counters path name val = M.insertWith setCounter' name [(path, val)] counters
    where setCounter' ((_, val):_) ((path, _):rest) = (path, val):rest
setCounters path instruct counters = foldl cb counters instruct
    where cb counters' (name, value) = setCounter counters' path name value

renderCounter counters (Content txt) = Content txt
renderCounter counters (Counter name)
    | Just ((_, count):_) <- name `M.lookup` counters = Content $ Txt.pack $ show count
    | otherwise = Content ""
renderCounter counters (Counters name sep)
    | Just counter <- name `M.lookup` counters = Content $ Txt.intercalate sep [
            Txt.pack $ show count | (_, count) <- reverse counter
        ]
    | otherwise = Content ""
renderCounters node counters = (counters, node {
        content = map (renderCounter counters) $ content node,
        counterSet = [(name, value) | (name, ((_, value):_)) <- M.toList counters]
    })

applyCounters root = root {
        children = snd $ treeOrder cb M.empty M.empty [0] $ children root
    } where
        cb :: M.Map Text [([Integer], Integer)] -> M.Map Text [([Integer], Integer)] ->
            [Integer] -> StyleTree -> (M.Map Text [([Integer], Integer)], StyleTree)
        cb counterSource valueSource path node = renderCounters node $
            setCounters path (counterSet node) $
            incrementCounters path (counterIncrement node) $
            instantiateCounters path (counterReset node) $
            inheritCounters path counterSource valueSource