]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/Parser.hs
haddock comments
[Lucu.git] / Network / HTTP / Lucu / Parser.hs
index 87722647018232d0379aa309d08c265610f06313..ac1bf02734f0a09485eddf924002f8d4fc27b88e 100644 (file)
@@ -1,22 +1,30 @@
 {-# LANGUAGE
-    BangPatterns
-  , ScopedTypeVariables
-  , UnicodeSyntax
+    UnicodeSyntax
   #-}
 -- |This is an auxiliary parser utilities. You usually don't have to
 -- use this module directly.
 module Network.HTTP.Lucu.Parser
     ( atMost
+    , finishOff
     )
     where
 import Control.Applicative
 import Control.Applicative.Unicode
+import Control.Monad.Unicode
+import Data.Attoparsec
+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]
+atMost ∷ Alternative f ⇒ Int → f α → f [α]
 {-# INLINE 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 =≪)