]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/Parser/Http.hs
Removed unnecessary 'try'
[Lucu.git] / Network / HTTP / Lucu / Parser / Http.hs
index 4ac11a4686624c3d66da14d4a034d29116b85640..520034247726f3ec6398eb8b69b143eb08456ceb 100644 (file)
@@ -41,7 +41,7 @@ import qualified Data.Attoparsec.FastSet as FS
 import qualified Data.ByteString.Char8 as BS
 import qualified Data.ByteString.Lazy.Char8 as LS
 import qualified Data.ByteString.Lazy.Internal as LS
-import qualified Data.Foldable as F
+import Data.Foldable
 import Data.Monoid
 import Data.Monoid.Unicode
 import qualified Data.Sequence as S
@@ -87,8 +87,7 @@ isToken !c
 listOf ∷ Parser a → Parser [a]
 {-# INLINEABLE listOf #-}
 listOf p
-    = try $
-      do skipMany lws
+    = do skipMany lws
          sepBy p $ do skipMany lws
                       _ <- char ','
                       skipMany lws
@@ -111,10 +110,9 @@ sp = char '\x20' ≫ return ()
 -- |HTTP LWS: crlf? (sp | ht)+
 lws ∷ Parser ()
 {-# INLINEABLE lws #-}
-lws = try $
-      do option () crlf
-         _ ← satisfy isSPHT
-         skipWhile isSPHT
+lws = do option () crlf
+         _ ← takeWhile1 isSPHT
+         return ()
 
 -- |Returns 'True' for SP and HT.
 isSPHT ∷ Char → Bool
@@ -192,7 +190,7 @@ instance Monoid CharAccumState where
 
 lastChunk ∷ CharAccumState → BS.ByteString
 {-# INLINE lastChunk #-}
-lastChunk = BS.pack ∘ F.toList ∘ casLastChunk
+lastChunk = BS.pack ∘ toList ∘ casLastChunk
 
 snoc ∷ CharAccumState → Char → CharAccumState
 {-# INLINEABLE snoc #-}
@@ -210,7 +208,7 @@ snoc cas c
 finish ∷ CharAccumState → LS.ByteString
 {-# INLINEABLE finish #-}
 finish cas
-    = let chunks = F.toList $ casChunks cas ⊳ lastChunk cas
+    = let chunks = toList $ casChunks cas ⊳ lastChunk cas
           str    = LS.fromChunks chunks
       in
         str