Skip to content

Instantly share code, notes, and snippets.

@rahulmutt
Created March 3, 2017 05:07
Show Gist options
  • Save rahulmutt/840e2b67796c131d2345be4df7fa7858 to your computer and use it in GitHub Desktop.
Save rahulmutt/840e2b67796c131d2345be4df7fa7858 to your computer and use it in GitHub Desktop.
Length of HList
{-# LANGUAGE DataKinds, TypeFamilies, ScopedTypeVariables, TypeOperators, GADTs, UndecidableInstances, FlexibleContexts #-}
module Main where
import GHC.TypeLits
import Data.Proxy
main :: IO ()
main = print $ hlength (HCons "Hello" (HCons (1 :: Int) HNil))
hlength :: forall xs. KnownNat (Length xs) => HList xs -> Integer
hlength _ = natVal (Proxy :: Proxy (Length xs))
data HList :: [*] -> * where
HNil :: HList '[]
HCons :: x -> HList xs -> HList (x ': xs)
type family Length (a :: [*]) :: Nat where
Length '[] = 0
Length (x ': xs) = 1 + (Length xs)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment