Skip to content

Instantly share code, notes, and snippets.

@glguy
Last active November 18, 2020 23:48
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save glguy/98331ca1c3876a188e5380b9d0da5751 to your computer and use it in GitHub Desktop.
Save glguy/98331ca1c3876a188e5380b9d0da5751 to your computer and use it in GitHub Desktop.
{-# Language TypeOperators, GADTs, TypeInType, TypeFamilies #-}
module Help where
import Data.Kind
-- Suppose we have some type families
type family Two t where Two x = '(x,x)
type family Swap t where Swap '(x,y) = '(y,x)
-- And we want a reusable Map function on types
type family Map (f :: fK dom rng) (xs :: [dom]) :: [rng] where
Map f '[] = '[]
Map f (x ': xs) = f $ x ': Map f xs
-- We can defunctionalize our type-families
type Defun = Type -> Type -> Type
data TwoK :: Defun where Two_ :: TwoK x (x,x)
data SwapK :: Defun where Swap_ :: SwapK (a, b) (b, a)
type family ($) (defun :: fK dom rng) (x :: dom) :: rng
type instance Two_ $ x = Two x
type instance Swap_ $ x = Swap x
-- And we can see it in action here
type Example1 = Map Two_ '[Int, Bool, Char]
type Example2 = Map Swap_ '[ '(Maybe, Bool), '([], Int)]
{-
>>> :kind! Example1
Example1 :: [(*, *)]
= '[ '(Int, Int), '(Bool, Bool), '(Char, Char)]
>>> :kind! Example2
Example2 :: [(*, * -> *)]
= '[ '(Bool, Maybe), '(Int, [])]
-}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment