Last active
February 8, 2018 16:01
-
-
Save soareschen/e2abe00b8795b09ade405bd2ce161420 to your computer and use it in GitHub Desktop.
Row Polymorphic-like composition in Haskell
This file contains hidden or 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 RankNTypes #-} | |
{-# LANGUAGE ExplicitForAll #-} | |
{-# LANGUAGE KindSignatures #-} | |
{-# LANGUAGE ConstraintKinds #-} | |
{-# LANGUAGE TypeApplications #-} | |
{-# LANGUAGE ScopedTypeVariables #-} | |
{-# LANGUAGE AllowAmbiguousTypes #-} | |
import GHC.Exts | |
-- This code snippet demonstrates how we can compose | |
-- two functions with row-polymorphic-like arguments. | |
-- i.e. to implement the type: | |
-- forall | |
-- (p :: * -> Constraint) | |
-- (q :: * -> Constraint) | |
-- (c :: *). | |
-- (p c => c -> String) -> | |
-- (q c => c -> String) -> | |
-- ((p c, q c) => c -> String) | |
type Handler p c = (p c => c -> String) | |
type Union (p :: * -> Constraint) (q :: * -> Constraint) (c :: *) = (p c, q c) | |
-- Following the Has type class pattern, | |
-- we define 2 "row" types that represent | |
-- configuration fields we need in our functions. | |
class HasFoo a where | |
getFoo :: a -> String | |
class HasBar a where | |
getBar :: a -> String | |
-- fooHandler is a handler function that process | |
-- any object with a foo field. | |
-- In a row polymorphic type systems like PureScript, | |
-- this is akin to | |
-- fooHandler :: { foo :: String | r } -> String | |
fooHandler :: Handler HasFoo c | |
fooHandler c = "(foo-result " ++ (getFoo c) ++ ")" | |
-- barHandler is a handler function that process | |
-- any object with a bar field. | |
barHandler :: Handler HasBar c | |
barHandler c = "(bar-result " ++ (getBar c) ++ ")" | |
-- We define a type synonym to define the type | |
-- signature of our composeHandlers function | |
type ComposeType | |
(p :: * -> Constraint) | |
(q :: * -> Constraint) | |
(c :: *) = | |
(Handler p c) -> | |
(Handler q c) -> | |
(Handler (Union p q) c) | |
-- Compose 2 arbitrary functions with arbitrary | |
-- constraints together. The resulting composed | |
-- handler function has a combined constraint. | |
composeHandlers :: ComposeType p q c | |
composeHandlers f g c = "(compose-result " ++ (f c) ++ " " ++ (g c) ++ ")" | |
-- In a row polymorphic type systems like PureScript, | |
-- this is conceptually something like | |
-- composeHandlers :: | |
-- ({| p} -> String) -> ({| q} -> String) -> | |
-- ({| p, q} -> String) | |
-- However we can't simply combine two row variables | |
-- at least in PureScript. | |
-- In the simplest case we have a simple record | |
-- type that has foo and bar fields. Note here | |
-- that they don't need to have the same field | |
-- labels. | |
data Config = Config { fooField :: String, barField :: String } | |
-- Manually instantiate the record type to satisfy | |
-- our row constraints. Perhaps there are packages | |
-- that use template Haskell to help us do auto | |
-- instantiation. | |
instance HasFoo Config where | |
getFoo = fooField | |
instance HasBar Config where | |
getBar = barField | |
-- bazHandler is made by composing fooHandler and barHandler. | |
-- We are able to use the generic composeHandlers function | |
-- with the help of explicit type application. | |
-- bazHandler :: Handler (Union HasFoo HasBar) c | |
bazHandler c = composeHandlers @HasFoo @HasBar fooHandler barHandler c | |
-- Note: The c parameter has to be passed here as otherwise | |
-- Haskell would fail with ambiguous type error unless explicit | |
-- type signature is given. | |
-- bazHandler is also generic, and we can freely pass | |
-- our Config record in because it satisfy all constraints. | |
result = bazHandler $ Config "fooValue" "barValue" | |
main = putStrLn result |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment