Remove most warnings.

More stuff from 7.10.
This commit is contained in:
joneshf 2015-05-06 19:28:35 -07:00
parent 367c3d33bb
commit 1211d4599c
5 changed files with 33 additions and 37 deletions

View File

@ -11,7 +11,6 @@
module Text.Taggy.Combinators (hasName, hasAttr, getAttr, innerText, (//), (/&), (/*), trees, subtrees) where
import Prelude hiding (lookup)
import Data.Monoid (mconcat)
import Control.Monad (ap, (<=<))
import Data.Text (Text)
import Text.Taggy.DOM (Element(..), Node(..), AttrName, AttrValue)
@ -47,7 +46,7 @@ innerText = mconcat . map getContent . eltChildren
(//) = flip filter . trees
-- | Given a sequence of predicates, filter an element
-- and its children, selecting only those subtrees who
-- and its children, selecting only those subtrees who
-- match the provided predicate for each point.
--
-- >>> let element = (\(NodeElement e) -> e) . head . domify . taggyWith False $ "<html>foo<bar class=\"el\">baz</bar><qux class=\"el\"><quux></quux></qux></html>"
@ -60,8 +59,8 @@ innerText = mconcat . map getContent . eltChildren
(/&) element [] = [element]
(/&) element (x:xs) = (/& xs) <=< filter x . catElements $ eltChildren element
-- | Filter from all subtrees (including the one
-- with the target as its root), those matching the
-- | Filter from all subtrees (including the one
-- with the target as its root), those matching the
-- given sequence of predicates.
(/*) :: Element -> [(Element -> Bool)] -> [Element]

View File

@ -5,12 +5,11 @@
-- License : BSD3
-- Maintainer : alpmestan@gmail.com
-- Stability : experimental
--
--
-- Render a DOM tree (from "Text.Taggy.DOM")
-- using the excellent blaze markup rendering library.
module Text.Taggy.Renderer where
import Data.Foldable (Foldable(foldMap))
import Data.HashMap.Strict (HashMap, foldlWithKey')
import Data.Monoid ((<>))
import Data.Text (Text, unpack)
@ -23,7 +22,7 @@ import Text.Blaze.Internal (ChoiceString(..), StaticString(..), MarkupM(..))
-- renderMarkup does entity conversion implicitly, and an override at the
-- constructor level is needed to control this; `PreEscaped (Text s)` is not
-- escaped, but a naked `Text s` is.
-- escaped, but a naked `Text s` is.
class AsMarkup a where
-- | If the first parameter is true, we align the constructors for entity

View File

@ -5,34 +5,34 @@
-- License : BSD3
-- Maintainer : alpmestan@gmail.com
-- Stability : experimental
--
--
-- Core types of /taggy/.
module Text.Taggy.Types
( -- * 'Tag' type
Tag(..)
, tname
, isTagOpen
, isTagClose
, isTagText
, isTagComment
, isTagScript
, isTagStyle
, tagsNamed
( -- * 'Tag' type
Tag(..)
, tname
, isTagOpen
, isTagClose
, isTagText
, isTagComment
, isTagScript
, isTagStyle
, tagsNamed
, -- * 'Attribute's
Attribute(..)
, attrs
, attrKey
, attrValue
, attrs
, attrKey
, attrValue
, -- * A small difference list implementation
L
, emptyL
, appL
, insertL
, singletonL
, toListL
) where
, -- * A small difference list implementation
L
, emptyL
, appL
, insertL
, singletonL
, toListL
) where
import Data.Text (Text, toCaseFold)
@ -119,7 +119,7 @@ isTagStyle _ = False
-- | Get all the (opening) tags with the given name
tagsNamed :: Text -> [Tag] -> [Tag]
tagsNamed nam = filter (named nam)
where named n (TagOpen t _ _) = toCaseFold n == toCaseFold t
named _ _ = False

View File

@ -3,7 +3,6 @@
module Main (main) where
import Prelude hiding (readFile)
import Data.Functor ((<$>))
import Data.List (isSuffixOf)
import Data.Text.Lazy (Text)
import Data.Text.Lazy.IO (readFile)
@ -13,9 +12,9 @@ import Test.Hspec (hspec, runIO, describe, it, shouldSatisfy)
import Text.Taggy (taggyWith)
getHTMLFiles :: IO [(FilePath, Text)]
getHTMLFiles = getDataFileName "html_files"
>>= setCurrentDirectory
>> filter (isSuffixOf ".html") <$> getDirectoryContents "."
getHTMLFiles = getDataFileName "html_files"
>>= setCurrentDirectory
>> filter (isSuffixOf ".html") <$> getDirectoryContents "."
>>= mapM (\name -> fmap (name,) $ readFile name)
main :: IO ()

View File

@ -2,7 +2,6 @@
module Text.Taggy.CombinatorsSpec where
import Data.Monoid
import Text.Taggy.Combinators
import Test.Hspec
import Text.Taggy
@ -21,10 +20,10 @@ spec = do
describe "getAttr" $ do
it "Retrieves present attributes." $
(element `getAttr` "xmlns") `shouldBe` Just "http://www.w3.org/1999/xhtml"
it "Nothing's missing attributes." $
it "Nothing's missing attributes." $
(element `getAttr` "style") `shouldBe` Nothing
describe "innerText" $ do
it "Should concatenate the NodeContent of the target element and all its children." $
it "Should concatenate the NodeContent of the target element and all its children." $
innerText element `shouldBe` "foobaz"
describe "(//)" $ do
it "Should return all children satisfying the predicate." $ do