]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/MIMEParams.hs
Code clean-up using convertible-text.
[Lucu.git] / Network / HTTP / Lucu / MIMEParams.hs
index a2b93412a7eecb6d9be0eb5ccd77b7e13e02507a..6f9eb7e1b8a9f4055b0bc878578d6b2679952991 100644 (file)
@@ -62,7 +62,7 @@ instance ConvertSuccess MIMEParams Ascii where
     convertSuccess = convertSuccessVia ((⊥) ∷ AsciiBuilder)
 
 instance ConvertSuccess MIMEParams AsciiBuilder where
-    {-# INLINE convertSuccess #-}
+    {-# INLINEABLE convertSuccess #-}
     convertSuccess = foldl' f (∅)
         where
           f ∷ AsciiBuilder → (CIAscii, Text) → AsciiBuilder
@@ -119,6 +119,10 @@ toHex o = cs ("%" ∷ Ascii) ⊕
           | otherwise = toEnum $ fromIntegral
                                $ fromEnum 'A' + fromIntegral (h - 0x0A)
 
+deriveAttempts [ ([t| MIMEParams |], [t| Ascii        |])
+               , ([t| MIMEParams |], [t| AsciiBuilder |])
+               ]
+
 data ExtendedParam
     = InitialEncodedParam {
         epName    ∷ !CIAscii
@@ -164,7 +168,7 @@ paramP = do skipMany lws
                        return $ AsciiParam name sect payload
 
 nameP ∷ Parser (CIAscii, Integer, Bool)
-nameP = do name      ← (A.toCIAscii ∘ A.unsafeFromByteString) <$>
+nameP = do name      ← (cs ∘ A.unsafeFromByteString) <$>
                        takeWhile1 (\c → isToken c ∧ c ≢ '*')
            sect      ← option 0     $ try (char '*' *> decimal  )
            isEncoded ← option False $ try (char '*' *> pure True)
@@ -186,7 +190,7 @@ initialEncodedValue
              return (charset, payload)
     where
       metadata ∷ Parser CIAscii
-      metadata = (A.toCIAscii ∘ A.unsafeFromByteString) <$>
+      metadata = (cs ∘ A.unsafeFromByteString) <$>
                  takeWhile (\c → c ≢ '\'' ∧ isToken c)
 
 encodedPayload ∷ Parser BS.ByteString
@@ -253,7 +257,7 @@ sortBySection = flip go (∅)
                            → fail (concat [ "Duplicate section "
                                           , show $ section x
                                           , " for parameter '"
-                                          , A.toString $ A.fromCIAscii $ epName x
+                                          , cs $ epName x
                                           , "'"
                                           ])
 
@@ -276,7 +280,7 @@ decodeSections = (decodeSeq =≪) ∘ flip (flip toSeq 0) (∅)
                         → fail (concat [ "Missing section "
                                        , show $ section p
                                        , " for parameter '"
-                                       , A.toString $ A.fromCIAscii $ epName p
+                                       , cs $ epName p
                                        , "'"
                                        ])
 
@@ -292,9 +296,7 @@ decodeSections = (decodeSeq =≪) ∘ flip (flip toSeq 0) (∅)
               Just (ContinuedEncodedParam {..}, _)
                   → fail "decodeSeq: internal error: CEP at section 0"
               Just (AsciiParam {..}, xs)
-                  → let t = A.toText apPayload
-                    in
-                      decodeSeq' Nothing xs $ singleton t
+                  → decodeSeq' Nothing xs $ singleton $ cs apPayload
 
       decodeSeq' ∷ Monad m
                  ⇒ Maybe Decoder
@@ -316,13 +318,11 @@ decodeSections = (decodeSeq =≪) ∘ flip (flip toSeq 0) (∅)
                            → fail (concat [ "Section "
                                           , show epSection
                                           , " for parameter '"
-                                          , A.toString $ A.fromCIAscii epName
+                                          , cs epName
                                           , "' is encoded but its first section is not"
                                           ])
               Just (AsciiParam {..}, xs)
-                  → let t = A.toText apPayload
-                    in
-                      decodeSeq' decoder xs $ chunks ⊳ t
+                  → decodeSeq' decoder xs $ chunks ⊳ cs apPayload
 
 type Decoder = BS.ByteString → Either UnicodeException Text
 
@@ -336,5 +336,4 @@ getDecoder ∷ Monad m ⇒ CIAscii → m Decoder
 getDecoder charset
     | charset ≡ "UTF-8"    = return decodeUtf8'
     | charset ≡ "US-ASCII" = return decodeUtf8'
-    | otherwise            = fail $ "No decoders found for charset: "
-                                  ⧺ A.toString (A.fromCIAscii charset)
+    | otherwise            = fail $ "No decoders found for charset: " ⊕ cs charset