Skip to content

Commit

Permalink
chore: Fix compiler warnings
Browse files Browse the repository at this point in the history
  • Loading branch information
k0ral committed Oct 31, 2024
1 parent 4359b19 commit f0843dc
Showing 1 changed file with 2 additions and 3 deletions.
5 changes: 2 additions & 3 deletions xml-conduit/src/Text/XML/Stream/Parse.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
-- | This module provides both a native Haskell solution for parsing XML
-- documents into a stream of events, and a set of parser combinators for
-- dealing with a stream of events.
Expand Down Expand Up @@ -148,7 +149,6 @@ import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Maybe (MaybeT (..))
import Control.Monad.Trans.Resource (MonadResource, MonadThrow (..),
throwM)
import Data.Attoparsec.Internal (concatReverse)
import Data.Attoparsec.Text (Parser, anyChar, char, manyTill,
skipWhile, string, takeWhile,
takeWhile1, (<?>),
Expand Down Expand Up @@ -1151,13 +1151,12 @@ anyOf values = matching (`elem` values)
newtype AttrParser a = AttrParser { runAttrParser :: [(Name, [Content])] -> Either SomeException ([(Name, [Content])], a) }

instance Monad AttrParser where
return a = AttrParser $ \as -> Right (as, a)
(AttrParser f) >>= g = AttrParser $ \as ->
either Left (\(as', f') -> runAttrParser (g f') as') (f as)
instance Functor AttrParser where
fmap = liftM
instance Applicative AttrParser where
pure = return
pure a = AttrParser $ \as -> Right (as, a)
(<*>) = ap
instance Alternative AttrParser where
empty = AttrParser $ const $ Left $ toException $ XmlException "AttrParser.empty" Nothing
Expand Down

0 comments on commit f0843dc

Please sign in to comment.