Adding Read instances for HList

One option looks something like the code below. Another option would mirror the current Show instances by pushing "H[" back onto the state each time an item is parsed (I don't think that's a particularly clean approach, but it's an option). {-# LANGUAGE DataKinds ,KindSignatures ,FlexibleContexts ,FlexibleInstances ,TypeOperators ,GADTs ,ScopedTypeVariables #-} module MyHList where import GHC.Read import Text.ParserCombinators.ReadPrec import qualified Text.Read.Lex as L -- This declaration is copied from `Data.HList.HList`. data HList (l::[*]) where HNil :: HList '[] HCons :: e -> HList l -> HList (e ': l) infixr 2 `HCons` instance Read (HList '[]) where readPrec = parens ( do expectP (L.Ident "H") expectP (L.Punc "[") expectP (L.Punc "]") return HNil ) instance forall e . Read e => Read (HList (e ': '[])) where readPrec = parens ( do expectP (L.Ident "H") expectP (L.Punc "[") e <- reset $ (readPrec::ReadPrec e) expectP (L.Punc "]") return (e `HCons` HNil) ) instance forall e f (l::[*]) . (Read e, ReadTl (HList (f ': l))) => Read (HList (e ': f ': l)) where readPrec = parens ( do expectP (L.Ident "H") expectP (L.Punc "[") e <- reset $ (readPrec::ReadPrec e) expectP (L.Punc ",") rest <- readTl :: ReadPrec (HList (f ': l)) return (e `HCons` rest) ) class ReadTl l where readTl :: ReadPrec l instance forall e . Read e => ReadTl (HList (e ': '[])) where {-# INLINE readTl #-} readTl = do e <- reset $ (readPrec::ReadPrec e) expectP (L.Punc "]") return $ e `HCons` HNil instance forall e f (l::[*]) . (Read e, ReadTl (HList (f ': l))) => ReadTl (HList (e ': f ': l)) where {-# INLINE readTl #-} readTl = do e <- reset $ (readPrec::ReadPrec e) expectP (L.Punc ",") rest <- readTl return (e `HCons` rest)
participants (1)
-
David Feuer