]> gitweb @ CieloNegro.org - Rakka.git/blobdiff - Rakka/Utils.hs
Resurrection from bitrot
[Rakka.git] / Rakka / Utils.hs
index cb77474553c42fee4f6cdcaf340a32a8db4e38a9..3148c6bf108906112b39ebb81f63132ae8baa158 100644 (file)
@@ -1,22 +1,49 @@
+{-# LANGUAGE
+    Arrows
+  , OverloadedStrings
+  , TypeOperators
+  , UnicodeSyntax
+  #-}
 module Rakka.Utils
-    ( parseYesOrNo
+    ( yesOrNo
+    , trueOrFalse
+    , parseYesOrNo
     , maybeA
-    , defaultTo
     , deleteIfEmpty
+    , chomp
+    , guessMIMEType
+    , isSafeChar
+    , mkQueryString
     )
     where
-
+import qualified Codec.Binary.UTF8.String as UTF8
 import           Control.Arrow
 import           Control.Arrow.ArrowList
+import qualified Data.ByteString.Lazy as Lazy (ByteString)
+import qualified Data.ByteString.Lazy.Char8 as L8 hiding (ByteString)
+import Data.Monoid.Unicode
+import Data.String
+import           Magic
+import           Network.HTTP.Lucu
+import           Network.URI
+import Prelude.Unicode
+import           System.IO.Unsafe
 
+yesOrNo ∷ Bool → String
+yesOrNo True  = "yes"
+yesOrNo False = "no"
 
-parseYesOrNo :: ArrowChoice a => a String Bool
-parseYesOrNo 
-    = proc str -> do case str of
-                       "yes" -> returnA -< True
-                       "no"  -> returnA -< False
-                       _     -> returnA -< error ("Expected yes or no: " ++ str)
+trueOrFalse ∷ Bool → String
+trueOrFalse True  = "true"
+trueOrFalse False = "false"
 
+parseYesOrNo ∷ (Eq s, Show s, IsString s, ArrowChoice (⇝)) ⇒ s ⇝ Bool
+parseYesOrNo
+    = proc str →
+      case str of
+        _ | str ≡ "yes" → returnA ⤙ True
+          | str ≡ "no"  → returnA ⤙ False
+          | otherwise   → returnA ⤙ error ("Expected yes or no: " ⊕ show str)
 
 maybeA :: (ArrowList a, ArrowChoice a) => a b c -> a b (Maybe c)
 maybeA a = listA a
@@ -26,15 +53,42 @@ maybeA a = listA a
                         (x:_) -> returnA -< Just x
 
 
-defaultTo :: ArrowChoice a => b -> a (Maybe b) b
-defaultTo def
-    = proc m -> case m of
-                  Nothing -> returnA -< def
-                  Just x  -> returnA -< x
-
-
 deleteIfEmpty :: (ArrowList a, ArrowChoice a) => a String String
 deleteIfEmpty
     = proc str -> do case str of
                        "" -> none    -< ()
-                       _  -> returnA -< str
\ No newline at end of file
+                       _  -> returnA -< str
+
+
+chomp :: String -> String
+chomp = reverse . snd . break (/= '\n') . reverse
+
+
+guessMIMEType :: Lazy.ByteString -> MIMEType
+guessMIMEType = read . unsafePerformIO . magicString magic . L8.unpack
+    where
+      magic :: Magic
+      magic = unsafePerformIO
+              $ do m <- magicOpen [MagicMime]
+                   magicLoadDefault m
+                   return m
+
+
+isSafeChar :: Char -> Bool
+isSafeChar c
+    | c == '/'            = True
+    | isReserved c        = False
+    | c > ' ' && c <= '~' = True
+    | otherwise           = False
+
+
+mkQueryString :: [(String, String)] -> String
+mkQueryString []            = ""
+mkQueryString ((k, v) : xs) = encode k ++ "=" ++ encode v ++
+                              if xs == [] then
+                                  ""
+                              else
+                                  ';' : mkQueryString(xs)
+    where
+      encode :: String -> String
+      encode = escapeURIString isSafeChar . UTF8.encodeString
\ No newline at end of file