]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/Parser.hs
Better name-rewriting engine
[Lucu.git] / Network / HTTP / Lucu / Parser.hs
index ce4371878890301eb152d3b9ef55c526c4127174..db83b9c20107818236b1292969ad17e9d7c3e231 100644 (file)
@@ -1,20 +1,56 @@
 {-# LANGUAGE
     UnicodeSyntax
   #-}
--- |This is an auxiliary parser utilities. You usually don't have to
--- use this module directly.
+-- |A set of auxiliary parser utilities.
 module Network.HTTP.Lucu.Parser
     ( atMost
+    , finishOff
+    , skipManyTill
+    , skipWhile1
+    , skipSpace1
+    , isAlphaNum
     )
     where
 import Control.Applicative
 import Control.Applicative.Unicode
+import Control.Monad.Unicode
+import Data.Attoparsec.Char8
+import Prelude.Unicode
 
 -- |@'atMost' n v@ is like @'P.many' v@ but accumulates @v@ at most
 -- @n@ times.
-atMost ∷ Alternative f ⇒ Int → f a → f [a]
-{-# INLINE atMost #-}
+atMost ∷ Alternative f ⇒ Int → f α → f [α]
+{-# INLINEABLE atMost #-}
 atMost 0 _ = pure []
 atMost n v = ( (:) <$> v ⊛ atMost (n-1) v )
              <|>
              pure []
+
+-- |@'finishOff' p@ is equivalent to @p '>>=' \\a -> 'endOfInput' '>>'
+-- 'return' a@.
+finishOff ∷ Parser α → Parser α
+{-# INLINE finishOff #-}
+finishOff = ((endOfInput *>) ∘ return =≪)
+
+-- |Similar to 'manyTill' but discards the result.
+skipManyTill ∷ Alternative f ⇒ f α → f β → f ()
+{-# INLINEABLE skipManyTill #-}
+skipManyTill p end = go
+    where
+      go = (end *> pure ()) <|> (p *> go)
+
+-- |Similar to 'skipWhile' but consumes at least one character.
+skipWhile1 ∷ (Char → Bool) → Parser ()
+{-# INLINE skipWhile1 #-}
+skipWhile1 p = takeWhile1 p *> pure ()
+
+-- |Similar to 'skipSpace' but consumes at least one whitespace.
+skipSpace1 ∷ Parser ()
+{-# INLINE skipSpace1 #-}
+skipSpace1 = skipMany1 space
+
+-- |@'isAlphaNum' c@ returns 'True' iff @'isDigit' c ||
+-- 'isAlpha_ascii' c@.
+isAlphaNum ∷ Char → Bool
+{-# INLINE isAlphaNum #-}
+isAlphaNum c = isDigit c ∨ isAlpha_ascii c