]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/Resource/Dispatcher.hs
Unfoldable Dispatcher
[Lucu.git] / Network / HTTP / Lucu / Resource / Dispatcher.hs
index ffaba2d1ec114e49a3a22eb900a1bc81d286055e..029d7b2de6294fb0bc970ae7b951d51932049a3f 100644 (file)
@@ -1,28 +1,32 @@
 {-# LANGUAGE
     ExistentialQuantification
   , FlexibleInstances
+  , MultiParamTypeClasses
+  , UndecidableInstances
   , UnicodeSyntax
   #-}
 -- |FIXME: doc
 module Network.HTTP.Lucu.Resource.Dispatcher
     ( Dispatchable(..)
     , Dispatcher
+    , uriHost
+    , uriPathSegments
     )
     where
-import Control.Applicative
-import Data.ByteString (ByteString)
 import Data.CaseInsensitive (CI)
+import Data.Collections
 import Data.Monoid
 import Data.Text (Text)
 import Network.HTTP.Lucu.Resource.Internal
+import Network.HTTP.Lucu.Utils
+import Network.URI
 import Prelude.Unicode
 
 -- |FIXME: docs
+--
+-- Minimal complete definition: 'dispatch'
 class Dispatchable α where
-    dispatch ∷ α
-             → CI Text
-             → [ByteString]
-             → IO (Maybe ([ByteString], Resource))
+    dispatch ∷ α → URI → IO (Maybe Resource)
 
     dispatcher ∷ α → Dispatcher
     {-# INLINE dispatcher #-}
@@ -35,47 +39,45 @@ instance Dispatchable Dispatcher where
     dispatch (Dispatcher α) = dispatch α
     dispatcher = id
 
--- |@a `'mappend'` b@ first tries to find a resource with @a@, and if
--- it returns 'Nothing', tries @b@ next.
-instance Monoid Dispatcher where
-    {-# INLINE mempty #-}
-    mempty = dispatcher ()
-
-    {-# INLINEABLE mappend #-}
-    mappend (Dispatcher α) (Dispatcher β)
+-- |@insert a b@ first tries @a@, and then tries @b@. @insertMany bs
+-- a@ first tries @a@, and then tries each one in @bs@ from head to
+-- tail.
+instance Dispatchable α ⇒ Unfoldable Dispatcher α where
+    {-# INLINEABLE insert #-}
+    insert a (Dispatcher b)
         = dispatcher
-          $ \host path → do r ← dispatch α host path
-                            case r of
-                              Just _  → return r
-                              Nothing → dispatch β host path
+          $ \uri → do r ← dispatch a uri
+                      case r of
+                        Just _  → return r
+                        Nothing → dispatch b uri
+    {-# INLINE empty #-}
+    empty = dispatcher e
+        where
+          e ∷ URI → IO (Maybe Resource)
+          {-# INLINE e #-}
+          e = return ∘ const Nothing
+    {-# INLINE singleton #-}
+    singleton = dispatcher
 
--- |An IO-based dispatcher returning resource paths as well as
--- 'Resource's.
-instance Dispatchable (CI Text
-                       → [ByteString]
-                       → IO (Maybe ([ByteString], Resource))) where
-    dispatch = id
+-- |@a `'mappend'` b@ first tries @a@, and then tries @b@.
+instance Monoid Dispatcher where
+    {-# INLINE mempty #-}
+    mempty = empty
+    {-# INLINE mappend #-}
+    mappend = insert
 
 -- |An IO-based dispatcher.
-instance Dispatchable (CI Text → [ByteString] → IO (Maybe Resource)) where
-    dispatch = ((((<$>) ∘ (<$>)) ((,) []) ∘) ∘)
+instance Dispatchable (URI → IO (Maybe Resource)) where
+    dispatch = id
 
 -- |A pure dispatcher.
-instance Dispatchable (CI Text → [ByteString] → Maybe Resource) where
-    dispatch = (((return ∘ ((,) [] <$>)) ∘) ∘)
-
--- |An IO-based dispatcher ignoring host names.
-instance Dispatchable ([ByteString] → IO (Maybe Resource)) where
-    dispatch = const ∘ (((<$>) ∘ (<$>)) ((,) []) ∘)
-
--- |A pure dispatcher ignoring host names.
-instance Dispatchable ([ByteString] → Maybe Resource) where
-    dispatch = const ∘ ((return ∘ ((,) [] <$>)) ∘)
+instance Dispatchable (URI → Maybe Resource) where
+    dispatch = (return ∘)
 
 -- |The constant dispatcher returning always the same 'Resource'.
 instance Dispatchable Resource where
-    dispatch = const ∘ const ∘ return ∘ Just ∘ (,) []
+    dispatch = const ∘ return ∘ Just
 
--- |The empty dispatcher returning always 'Nothing'.
-instance Dispatchable () where
-    dispatch _ _ _ = return Nothing
+-- |FIXME: doc
+uriHost ∷ URI → CI Text
+uriHost = error "FIXME"