Skip to content

Instantly share code, notes, and snippets.

@purpleP
Created January 27, 2020 16:23
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 purpleP/6aae7d5be624750d4685a965a4a2f7b3 to your computer and use it in GitHub Desktop.
Save purpleP/6aae7d5be624750d4685a965a4a2f7b3 to your computer and use it in GitHub Desktop.
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
import Data.Kind (Constraint, Type)
main = undefined
data HList (ts :: [Type]) where
HNil :: HList '[]
(:#) :: t -> HList ts -> HList (t ': ts)
infixr 5 :#
instance Eq (HList '[]) where
HNil == HNil = True
instance (Eq t, Eq (HList ts)) => Eq (HList (t ': ts)) where
(a :# as) == (b :# bs) = a == b && as == bs
instance Ord (HList '[]) where
compare HNil HNil = EQ
instance (Ord t, Ord (HList ts)) => Ord (HList (t ': ts)) where
compare (a :# as) (b :# bs) = case compare a b of
EQ -> compare as bs
x -> x
instance Show (HList '[]) where
show HNil = "[]"
instance (Show t, Show (HList ts)) => Show (HList (t ': ts)) where
show xs = "[" ++ (showMany xs "") ++ "]"
where
showMany (y :# ys) prefix = prefix ++ (show y) ++ rest
where rest = case ys of
HNil -> ""
ys -> showMany ys ", "
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment