Last active
June 19, 2019 22:18
-
-
Save ramirez7/be39df7d32ac4f413b7c4152fb1934b2 to your computer and use it in GitHub Desktop.
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 PolyKinds #-} | |
{-# LANGUAGE DataKinds #-} | |
{-# LANGUAGE GADTs #-} | |
{-# LANGUAGE RankNTypes #-} | |
{-# LANGUAGE UnsaturatedTypeFamilies #-} | |
{-# LANGUAGE TypeOperators #-} | |
module Main where | |
import Data.Kind | |
{- | |
$ ./_build/stage1/bin/ghc -o unsaturated-poly ../PolyUnsaturatedMultiConstraint.hs | |
$ ./unsaturated-poly | |
I can show it: [False,True,False] | |
I can eq it: True | |
I can only show it: [False,True,True,True] | |
-} | |
main :: IO () | |
main = do | |
useShowEq (Box [False, True, False]) | |
simpleBox (Box [False, True, True, True]) | |
-- It's matchability-polymorphic | |
data Box (c :: Type ->{m} Constraint) where | |
Box :: forall m (c :: Type ->{m} Constraint) x. c x => x -> Box c | |
type family MultiConstraint (xs :: [Type -> Constraint]) a :: Constraint where | |
MultiConstraint '[] a = () | |
MultiConstraint (x ': xs) a = (x a, MultiConstraint xs a) | |
useShowEq :: Box (MultiConstraint '[Show, Eq]) -> IO () | |
useShowEq box = case box of | |
Box x -> do | |
putStrLn $ "I can show it: " ++ show x | |
putStrLn $ "I can eq it: " ++ show (x == x) | |
simpleBox :: Box Show -> IO () | |
simpleBox box = case box of | |
Box x -> do | |
putStrLn $ "I can only show it: " ++ show x |
As I did this, I figured out that you can get this nice Box interface w/type families alone without -XUnsaturatedTypeFamilies
too:
https://gist.github.com/ramirez7/bcca51360df273e4a7a5a682e28fd7fa
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment
Without the matchability polymorphism (i.e. using a
~>
instead), we get this type error:With just
-XTypeFamilies
we get this type error: