@@ 1,7 1,6 @@
{-# LANGUAGE OverloadedStrings #-}
-- | Bindings from `xml-conduit` to `haskell-stylist`.
module Data.HTML2CSS(
- externalStyles, externalStylesForURL, internalStyles, internalStylesForURL, -- legacy
html2css, cssPriorityAgent, cssPriorityUser, cssPriorityAuthor, -- parsing
traverseStyles, traversePrepopulatedStyles, traverseStyles', elToStylish -- application
) where
@@ 53,42 52,6 @@ parseMediaQuery attrs
| Just text <- "media" `M.lookup` attrs = Query.parse' (tokenize text) []
| otherwise = []
----- Parsing (legacy)
--- | LEGACY: Extract relative links to external stylesheets.
-externalStyles :: StyleSheet s => s -> (M.Map XML.Name Txt.Text -> Bool) ->
- XML.Element -> (URI -> IO Txt.Text) -> IO s
-externalStyles a b c d = externalStylesForURL a b c nullURI d
--- | LEGACY: Extract absolutized links to external stylesheets.
-externalStylesForURL stylesheet testMedia html base loadURL = do
- css <- externalStyles' testMedia html base loadURL
- return $ foldl (\a (b, c) -> parseForURL a b c) (cssPriorityAuthor stylesheet) css
-externalStyles' testMedia html base loadURL = go $ linkedStyles' testMedia html
- where -- TODO parallelise loads
- go (link:links) = do
- response <- loadURL $ relativeTo link base
- rest <- go links
- return $ (relativeTo link base, response) : rest
- go [] = return []
-
-linkedStyles' testMedia (XML.Element (XML.Name "link" _ _) attrs _)
- | Just link <- "href" `M.lookup` attrs,
- Just "stylesheet" <- "rel" `M.lookup` attrs,
- testMedia attrs,
- Just uri <- parseURIReference $ Txt.unpack link = [uri]
-linkedStyles' testMedia (XML.Element _ _ children) =
- concat [linkedStyles' testMedia el | XML.NodeElement el <- children]
-
--- | LEGACY: Extract internally embedded CSS stylesheets.
-internalStyles a b c = internalStylesForURL a b nullURI c
--- | LEGACY: Extract internally embedded CSS stylesheets, with absolutized URLs.
-internalStylesForURL testMedia stylesheet base html =
- foldl (\s -> parseForURL s base) (cssPriorityAuthor stylesheet) $
- internalStyles' testMedia html
-internalStyles' testMedia (XML.Element (XML.Name "style"_ _) attrs children)
- | testMedia attrs = [strContent children]
-internalStyles' testMedia (XML.Element _ _ children) =
- concat [internalStyles' testMedia el | XML.NodeElement el <- children]
-
strContent :: [XML.Node] -> Txt.Text
strContent (XML.NodeContent text : rest) = text `Txt.append` strContent rest