Skip to content

Instantly share code, notes, and snippets.

@leftaroundabout
Last active July 10, 2019 13:41
Show Gist options
  • Star 1 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save leftaroundabout/746cfa44fdf1a79a645507e66780eba3 to your computer and use it in GitHub Desktop.
Save leftaroundabout/746cfa44fdf1a79a645507e66780eba3 to your computer and use it in GitHub Desktop.
#!/usr/bin/env stack
{- stack --resolver lts-12.0 runghc -}
{-# LANGUAGE TypeFamilies, FlexibleInstances #-}
{-# LANGUAGE DataKinds, PolyKinds, KindSignatures, TypeInType #-}
{-# LANGUAGE AllowAmbiguousTypes, TypeApplications, GADTs #-}
import Prelude hiding ((.), id)
import qualified Prelude
import Data.Kind
class Category o where
type Hom o (a :: o) (b :: o) :: Type
type ValidObject o (a :: o) :: Constraint
type ValidObject o a = ()
(.) :: Hom o b c -> Hom o a b -> Hom o a c
id :: ValidObject o a => Hom o a a
instance Category Type where
type Hom Type a b = a->b
(.) = (Prelude..)
id = Prelude.id
f :: Hom Type Int Int
f 0 = 0
f n = n+1
g :: Hom Type Int Int
g = succ
h :: Hom Type Int Int
h = (.) @Type g f
main :: IO ()
main = print [h 0, h 1, h 2]
data XY = X | Y
data XYMorphism :: (XY -> XY -> *) where
X2X :: XYMorphism 'X 'X
Y2Y :: XYMorphism 'Y 'Y
X2Y :: XYMorphism 'X 'Y
Y2X :: XYMorphism 'Y 'X
class XOrY (p :: XY) where
xyId :: XYMorphism p p
instance XOrY 'X where xyId = X2X
instance XOrY 'Y where xyId = Y2Y
instance Category XY where
type Hom XY a b = XYMorphism a b
type ValidObject XY p = XOrY p
X2X . f = f
Y2Y . f = f
f . X2X = f
f . Y2Y = f
X2Y . Y2X = Y2Y
Y2X . X2Y = X2X
id = xyId
@leftaroundabout
Copy link
Author

This is a Haskell version of the Idris interface proposed in idris-lang/Idris-dev#4736

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment