
Hi all, I am in the process of writing a Scheme interpreter/compiler in Haskell as my first serious project after learning the basics of Haskell. The goal is to really get a feel for Haskell. I am trying to accomplish this as much as I can on my own, but am referring to Jonathan Tang's 'Write Yourself a Scheme in 48 hours' whenever I get really stuck. I have a question regarding a pattern that I have found within my code for which I cannot seem to find an abstraction. I am implementing some of the primitive Scheme type-checker functions with the following code: numberP :: SchemeVal -> SchemeVal numberP (Number _) = Bool True numberP _ = Bool False boolP :: SchemeVal -> SchemeVal boolP (Bool _) = Bool True boolP _ = Bool False symbolP :: SchemeVal -> SchemeVal symbolP (Atom _) = Bool True symbolP _ = Bool False This is a pattern that I could easily provide an abstraction for with a Lisp macro, but I'm having trouble discovering if/how it's possible to do so elegantly in Haskell. The closest (but obviously incorrect) code to what I'm trying to accomplish would be: typeChecker :: SchemeVal -> SchemeVal -> SchemeVal typeChecker (cons _) (cons2 _) = Bool $ cons == cons2 I understand this code drastically misunderstands how pattern matching works, but (hopefully) it expresses what I'm trying to accomplish. Anyone have any suggestions? I do realise that such an abstraction is barely worth it for the amount of code it will save, but this exercise is about learning the ins and outs of Haskell. Appreciate you taking the time to read this, Matt Andrew

Perhaps I am misunderstanding your question, but why not just skip defining
these predicates altogether? You could just use pattern matching directly
when you want to check that something is a number, or that it is a symbol,
etc.
On Tue, Aug 3, 2010 at 07:51, Matt Andrew
Hi all,
I am in the process of writing a Scheme interpreter/compiler in Haskell as my first serious project after learning the basics of Haskell. The goal is to really get a feel for Haskell. I am trying to accomplish this as much as I can on my own, but am referring to Jonathan Tang's 'Write Yourself a Scheme in 48 hours' whenever I get really stuck.
I have a question regarding a pattern that I have found within my code for which I cannot seem to find an abstraction.
I am implementing some of the primitive Scheme type-checker functions with the following code:
numberP :: SchemeVal -> SchemeVal numberP (Number _) = Bool True numberP _ = Bool False
boolP :: SchemeVal -> SchemeVal boolP (Bool _) = Bool True boolP _ = Bool False
symbolP :: SchemeVal -> SchemeVal symbolP (Atom _) = Bool True symbolP _ = Bool False
This is a pattern that I could easily provide an abstraction for with a Lisp macro, but I'm having trouble discovering if/how it's possible to do so elegantly in Haskell. The closest (but obviously incorrect) code to what I'm trying to accomplish would be:
typeChecker :: SchemeVal -> SchemeVal -> SchemeVal typeChecker (cons _) (cons2 _) = Bool $ cons == cons2
I understand this code drastically misunderstands how pattern matching works, but (hopefully) it expresses what I'm trying to accomplish. Anyone have any suggestions?
I do realise that such an abstraction is barely worth it for the amount of code it will save, but this exercise is about learning the ins and outs of Haskell.
Appreciate you taking the time to read this,
Matt Andrew _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- mac

On Tue, Aug 03, 2010 at 09:51:45PM +1000, Matt Andrew wrote:
Hi all,
I am in the process of writing a Scheme interpreter/compiler in Haskell as my first serious project after learning the basics of Haskell. The goal is to really get a feel for Haskell. I am trying to accomplish this as much as I can on my own, but am referring to Jonathan Tang's 'Write Yourself a Scheme in 48 hours' whenever I get really stuck.
I have a question regarding a pattern that I have found within my code for which I cannot seem to find an abstraction.
I am implementing some of the primitive Scheme type-checker functions with the following code:
numberP :: SchemeVal -> SchemeVal numberP (Number _) = Bool True numberP _ = Bool False
boolP :: SchemeVal -> SchemeVal boolP (Bool _) = Bool True boolP _ = Bool False
symbolP :: SchemeVal -> SchemeVal symbolP (Atom _) = Bool True symbolP _ = Bool False
This is a pattern that I could easily provide an abstraction for with a Lisp macro, but I'm having trouble discovering if/how it's possible to do so elegantly in Haskell. The closest (but obviously incorrect) code to what I'm trying to accomplish would be:
It isn't really possible to abstract this any further in Haskell. Constructors are rather magical functions, but they are still functions, and like other functions cannot be compared for equality directly. Pattern-matching them is the only sort of equality comparison you get. With that said, your intuition to use Lisp macros is a good one. Haskell has a similar metaprogramming facility called Template Haskell, which could easily be used to automatically generate these sorts of functions. Of course, it's a little more complicated than Lisp macros since Haskell syntax is so much more complex than Lisp's -- but given that, on the whole it's not so bad. I wouldn't use TH to generate just the three functions you showed -- but I would certainly consider it for ten. -Brent

I have never used Data.Typeable, but maybe it could be made relevant here?
On Tue, Aug 3, 2010 at 4:18 PM, Brent Yorgey
Hi all,
I am in the process of writing a Scheme interpreter/compiler in Haskell as my first serious project after learning the basics of Haskell. The goal is to really get a feel for Haskell. I am trying to accomplish this as much as I can on my own, but am referring to Jonathan Tang's 'Write Yourself a Scheme in 48 hours' whenever I get really stuck.
I have a question regarding a pattern that I have found within my code for which I cannot seem to find an abstraction.
I am implementing some of the primitive Scheme type-checker functions with the following code:
numberP :: SchemeVal -> SchemeVal numberP (Number _) = Bool True numberP _ = Bool False
boolP :: SchemeVal -> SchemeVal boolP (Bool _) = Bool True boolP _ = Bool False
symbolP :: SchemeVal -> SchemeVal symbolP (Atom _) = Bool True symbolP _ = Bool False
This is a pattern that I could easily provide an abstraction for with a Lisp macro, but I'm having trouble discovering if/how it's possible to do so elegantly in Haskell. The closest (but obviously incorrect) code to what I'm
On Tue, Aug 03, 2010 at 09:51:45PM +1000, Matt Andrew wrote: trying to accomplish would be:
It isn't really possible to abstract this any further in Haskell. Constructors are rather magical functions, but they are still functions, and like other functions cannot be compared for equality directly. Pattern-matching them is the only sort of equality comparison you get.
With that said, your intuition to use Lisp macros is a good one. Haskell has a similar metaprogramming facility called Template Haskell, which could easily be used to automatically generate these sorts of functions. Of course, it's a little more complicated than Lisp macros since Haskell syntax is so much more complex than Lisp's -- but given that, on the whole it's not so bad. I wouldn't use TH to generate just the three functions you showed -- but I would certainly consider it for ten.
-Brent _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachments Alex R

On Tue, Aug 03, 2010 at 04:19:58PM +0300, Alex Rozenshteyn wrote:
I have never used Data.Typeable, but maybe it could be made relevant here?
Not really. Data.Typeable lets you pass (representations of) types around at runtime, and thus do things like type-safe casts. So it's useful for things like serialization, extracting things out of existential wrappers, and so on. It isn't really relevant in this situation, as Matt already has all the type information he could want. -Brent
On Tue, Aug 3, 2010 at 4:18 PM, Brent Yorgey
wrote: Hi all,
I am in the process of writing a Scheme interpreter/compiler in Haskell as my first serious project after learning the basics of Haskell. The goal is to really get a feel for Haskell. I am trying to accomplish this as much as I can on my own, but am referring to Jonathan Tang's 'Write Yourself a Scheme in 48 hours' whenever I get really stuck.
I have a question regarding a pattern that I have found within my code for which I cannot seem to find an abstraction.
I am implementing some of the primitive Scheme type-checker functions with the following code:
numberP :: SchemeVal -> SchemeVal numberP (Number _) = Bool True numberP _ = Bool False
boolP :: SchemeVal -> SchemeVal boolP (Bool _) = Bool True boolP _ = Bool False
symbolP :: SchemeVal -> SchemeVal symbolP (Atom _) = Bool True symbolP _ = Bool False
This is a pattern that I could easily provide an abstraction for with a Lisp macro, but I'm having trouble discovering if/how it's possible to do so elegantly in Haskell. The closest (but obviously incorrect) code to what I'm
On Tue, Aug 03, 2010 at 09:51:45PM +1000, Matt Andrew wrote: trying to accomplish would be:
It isn't really possible to abstract this any further in Haskell. Constructors are rather magical functions, but they are still functions, and like other functions cannot be compared for equality directly. Pattern-matching them is the only sort of equality comparison you get.
With that said, your intuition to use Lisp macros is a good one. Haskell has a similar metaprogramming facility called Template Haskell, which could easily be used to automatically generate these sorts of functions. Of course, it's a little more complicated than Lisp macros since Haskell syntax is so much more complex than Lisp's -- but given that, on the whole it's not so bad. I wouldn't use TH to generate just the three functions you showed -- but I would certainly consider it for ten.
-Brent _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachments
Alex R
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

I was going to argue this point but then it occurred to me that writing a
whole bunch of functions like:
isAFoo :: FooBarBaz -> FooBarBaz -> Bool
isAFoo x = typeChecker (Foo undefined) x
isn't really in any way better than:
isAFoo :: FooBarBaz -> FooBarBaz -> Bool
isAFoo (Foo _) = True
isAFoo _ = False
Although it did give me a chance to play around with Data and Typeable a
bit.
-R. Kyle Murphy
--
Curiosity was framed, Ignorance killed the cat.
On Tue, Aug 3, 2010 at 15:25, Brent Yorgey
On Tue, Aug 03, 2010 at 04:19:58PM +0300, Alex Rozenshteyn wrote:
I have never used Data.Typeable, but maybe it could be made relevant here?
Not really. Data.Typeable lets you pass (representations of) types around at runtime, and thus do things like type-safe casts. So it's useful for things like serialization, extracting things out of existential wrappers, and so on. It isn't really relevant in this situation, as Matt already has all the type information he could want.
-Brent
On Tue, Aug 3, 2010 at 4:18 PM, Brent Yorgey
wrote:
On Tue, Aug 03, 2010 at 09:51:45PM +1000, Matt Andrew wrote:
Hi all,
I am in the process of writing a Scheme interpreter/compiler in
Haskell
as my first serious project after learning the basics of Haskell. The goal is to really get a feel for Haskell. I am trying to accomplish this as much as I can on my own, but am referring to Jonathan Tang's 'Write Yourself a Scheme in 48 hours' whenever I get really stuck.
I have a question regarding a pattern that I have found within my
code for which I cannot seem to find an abstraction.
I am implementing some of the primitive Scheme type-checker functions
with the following code:
numberP :: SchemeVal -> SchemeVal numberP (Number _) = Bool True numberP _ = Bool False
boolP :: SchemeVal -> SchemeVal boolP (Bool _) = Bool True boolP _ = Bool False
symbolP :: SchemeVal -> SchemeVal symbolP (Atom _) = Bool True symbolP _ = Bool False
This is a pattern that I could easily provide an abstraction for with
a Lisp macro, but I'm having trouble discovering if/how it's possible to do so elegantly in Haskell. The closest (but obviously incorrect) code to what I'm trying to accomplish would be:
It isn't really possible to abstract this any further in Haskell. Constructors are rather magical functions, but they are still functions, and like other functions cannot be compared for equality directly. Pattern-matching them is the only sort of equality comparison you get.
With that said, your intuition to use Lisp macros is a good one. Haskell has a similar metaprogramming facility called Template Haskell, which could easily be used to automatically generate these sorts of functions. Of course, it's a little more complicated than Lisp macros since Haskell syntax is so much more complex than Lisp's -- but given that, on the whole it's not so bad. I wouldn't use TH to generate just the three functions you showed -- but I would certainly consider it for ten.
-Brent _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachments
Alex R
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

