[Haskell-cafe] Simulating open datatypes with type families?
Patrick Thomson
thomsonp at gwmail.gwu.edu
Sat Feb 26 16:43:27 CET 2011
I'm currently working on a project that involves a C parser (using Parsec3) that needs to be dynamically extensible - i.e. end-users should be able to add new statement types, expression types, operators, and so on and so forth.
Since Haskell ADT's are closed, I thought I would be able to simulate this by using type families, e.g.:
{-# LANGUAGE TypeFamilies, DeriveDataTypeable #-}
-- the statement type
type CStatement = BreakStmt
| CaseStmt CExpression CStatement
-- rest of the statement types omitted here for brevity
-- CStatement derives (Show, Eq, Typeable, Data)
statement :: Parser CStatement
-- how exactly this is parsed is not relevant, so its definition is also omitted
data family StatementLike a
data instance StatementLike CStatement = MkStmt CStatement
-- okay, this is all well and good. let's create a new ADT, representing the Ruby/Perl-esque 'until' statement and add a StatementLike instance for it.
data Until = UntilStmt CExpression CStatement deriving (Eq, Show, Typeable, Data)
data instance StatementLike Until = MkUntil Until
untilStatement :: Parser Until
-- definition omitted
-- Here's where it breaks down. I want to be able to have a function of type Parser (StatementLike a) so that I can pattern-match over the a in future code, but this function doesn't typecheck: GHC says that the function can't be that general - it expects either a Parser (StatementLike CStatement) or a Parser (StatementLike Until).
newStatement :: Parser (CStatement a)
newStatement = (MkUntil <$> untilStatement) <|> (MkStmt <$> statement)
Am I expecting the wrong thing of type families? Are typeclasses the better way to do this? Is there any other way to simulate an open, extensible ADT, or am I totally barking up the wrong tree?
Any assistance would be much appreciated. Please let me know if I need to provide more information.
Thanks in advance,
-- Patrick Thomson
More information about the Haskell-Cafe
mailing list