[Haskell-cafe] Would someone explain this code to me?
Brandon Moore
brandonm at yahoo-inc.com
Wed Dec 6 16:06:56 EST 2006
Justin Bailey wrote:
> I'm reading Chris Okasaki's "Purely Functional Data Structures", and
> some of his Haskell is confusing me. He defines the type Color and
> RedBlackSet as:
>
> data Color = R | B
> data RedBlackSet a = E | T Color (RedBlackSet a) a (RedBlackSet a)
>
> and then later he defines a function insertSet:
>
> insertSet x s = T B a y b
> where ins E = T R E x E
> ...
> T _ a y b = ins s
>
> What I don't understand is his use of the "T" constructor, both at
>
> insertSet x s = T B a y b
>
> and in the where statement:
>
> T _ a y b = ins s
>
...
> If anyone can explain what's going on here, I'd appreciate it. Thank you!
If you ask correctly GHC will explain for you, with utmost verbosity.
It would be a lot more productive for you to look over the Haskell Report
and ask questions, but I had more fun working out this approach.
So, shall we continue this long and useless but hopefully interesting
journey?
To turn a module into a program that dumps the AST for the definitions
in that module, Replace
module *Name* where
*imports*
*definitions*
with
{-# OPTIONS -fth #-}
module Main where
*imports*
import Language.Haskell.TH
main = do {print =<< runQ [d|
*definitions
|]}
I can wrap up your example like this
{-# OPTIONS -fth #-}
module Main where
import Language.Haskell.TH
main = do {print =<< runQ [d|
data Color = R | B
data RedBlackSet a = E | T Color (RedBlackSet a) a (RedBlackSet a)
insertSet x s = T B a y b
where ins E = T R E x E
T _ a y b = ins s
|]}
Build like this
~$ ghc --make ExplainExample
and run to get this
~$ ./ExplainExample
[DataD [] Color [] [NormalC R [],NormalC B []] [],DataD [] RedBlackSet
[a_0] [NormalC E [],NormalC T [(NotStrict,ConT Color),(NotStrict,AppT
(ConT RedBlackSet) (VarT a_0)),(NotStrict,VarT a_0),(NotStrict,AppT
(ConT RedBlackSet) (VarT a_0))]] [],FunD insertSet [Clause [VarP
x_1,VarP s_2] (NormalB (AppE (AppE (AppE (AppE (ConE T) (ConE B)) (VarE
a_4)) (VarE y_5)) (VarE b_6))) [FunD ins_3 [Clause [ConP E []] (NormalB
(AppE (AppE (AppE (AppE (ConE T) (ConE R)) (ConE E)) (VarE x_1)) (ConE
E))) []],ValD (ConP T [WildP,VarP a_4,VarP y_5,VarP b_6]) (NormalB (AppE
(VarE ins_3) (VarE s_2))) []]]]
This is very similar -ddump-parsed GHC flag, except that pretty prints
the AST back into normal Haskell syntax, losing all the unambiguous labels.
If there was some way to get the AST printed with reasonable newlines
and indentation,
you might actually be able to match this back to your syntax. Maybe
combining Data.Generics with some pretty printer library could do that
easily, but that's a story for another time.
Supposing you could match this back to your syntax, you would find that
"ins E = T B a y b"
became
FunD ins_3
[Clause [ConP E []]
(NormalB (AppE (AppE (AppE (AppE (ConE T) (ConE R)) (ConE E))
(VarE x_1)) (ConE E))) []]
and
"T _ a y b = ins s"
became
ValD (ConP T [WildP,VarP a_4,VarP y_5,VarP b_6])
(NormalB (AppE (VarE ins_3) (VarE s_2))) []
Matching these back to the grammar in the Haskell Report (the docs for
Language.Haskell.TH.Syntax should really include references) would
presumably tell you something about how the expression parsed.
Brandon
More information about the Haskell-Cafe
mailing list