To my understanding, what you want is pattern matching on data constructors.
In the following example,
data Expr = Num Int
| Plus Expr Expr
| Minus Expr Expr
incrementNums :: Expr -> Expr
incrementNums (Num i) = Num (i+1)
incrementNums (Plus i j) = Plus (incrementNums i) (incrementNums j)
incrementNums (Minus i j) = Minus (incrementNums i) (incrementNums j)
incrementNums' :: Expr -> Expr
incrementNums' (Num i) = Num (i+1)
incrementNums' (cons i j) = cons (incrementNums' i) (incrementNums' j)
You want incrementNums' instead of incrementNums.
And that's not possible with this data type. Of course you can always do the
following:
data ExprEnum = Plus | Minus
data Expr = Num Int
| BinExpr ExprEnum Expr Expr
incrementNums :: Expr -> Expr
incrementNums (Num i) = Num (i+1)
incrementNums (BinExpr cons i j) = BinExpr cons (incrementNums i)
(incrementNums j)
Hope this helps. Cheers,
On 3 August 2010 12:51, Matt Andrew
Hi all,
I am in the process of writing a Scheme interpreter/compiler in Haskell as my first serious project after learning the basics of Haskell. The goal is to really get a feel for Haskell. I am trying to accomplish this as much as I can on my own, but am referring to Jonathan Tang's 'Write Yourself a Scheme in 48 hours' whenever I get really stuck.
I have a question regarding a pattern that I have found within my code for which I cannot seem to find an abstraction.
I am implementing some of the primitive Scheme type-checker functions with the following code:
numberP :: SchemeVal -> SchemeVal numberP (Number _) = Bool True numberP _ = Bool False
boolP :: SchemeVal -> SchemeVal boolP (Bool _) = Bool True boolP _ = Bool False
symbolP :: SchemeVal -> SchemeVal symbolP (Atom _) = Bool True symbolP _ = Bool False
This is a pattern that I could easily provide an abstraction for with a Lisp macro, but I'm having trouble discovering if/how it's possible to do so elegantly in Haskell. The closest (but obviously incorrect) code to what I'm trying to accomplish would be:
typeChecker :: SchemeVal -> SchemeVal -> SchemeVal typeChecker (cons _) (cons2 _) = Bool $ cons == cons2
I understand this code drastically misunderstands how pattern matching works, but (hopefully) it expresses what I'm trying to accomplish. Anyone have any suggestions?
I do realise that such an abstraction is barely worth it for the amount of code it will save, but this exercise is about learning the ins and outs of Haskell.
Appreciate you taking the time to read this,
Matt Andrew _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Ozgur Akgun

Matt Andrew schrieb:
Hi all,
I am in the process of writing a Scheme interpreter/compiler in Haskell as my first serious project after learning the basics of Haskell. The goal is to really get a feel for Haskell. I am trying to accomplish this as much as I can on my own, but am referring to Jonathan Tang's 'Write Yourself a Scheme in 48 hours' whenever I get really stuck.
I have a question regarding a pattern that I have found within my code for which I cannot seem to find an abstraction.
I am implementing some of the primitive Scheme type-checker functions with the following code:
numberP :: SchemeVal -> SchemeVal numberP (Number _) = Bool True numberP _ = Bool False
boolP :: SchemeVal -> SchemeVal boolP (Bool _) = Bool True boolP _ = Bool False
symbolP :: SchemeVal -> SchemeVal symbolP (Atom _) = Bool True symbolP _ = Bool False
This is a pattern that I could easily provide an abstraction for with a Lisp macro, but I'm having trouble discovering if/how it's possible to do so elegantly in Haskell. The closest (but obviously incorrect) code to what I'm trying to accomplish would be:
typeChecker :: SchemeVal -> SchemeVal -> SchemeVal typeChecker (cons _) (cons2 _) = Bool $ cons == cons2
I understand this code drastically misunderstands how pattern matching works, but (hopefully) it expresses what I'm trying to accomplish. Anyone have any suggestions?
typeChecker s1 s2 = let f = takeWhile isAlphaNum . show in Bool $ f s1 == f s2 hoping that my "f" just extracts the constructor as string. C.
I do realise that such an abstraction is barely worth it for the amount of code it will save, but this exercise is about learning the ins and outs of Haskell.
Appreciate you taking the time to read this,
Matt Andrew

That is a dirty, dirty hack.
On Tue, Aug 3, 2010 at 8:45 PM, Christian Maeder
Hi all,
I am in the process of writing a Scheme interpreter/compiler in Haskell as my first serious project after learning the basics of Haskell. The goal is to really get a feel for Haskell. I am trying to accomplish this as much as I can on my own, but am referring to Jonathan Tang's 'Write Yourself a Scheme in 48 hours' whenever I get really stuck.
I have a question regarding a pattern that I have found within my code for which I cannot seem to find an abstraction.
I am implementing some of the primitive Scheme type-checker functions with the following code:
numberP :: SchemeVal -> SchemeVal numberP (Number _) = Bool True numberP _ = Bool False
boolP :: SchemeVal -> SchemeVal boolP (Bool _) = Bool True boolP _ = Bool False
symbolP :: SchemeVal -> SchemeVal symbolP (Atom _) = Bool True symbolP _ = Bool False
This is a pattern that I could easily provide an abstraction for with a Lisp macro, but I'm having trouble discovering if/how it's possible to do so elegantly in Haskell. The closest (but obviously incorrect) code to what I'm
Matt Andrew schrieb: trying to accomplish would be:
typeChecker :: SchemeVal -> SchemeVal -> SchemeVal typeChecker (cons _) (cons2 _) = Bool $ cons == cons2
I understand this code drastically misunderstands how pattern matching
works, but (hopefully) it expresses what I'm trying to accomplish. Anyone have any suggestions?
typeChecker s1 s2 = let f = takeWhile isAlphaNum . show in Bool $ f s1 == f s2
hoping that my "f" just extracts the constructor as string.
C.
I do realise that such an abstraction is barely worth it for the amount of code it will save, but this exercise is about learning the ins and outs of Haskell.
Appreciate you taking the time to read this,
Matt Andrew
Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachments Alex R

Less of a dirty dirty hack (requires that SchemeVal be an instance of
Typeable):
import Data.Typeable
import Data.Maybe
typeChecker :: (Typeable a, Typeable b) => a -> b -> Bool
typeChecker a b = f a == f b
where
f :: (Typeable a) => a -> Maybe TypeRep
f = listToMaybe . typeRepArgs . typeOf
-R. Kyle Murphy
--
Curiosity was framed, Ignorance killed the cat.
On Tue, Aug 3, 2010 at 13:51, Alex Rozenshteyn
That is a dirty, dirty hack.
On Tue, Aug 3, 2010 at 8:45 PM, Christian Maeder
wrote:
Hi all,
I am in the process of writing a Scheme interpreter/compiler in Haskell as my first serious project after learning the basics of Haskell. The goal is to really get a feel for Haskell. I am trying to accomplish this as much as I can on my own, but am referring to Jonathan Tang's 'Write Yourself a Scheme in 48 hours' whenever I get really stuck.
I have a question regarding a pattern that I have found within my code for which I cannot seem to find an abstraction.
I am implementing some of the primitive Scheme type-checker functions with the following code:
numberP :: SchemeVal -> SchemeVal numberP (Number _) = Bool True numberP _ = Bool False
boolP :: SchemeVal -> SchemeVal boolP (Bool _) = Bool True boolP _ = Bool False
symbolP :: SchemeVal -> SchemeVal symbolP (Atom _) = Bool True symbolP _ = Bool False
This is a pattern that I could easily provide an abstraction for with a Lisp macro, but I'm having trouble discovering if/how it's possible to do so elegantly in Haskell. The closest (but obviously incorrect) code to what I'm
Matt Andrew schrieb: trying to accomplish would be:
typeChecker :: SchemeVal -> SchemeVal -> SchemeVal typeChecker (cons _) (cons2 _) = Bool $ cons == cons2
I understand this code drastically misunderstands how pattern matching
works, but (hopefully) it expresses what I'm trying to accomplish. Anyone have any suggestions?
typeChecker s1 s2 = let f = takeWhile isAlphaNum . show in Bool $ f s1 == f s2
hoping that my "f" just extracts the constructor as string.
C.
I do realise that such an abstraction is barely worth it for the amount of code it will save, but this exercise is about learning the ins and outs of Haskell.
Appreciate you taking the time to read this,
Matt Andrew
Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachments
Alex R
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Actually looking at the original question I'm not sure my code does what was
intended. I was looking at does some type (a b) == (a c), which wasn't
exactly the question. Oh well, back to the drawing board.
-R. Kyle Murphy
--
Curiosity was framed, Ignorance killed the cat.
On Tue, Aug 3, 2010 at 14:38, Kyle Murphy
Less of a dirty dirty hack (requires that SchemeVal be an instance of Typeable):
import Data.Typeable import Data.Maybe
typeChecker :: (Typeable a, Typeable b) => a -> b -> Bool typeChecker a b = f a == f b where f :: (Typeable a) => a -> Maybe TypeRep f = listToMaybe . typeRepArgs . typeOf
-R. Kyle Murphy -- Curiosity was framed, Ignorance killed the cat.
On Tue, Aug 3, 2010 at 13:51, Alex Rozenshteyn
wrote: That is a dirty, dirty hack.
On Tue, Aug 3, 2010 at 8:45 PM, Christian Maeder < Christian.Maeder@dfki.de> wrote:
Hi all,
I am in the process of writing a Scheme interpreter/compiler in Haskell as my first serious project after learning the basics of Haskell. The goal is to really get a feel for Haskell. I am trying to accomplish this as much as I can on my own, but am referring to Jonathan Tang's 'Write Yourself a Scheme in 48 hours' whenever I get really stuck.
I have a question regarding a pattern that I have found within my code for which I cannot seem to find an abstraction.
I am implementing some of the primitive Scheme type-checker functions with the following code:
numberP :: SchemeVal -> SchemeVal numberP (Number _) = Bool True numberP _ = Bool False
boolP :: SchemeVal -> SchemeVal boolP (Bool _) = Bool True boolP _ = Bool False
symbolP :: SchemeVal -> SchemeVal symbolP (Atom _) = Bool True symbolP _ = Bool False
This is a pattern that I could easily provide an abstraction for with a Lisp macro, but I'm having trouble discovering if/how it's possible to do so elegantly in Haskell. The closest (but obviously incorrect) code to what I'm
Matt Andrew schrieb: trying to accomplish would be:
typeChecker :: SchemeVal -> SchemeVal -> SchemeVal typeChecker (cons _) (cons2 _) = Bool $ cons == cons2
I understand this code drastically misunderstands how pattern matching
works, but (hopefully) it expresses what I'm trying to accomplish. Anyone have any suggestions?
typeChecker s1 s2 = let f = takeWhile isAlphaNum . show in Bool $ f s1 == f s2
hoping that my "f" just extracts the constructor as string.
C.
I do realise that such an abstraction is barely worth it for the amount of code it will save, but this exercise is about learning the ins and outs of Haskell.
Appreciate you taking the time to read this,
Matt Andrew
Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachments
Alex R
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

I was close, this actually does what was asked:
import Data.Data
typeChecker :: (Typeable a, Typeable b, Data a, Data b) => a -> b -> Bool
typeChecker a b = toConstr a == toConstr b
-R. Kyle Murphy
--
Curiosity was framed, Ignorance killed the cat.
On Tue, Aug 3, 2010 at 14:42, Kyle Murphy
Actually looking at the original question I'm not sure my code does what was intended. I was looking at does some type (a b) == (a c), which wasn't exactly the question. Oh well, back to the drawing board.
-R. Kyle Murphy -- Curiosity was framed, Ignorance killed the cat.
On Tue, Aug 3, 2010 at 14:38, Kyle Murphy
wrote: Less of a dirty dirty hack (requires that SchemeVal be an instance of Typeable):
import Data.Typeable import Data.Maybe
typeChecker :: (Typeable a, Typeable b) => a -> b -> Bool typeChecker a b = f a == f b where f :: (Typeable a) => a -> Maybe TypeRep f = listToMaybe . typeRepArgs . typeOf
-R. Kyle Murphy -- Curiosity was framed, Ignorance killed the cat.
On Tue, Aug 3, 2010 at 13:51, Alex Rozenshteyn
wrote: That is a dirty, dirty hack.
On Tue, Aug 3, 2010 at 8:45 PM, Christian Maeder < Christian.Maeder@dfki.de> wrote:
Matt Andrew schrieb:
Hi all,
I am in the process of writing a Scheme interpreter/compiler in Haskell as my first serious project after learning the basics of Haskell. The goal is to really get a feel for Haskell. I am trying to accomplish this as much as I can on my own, but am referring to Jonathan Tang's 'Write Yourself a Scheme in 48 hours' whenever I get really stuck.
I have a question regarding a pattern that I have found within my code for which I cannot seem to find an abstraction.
I am implementing some of the primitive Scheme type-checker functions with the following code:
numberP :: SchemeVal -> SchemeVal numberP (Number _) = Bool True numberP _ = Bool False
boolP :: SchemeVal -> SchemeVal boolP (Bool _) = Bool True boolP _ = Bool False
symbolP :: SchemeVal -> SchemeVal symbolP (Atom _) = Bool True symbolP _ = Bool False
This is a pattern that I could easily provide an abstraction for with a Lisp macro, but I'm having trouble discovering if/how it's possible to do so elegantly in Haskell. The closest (but obviously incorrect) code to what I'm trying to accomplish would be:
typeChecker :: SchemeVal -> SchemeVal -> SchemeVal typeChecker (cons _) (cons2 _) = Bool $ cons == cons2
I understand this code drastically misunderstands how pattern matching works, but (hopefully) it expresses what I'm trying to accomplish. Anyone have any suggestions?
typeChecker s1 s2 = let f = takeWhile isAlphaNum . show in Bool $ f s1 == f s2
hoping that my "f" just extracts the constructor as string.
C.
I do realise that such an abstraction is barely worth it for the amount of code it will save, but this exercise is about learning the ins and outs of Haskell.
Appreciate you taking the time to read this,
Matt Andrew
Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachments
Alex R
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Why do you need them to be Typeable? toConstr has the following type:
toConstr :: (Data a) => a -> Constr
Best,
On 3 August 2010 19:50, Kyle Murphy
I was close, this actually does what was asked:
import Data.Data
typeChecker :: (Typeable a, Typeable b, Data a, Data b) => a -> b -> Bool typeChecker a b = toConstr a == toConstr b
-R. Kyle Murphy -- Curiosity was framed, Ignorance killed the cat.
On Tue, Aug 3, 2010 at 14:42, Kyle Murphy
wrote: Actually looking at the original question I'm not sure my code does what was intended. I was looking at does some type (a b) == (a c), which wasn't exactly the question. Oh well, back to the drawing board.
-R. Kyle Murphy -- Curiosity was framed, Ignorance killed the cat.
On Tue, Aug 3, 2010 at 14:38, Kyle Murphy
wrote: Less of a dirty dirty hack (requires that SchemeVal be an instance of Typeable):
import Data.Typeable import Data.Maybe
typeChecker :: (Typeable a, Typeable b) => a -> b -> Bool typeChecker a b = f a == f b where f :: (Typeable a) => a -> Maybe TypeRep f = listToMaybe . typeRepArgs . typeOf
-R. Kyle Murphy -- Curiosity was framed, Ignorance killed the cat.
On Tue, Aug 3, 2010 at 13:51, Alex Rozenshteyn
wrote: That is a dirty, dirty hack.
On Tue, Aug 3, 2010 at 8:45 PM, Christian Maeder < Christian.Maeder@dfki.de> wrote:
Matt Andrew schrieb:
Hi all,
I am in the process of writing a Scheme interpreter/compiler in Haskell as my first serious project after learning the basics of Haskell. The goal is to really get a feel for Haskell. I am trying to accomplish this as much as I can on my own, but am referring to Jonathan Tang's 'Write Yourself a Scheme in 48 hours' whenever I get really stuck.
I have a question regarding a pattern that I have found within my code for which I cannot seem to find an abstraction.
I am implementing some of the primitive Scheme type-checker functions with the following code:
numberP :: SchemeVal -> SchemeVal numberP (Number _) = Bool True numberP _ = Bool False
boolP :: SchemeVal -> SchemeVal boolP (Bool _) = Bool True boolP _ = Bool False
symbolP :: SchemeVal -> SchemeVal symbolP (Atom _) = Bool True symbolP _ = Bool False
This is a pattern that I could easily provide an abstraction for with a Lisp macro, but I'm having trouble discovering if/how it's possible to do so elegantly in Haskell. The closest (but obviously incorrect) code to what I'm trying to accomplish would be:
typeChecker :: SchemeVal -> SchemeVal -> SchemeVal typeChecker (cons _) (cons2 _) = Bool $ cons == cons2
I understand this code drastically misunderstands how pattern matching works, but (hopefully) it expresses what I'm trying to accomplish. Anyone have any suggestions?
typeChecker s1 s2 = let f = takeWhile isAlphaNum . show in Bool $ f s1 == f s2
hoping that my "f" just extracts the constructor as string.
C.
I do realise that such an abstraction is barely worth it for the amount of code it will save, but this exercise is about learning the ins and outs of Haskell.
Appreciate you taking the time to read this,
Matt Andrew
Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachments
Alex R
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Ozgur Akgun

You're partially right. The Typeable is redundant because Data has the type:
(Typeable a) => Data a
-R. Kyle Murphy
--
Curiosity was framed, Ignorance killed the cat.
On Tue, Aug 3, 2010 at 15:01, Ozgur Akgun
Why do you need them to be Typeable? toConstr has the following type:
toConstr :: (Data a) => a -> Constr
Best,
On 3 August 2010 19:50, Kyle Murphy
wrote: I was close, this actually does what was asked:
import Data.Data
typeChecker :: (Typeable a, Typeable b, Data a, Data b) => a -> b -> Bool typeChecker a b = toConstr a == toConstr b
-R. Kyle Murphy -- Curiosity was framed, Ignorance killed the cat.
On Tue, Aug 3, 2010 at 14:42, Kyle Murphy
wrote: Actually looking at the original question I'm not sure my code does what was intended. I was looking at does some type (a b) == (a c), which wasn't exactly the question. Oh well, back to the drawing board.
-R. Kyle Murphy -- Curiosity was framed, Ignorance killed the cat.
On Tue, Aug 3, 2010 at 14:38, Kyle Murphy
wrote: Less of a dirty dirty hack (requires that SchemeVal be an instance of Typeable):
import Data.Typeable import Data.Maybe
typeChecker :: (Typeable a, Typeable b) => a -> b -> Bool typeChecker a b = f a == f b where f :: (Typeable a) => a -> Maybe TypeRep f = listToMaybe . typeRepArgs . typeOf
-R. Kyle Murphy -- Curiosity was framed, Ignorance killed the cat.
On Tue, Aug 3, 2010 at 13:51, Alex Rozenshteyn
wrote: That is a dirty, dirty hack.
On Tue, Aug 3, 2010 at 8:45 PM, Christian Maeder < Christian.Maeder@dfki.de> wrote:
Matt Andrew schrieb: > Hi all, > > I am in the process of writing a Scheme interpreter/compiler in Haskell as my first serious project after learning the basics of Haskell. The goal is to really get a feel for Haskell. I am trying to accomplish this as much as I can on my own, but am referring to Jonathan Tang's 'Write Yourself a Scheme in 48 hours' whenever I get really stuck. > > I have a question regarding a pattern that I have found within my code for which I cannot seem to find an abstraction. > > I am implementing some of the primitive Scheme type-checker functions with the following code: > > numberP :: SchemeVal -> SchemeVal > numberP (Number _) = Bool True > numberP _ = Bool False > > boolP :: SchemeVal -> SchemeVal > boolP (Bool _) = Bool True > boolP _ = Bool False > > symbolP :: SchemeVal -> SchemeVal > symbolP (Atom _) = Bool True > symbolP _ = Bool False > > This is a pattern that I could easily provide an abstraction for with a Lisp macro, but I'm having trouble discovering if/how it's possible to do so elegantly in Haskell. The closest (but obviously incorrect) code to what I'm trying to accomplish would be: > > typeChecker :: SchemeVal -> SchemeVal -> SchemeVal > typeChecker (cons _) (cons2 _) = Bool $ cons == cons2 > > I understand this code drastically misunderstands how pattern matching works, but (hopefully) it expresses what I'm trying to accomplish. Anyone have any suggestions?
typeChecker s1 s2 = let f = takeWhile isAlphaNum . show in Bool $ f s1 == f s2
hoping that my "f" just extracts the constructor as string.
C.
> I do realise that such an abstraction is barely worth it for the amount of code it will save, but this exercise is about learning the ins and outs of Haskell. > > Appreciate you taking the time to read this, > > Matt Andrew _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachments
Alex R
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Ozgur Akgun

Kyle Murphy schrieb: [...]
typeChecker a b = toConstr a == toConstr b
Right, that is (slightly) cleaner than using my "show" trick below.
On Tue, Aug 3, 2010 at 13:51, Alex Rozenshteyn
mailto:rpglover64@gmail.com> wrote: That is a dirty, dirty hack.
[...] Alternatively you could define your own enumeration type: data SchemeType = NumberT | BoolT | AtomT deriving Eq schemeTypeOf :: SchemeVal -> SchemeType schemeTypeOf v = case v of Number _ -> NumberT Bool _ -> BoolT Atom _ -> AtomT typeChecker = Data.Function.on (==) schemeTypeOf C.
> > numberP :: SchemeVal -> SchemeVal > numberP (Number _) = Bool True > numberP _ = Bool False > > boolP :: SchemeVal -> SchemeVal > boolP (Bool _) = Bool True > boolP _ = Bool False > > symbolP :: SchemeVal -> SchemeVal > symbolP (Atom _) = Bool True > symbolP _ = Bool False
[...]
typeChecker s1 s2 = let f = takeWhile isAlphaNum . show in Bool $ f s1 == f s2
hoping that my "f" just extracts the constructor as string.
participants (7)
-
Alex Rozenshteyn
-
Brent Yorgey
-
Christian Maeder
-
Kyle Murphy
-
Matt Andrew
-
matthew coolbeth
-
Ozgur Akgun