
Support I want to infer the type given an Op that looks like this (incomplete): data Op = Minus | Plus | Mul | LT | GT Is there a shorthand way of bunching Minus, Plus and Mul in a function guard since they all result in TyNum whereas the rest in TyBool? I really don't want several function clauses and neither do I want separate guards for every constructor. Thanks, Joel -- http://wagerlabs.com/

Hi
isBool x = isLT x || isGT x
isNum x = not $ isBool x
isLT and isGT can be derived automatically using derve [1], with the
Is class (or DrIFT if you want).
Thanks
Neil
[1] google "data derive"
On 4/19/07, Joel Reymont
Support I want to infer the type given an Op that looks like this (incomplete):
data Op = Minus | Plus | Mul | LT | GT
Is there a shorthand way of bunching Minus, Plus and Mul in a function guard since they all result in TyNum whereas the rest in TyBool?
I really don't want several function clauses and neither do I want separate guards for every constructor.
Thanks, Joel
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Neil Mitchell wrote:
Hi
isBool x = isLT x || isGT x isNum x = not $ isBool x
isLT and isGT can be derived automatically using derve [1], with the Is class (or DrIFT if you want).
You can also get a long way with GHC's built in derivations for Eq, Enum and Show. If an Enum instance is possible then you can write something like isBool = (`elem` [LT .. GT]) isNum = (`elem` [Minus .. Mul]) If enum is not possible, because some of the constructors are not nullary, then there is the following cute/ugly hack if you instead derive Show: constrName = takeWhile (/=' ') . show and you can say isBool x = constrName x `elem` ["LT","GT"] isNum x = constrName x `elem` ["Minus","Plus","Mul"] What this leads us towards is that it might be rather nice (perhaps even nice enough to build into a compiler) to be able to derive, for each type with multiple constructors, a type 'which is the enumeration of the constructors'. I.e. a type with the same constructors (up to some namespace fix like prepending with C) but all nullary: data Atom = Null | MyInt Int | MyString String derives... data AtomCons = CNull | CMyInt | CMyString deriving (Ord,Eq,Enum,Show) and a function constr :: Atom -> AtomCons Jules

Hi Jules,
What this leads us towards is that it might be rather nice (perhaps even nice enough to build into a compiler) to be able to derive, for each type with multiple constructors, a type 'which is the enumeration of the constructors'. I.e. a type with the same constructors (up to some namespace fix like prepending with C) but all nullary:
data Atom = Null | MyInt Int | MyString String
derives...
data AtomCons = CNull | CMyInt | CMyString deriving (Ord,Eq,Enum,Show)
and a function
constr :: Atom -> AtomCons
If you can derive Enum for all possible constructors (supplying undefined for all fields) then people can do this already: isBool x = fromEnum x `elem` [fromEnum LT .. fromEnum GT] And I'm sure with an "elemCtorSet" you could automate most of this away in to a tidy little function. As a side note, this is what Derive already does :-) Thanks Neil

Joel Reymont wrote:
Support I want to infer the type given an Op that looks like this (incomplete):
data Op = Minus | Plus | Mul | LT | GT
Is there a shorthand way of bunching Minus, Plus and Mul in a function guard since they all result in TyNum whereas the rest in TyBool?
data NumOrBool = JNum | JBool deriving (Eq) numorbool Minus = JNum numorbool Plus = JNum numorbool Mul = JNum numorbool LT = JBool numorbool GT = JBool f o | numorbool o == JNum = TyNum (...) | numorbool o == JBool = TyBool (...) ...so you have to define one function rather verbosely (numorbool) but once you've done it once you can use it in a guard to define others more quickly. You could use pattern guards instead of == and forget about deriving Eq if you prefer. Jules

This is what want. Notice the succinctness. Objective Caml version 3.10+dev24 (2007-02-16) # type foo = A | B | C | D | E | F ;; type foo = A | B | C | D | E | F # A;; - : foo = A # let infer = function | A | B | C -> true; | D | E | F -> false;; val infer : foo -> bool = <fun> # infer A;; - : bool = true # infer B;; - : bool = true # infer D;; - : bool = false # infer F;; - : bool = false # -- http://wagerlabs.com/

Joel Reymont wrote:
This is what want. Notice the succinctness.
# let infer = function | A | B | C -> true; | D | E | F -> false;; val infer : foo -> bool = <fun>
Yes, I appreciate what you want, and I know ocaml too :) I was just talking around the other ways you can achieve it. I don't know if there is a strong reason why haskell doesn't support an equivalent syntax. I'd guess something like: f A = B = C = true f D = E = F = false or perhaps f A = f B = f C = true f D = f E = f F = false Jules

a) After filtering the content I want to use how do I extract the text? eg a = xtract "html/body/h2/-" which should return the text contained in the h2 tag. There is a parser called text which returns the text but I don't know how to use it ? Is there a much simpler way I have missed? b) What is a CRef? When are they used? Marc

| > # let infer = function | A | B | C -> true; | D | E | F -> false;; | > val infer : foo -> bool = <fun> | | | Yes, I appreciate what you want, and I know ocaml too :) | | I was just talking around the other ways you can achieve it. I don't | know if there is a strong reason why haskell doesn't support an | equivalent syntax. No, there's no strong reason. It's just one more feature... and (perhaps surprisingly) Joel is the first person to raise it that I can remember. Which is not to say that it's unimportant, but it helps to explain why it isn't in the language. Simon

Joel Reymont
Support I want to infer the type given an Op that looks like this (incomplete):
data Op = Minus | Plus | Mul | LT | GT
Is there a shorthand way of bunching Minus, Plus and Mul in a function guard since they all result in TyNum whereas the rest in TyBool?
I really don't want several function clauses and neither do I want separate guards for every constructor.
Is there some reason why you don't want data Op = Aop Aop | Bop Bop data Aop = Minus | Plus | Mul data Bop = LT | GT or similar? I would agree that it's a shame one cannot just write data Op = Aop (Minus | Plus | Mul) | Bop (LT | GT) or even, given a somewhat different type system, data Op = Aop | Bop where Aop = Minus | Plus | Mul Bop = LT | GT but it would seem reasonable to reflect the different types of the Ops in different types in their representations. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

On Apr 19, 2007, at 4:10 PM, Jón Fairbairn wrote:
Is there some reason why you don't want
data Op = Aop Aop | Bop Bop data Aop = Minus | Plus | Mul data Bop = LT | GT
It's a long story. The short version is that the above will complicate my AST a whole lot. I had it this way before. Thanks, Joel -- http://wagerlabs.com/

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 Jón Fairbairn wrote:
Is there some reason why you don't want
data Op = Aop Aop | Bop Bop data Aop = Minus | Plus | Mul data Bop = LT | GT
or similar? I would agree that it's a shame one cannot just write
data Op = Aop (Minus | Plus | Mul) | Bop (LT | GT)
or even, given a somewhat different type system,
data Op = Aop | Bop where Aop = Minus | Plus | Mul Bop = LT | GT
but it would seem reasonable to reflect the different types of the Ops in different types in their representations.
Slightly off-topic, I had a problem like this, only where I wanted to classify by more than one dimension: "readable?" as well as "writable?" (some were none, some both, some just readable and some just writable), so I couldn't split up the type hierarchically like that. I think I just wrote tedious functions to say whether each constructor was in each category. Isaac -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.6 (GNU/Linux) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org iD8DBQFGJ4uLHgcxvIWYTTURAkKgAJ9N998vRVsmrhHuz/zoVJaHN3nuKgCcCSmX qRFWGfKZGORAKI61J8153AI= =eVR6 -----END PGP SIGNATURE-----
participants (7)
-
Isaac Dupree
-
Joel Reymont
-
Jules Bean
-
Jón Fairbairn
-
Marc Weber
-
Neil Mitchell
-
Simon Peyton-Jones