Skip to content

Instantly share code, notes, and snippets.

@Porges
Created January 11, 2016 03:46
Show Gist options
  • Save Porges/b88092d0904ce66547a2 to your computer and use it in GitHub Desktop.
Save Porges/b88092d0904ce66547a2 to your computer and use it in GitHub Desktop.
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
data HList :: [*] -> * where
HNil :: HList '[]
HCons :: a -> HList k -> HList (a ': k)
hlen :: HList k -> Int
hlen HNil = 0
hlen (HCons _ hs) = 1 + hlen hs
withHList :: forall a b r. [Either a b] -> (forall k. HList k -> r) -> r
withHList xs f = go (reverse xs) HNil
where
go :: [Either a b] -> HList k -> r
go [] hl = f hl
go (Right x : xs) hl = go xs (HCons x hl)
go (Left x : xs) hl = go xs (HCons x hl)
main = print (withHList [Left "l", Right 'r', Right '2', Left "foo"] hlen)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment