Created
November 1, 2015 20:30
-
-
Save kosmikus/03b6ec4a66bceb49b85d to your computer and use it in GitHub Desktop.
Implementation of a small Servant-like DSL
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE DataKinds, PolyKinds, TypeOperators #-} | |
{-# LANGUAGE TypeFamilies, FlexibleInstances, ScopedTypeVariables #-} | |
{-# LANGUAGE InstanceSigs #-} | |
module TinyServant where | |
import Control.Applicative | |
import GHC.TypeLits | |
import Text.Read | |
import Data.Time | |
-- API specification DSL | |
data Get (a :: *) | |
data a :<|> b = a :<|> b | |
infixr 8 :<|> | |
data (a :: k) :> (b :: *) | |
infixr 9 :> | |
data Capture (a :: *) | |
-- Example API | |
type MyAPI = "date" :> Get Day | |
:<|> "time" :> Capture TimeZone :> Get ZonedTime | |
data Proxy a = Proxy | |
-- The Server type family | |
type family Server layout :: * | |
type instance Server (Get a) = IO a | |
type instance Server (a :<|> b) = Server a :<|> Server b | |
type instance Server ((s :: Symbol) :> r) = Server r | |
type instance Server (Capture a :> r) = a -> Server r | |
-- Handler for the example API | |
handleDate :: IO Day | |
handleDate = utctDay <$> getCurrentTime | |
handleTime :: TimeZone -> IO ZonedTime | |
handleTime tz = utcToZonedTime tz <$> getCurrentTime | |
handleMyAPI :: Server MyAPI | |
handleMyAPI = handleDate :<|> handleTime | |
-- The HasServer class | |
class HasServer layout where | |
route :: Proxy layout -> Server layout -> [String] -> Maybe (IO String) | |
serve :: HasServer layout | |
=> Proxy layout -> Server layout -> [String] -> IO String | |
serve p h xs = case route p h xs of | |
Nothing -> ioError (userError "404") | |
Just m -> m | |
-- The HasServer instance | |
type instance Server (Get a) = IO a | |
instance Show a => HasServer (Get a) where | |
route :: Proxy (Get a) -> IO a -> [String] -> Maybe (IO String) | |
route _ handler [] = Just (show <$> handler) | |
route _ _ _ = Nothing | |
instance (HasServer a, HasServer b) => HasServer (a :<|> b) where | |
route :: Proxy (a :<|> b) -> (Server a :<|> Server b) -> [String] -> Maybe (IO String) | |
route _ (handlera :<|> handlerb) xs = | |
route (Proxy :: Proxy a) handlera xs | |
<|> route (Proxy :: Proxy b) handlerb xs | |
instance (KnownSymbol s, HasServer r) => HasServer ((s :: Symbol) :> r) where | |
route :: Proxy (s :> r) -> Server r -> [String] -> Maybe (IO String) | |
route _ handler (x : xs) | |
| symbolVal (Proxy :: Proxy s) == x = route (Proxy :: Proxy r) handler xs | |
route _ _ _ = Nothing | |
instance (Read a, HasServer r) => HasServer (Capture a :> r) where | |
route :: Proxy (Capture a :> r) -> (a -> Server r) -> [String] -> Maybe (IO String) | |
route _ handler (x : xs) = do | |
a <- readMaybe x | |
route (Proxy :: Proxy r) (handler a) xs | |
route _ _ _ = Nothing |
@michaelt: It's not a GHC bug, just surprising behavior that might deserve a warning: https://gitlab.haskell.org/ghc/ghc/issues/14440
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment
Is it a ghc bug that the compiler accepts that line 31
is repeated on line 57?