]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/Parser/Http.hs
Haddock overhaul
[Lucu.git] / Network / HTTP / Lucu / Parser / Http.hs
index 4153dcb6eaf62f071e5ba7fe3406daa9d3c4c881..e3fbf3501b1cc50800bf1af90f88b123beee0030 100644 (file)
@@ -47,7 +47,7 @@ import qualified Data.Sequence as S
 import Data.Sequence.Unicode hiding ((∅))
 import Prelude.Unicode
 
--- |@'isCtl' c@ is 'Prelude.False' iff @0x20 <= c < 0x7F@.
+-- |@'isCtl' c@ returns 'False' iff @0x20 <= c < 0x7F@.
 isCtl ∷ Char → Bool
 {-# INLINE isCtl #-}
 isCtl c
@@ -60,7 +60,7 @@ isText ∷ Char → Bool
 {-# INLINE isText #-}
 isText = (¬) ∘ isCtl
 
--- |@'isSeparator' c@ is 'Prelude.True' iff c is one of HTTP
+-- |@'isSeparator' c@ returns 'True' iff c is one of the HTTP
 -- separators.
 isSeparator ∷ Char → Bool
 {-# INLINE isSeparator #-}
@@ -69,12 +69,12 @@ isSeparator = flip FS.memberChar set
       {-# NOINLINE set #-}
       set = FS.charClass "()<>@,;:\\\"/[]?={}\x20\x09"
 
--- |@'isChar' c@ is 'Prelude.True' iff @c <= 0x7f@.
+-- |@'isChar' c@ returns 'True' iff @c <= 0x7f@.
 isChar ∷ Char → Bool
 {-# INLINE isChar #-}
 isChar = (≤ '\x7F')
 
--- |@'isToken' c@ is equivalent to @not ('isCtl' c || 'isSeparator'
+-- |@'isToken' c@ is equivalent to @not ('isCtl' c '||' 'isSeparator'
 -- c)@
 isToken ∷ Char → Bool
 {-# INLINE isToken #-}
@@ -89,7 +89,7 @@ listOf p = do skipMany lws
                            _ ← char ','
                            skipMany lws
 
--- |'token' is similar to @'takeWhile1' 'isToken'@
+-- |'token' is almost the same as @'takeWhile1' 'isToken'@
 token ∷ Parser Ascii
 {-# INLINE token #-}
 token = A.unsafeFromByteString <$> takeWhile1 isToken
@@ -118,7 +118,7 @@ isSPHT '\x20' = True
 isSPHT '\x09' = True
 isSPHT _      = False
 
--- |@'separators'@ is similar to @'takeWhile1' 'isSeparator'@.
+-- |@'separators'@ is almost the same as @'takeWhile1' 'isSeparator'@.
 separators ∷ Parser Ascii
 {-# INLINE separators #-}
 separators = A.unsafeFromByteString <$> takeWhile1 isSeparator
@@ -158,8 +158,8 @@ qvalue = do x  ← char '0'
                     return (y:ys)
             return $ read (x:xs)
 
--- |@'atMost' n v@ is like @'P.many' v@ but applies the given action
--- at most @n@ times.
+-- |@'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 0 _ = pure []
@@ -167,7 +167,6 @@ atMost n v = ( (:) <$> v ⊛ atMost (n-1) v )
              <|>
              pure []
 
-
 data CharAccumState
     = CharAccumState {
         casChunks    ∷ !(S.Seq BS.ByteString)
@@ -210,6 +209,8 @@ finish cas
       in
         str
 
+-- |@'manyCharsTill' p end@ takes as many characters untill @p@
+-- succeeds.
 manyCharsTill ∷ ∀m b. (Monad m, Alternative m)
               ⇒ m Char
               → m b