RE: [Haskell] Pattern Matching with rank-2 types

2006-01-23 Thread Simon Peyton-Jones
the change (or at least to comment on it). Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Bruno Oliveira | Sent: 21 January 2006 18:44 | To: Haskell Mailing List | Subject: [Haskell] Pattern Matching with rank-2 types | | Hello, | | The

[Haskell] Pattern Matching with rank-2 types

2006-01-21 Thread Bruno Oliveira
Hello, The following function is a valid function in ghc6.2.2: > func :: (forall a . [a]) -> [b] > func [] = [] However, in ghc6.4.1 it does not work anymore: Iterators4.lhs:56:6: Couldn't match `forall a. [a]' against `[a]' When checking the pattern: [] In the definition of `func':

Re: [Haskell] pattern matching on record fields and position

2005-11-02 Thread John Meacham
You might want to look at the 'get', 'set' and 'update' rules that DrIFT can derive. i made them to addres a lot of the same issues you mentioned. I personally think it is a travesty that data Foo = Foo { a :: Int, b :: Char } | Bar { a :: Int } let x = Bar { a = 4 } y = x { b = 'x'} resu

Re: [Haskell] pattern matching on record fields and position

2005-11-02 Thread Malcolm Wallace
for which have been around for years, but never adopted. There is a related language feature (extension) called "pattern guards" which /is/ implemented in ghc, and gives most of the power of views. > I'd like to be able export a data type with constructors in such a way that &

[Haskell] pattern matching on record fields and position

2005-11-02 Thread David Roundy
Hello fellow haskellers, I have a couple of related (almost conjugate) proposals/questions. Basically, I've been thinking about how to make code more robust with respect to changes in the data types. Pattern matching based on positions is very fragile (I don't think this is a surprise

Re: [Haskell] pattern matching accross instance declarations

2004-12-01 Thread S. Alexander Jacobson
My point is that I want to be able to add new toMyType definitions without having to modify some central library file and I want the compiler to warn me when I haven't defined one for each instance. -Alex- On Thu, 2 Dec 2004, Ben Rudiak-Gould wrote: > S. Alexander Jacobson wrote: > > > data M

Re: [Haskell] pattern matching accross instance declarations

2004-12-01 Thread Ben Rudiak-Gould
S. Alexander Jacobson wrote: > data MyExistantialType=forall v.(Show v)=>EType v > > class MyExistentialTypeable a where >toMyType::String->MyExistantialType > > instance MyExistentialTypeable String where >toMyType "String" = EType "foo" > > instance MyExistentialTypeable Int where

[Haskell] pattern matching accross instance declarations

2004-12-01 Thread S. Alexander Jacobson
Doing read/show on existential types would be a lot easier if pattern matching worked *accross* instance declarations and not only within them For example, this code produces an "Ambiguous type variable" GHC error, but it would be really helpful if it didn't: data MyExistanti

[Haskell] pattern matching woes

2004-11-20 Thread Ryan Paul
I recently elected to employ Haskell for my functional programming needs rather than Ocaml. Thus far, I have been relatively happy with the expressiveness and syntactic grace of Haskell, but there are a few aspects of Haskell's syntax that irritate me... In OCaml, when I am doing pattern mat

Re: pattern-matching extension?

2003-12-08 Thread Derek Elkins
ed-dispatch.lhs";, but that > > > unfortunately has the downside of requiring you to write both a > > > constructor for PACK and an instance of Packable for each type > > > you'd like to dispatch on. > > > > > > The thought occurred to me that it is

Re: pattern-matching extension?

2003-12-07 Thread Fergus Henderson
ructor for PACK and an instance of Packable for each type you'd > > like to dispatch on. > > > > The thought occurred to me that it is (intuitively) natural to do this > > via extending the pattern-matching facility to include types as well > > as literal values, i.e. some

Re: pattern-matching extension?

2003-12-06 Thread Ralf Laemmel
d dispatch on the type of its argument as well as the value. One option I've seen for this is "http://okmij.org/ftp/Haskell/class-based-dispatch.lhs";, but that unfortunately has the downside of requiring you to write both a constructor for PACK and an instance of Packable for each

Re: pattern-matching extension?

2003-12-05 Thread Bernard James POPE
Abe writes: > The thought occurred to me that it is (intuitively) natural to do this via > extending the pattern-matching facility to include types as well as > literal values, i.e. something like: > > f :: a -> String > f (a :: Int) = "got an int, incremented: "

Re: pattern-matching extension?

2003-12-05 Thread Derek Elkins
; like to dispatch on. > > The thought occurred to me that it is (intuitively) natural to do this > via extending the pattern-matching facility to include types as well > as literal values, i.e. something like: > > f :: a -> String > f (a :: Int) = "got an int, incremented

pattern-matching extension?

2003-12-05 Thread Abraham Egnor
atch.lhs";, but that unfortunately has the downside of requiring you to write both a constructor for PACK and an instance of Packable for each type you'd like to dispatch on. The thought occurred to me that it is (intuitively) natural to do this via extending the pattern-matching facility

Re: Exhaustive Pattern-Matching

2003-08-29 Thread Marcin 'Qrczak' Kowalczyk
Dnia czw 28. sierpnia 2003 16:37, Frank Atanassow napisał: > SML has the same limitations w.r.t. guards as Haskell; Haskell > compilers can and do check exhaustiveness, but not redundancy because > matches are tried sequentially. I believe SML matching is also > sequential. If there is a differenc

Re: Exhaustive Pattern-Matching

2003-08-29 Thread Andrew J Bromage
G'day all. On Wed, Aug 27, 2003 at 04:57:27PM +0100, Simon Marlow wrote: > GHC tries to do so, but sometimes gets it wrong. See the > -fwarn-incomplete-patterns flag. We'd appreciate it if someone could > overhaul this code - it's been on the wish list for a long time. As a matter of curiosity

Re: Exhaustive Pattern-Matching

2003-08-28 Thread Frank Atanassow
On Thursday, Aug 28, 2003, at 08:47 Europe/Amsterdam, Steffen Mazanek wrote: Thank you all for your help. I will try this ghc-flag. It is interesting as well, that in contrast to Haskell Standard ML ensures, that pattern-matches are exhaustive and irredundant. SML has the same limitations w.r.t.

Re: Exhaustive Pattern-Matching

2003-08-28 Thread Steffen Mazanek
Thank you all for your help. I will try this ghc-flag. It is interesting as well, that in contrast to Haskell Standard ML ensures, that pattern-matches are exhaustive and irredundant. Ciao, Steffen ___ Haskell mailing list [EMAIL PROTECTED] http://www.has

Re: Exhaustive Pattern-Matching

2003-08-27 Thread Iavor Diatchki
hello, Steffen Mazanek wrote: Hello, I have a question about pattern-matching. In the Haskell-report it is not postulated, that pattern matching has to be exhaustive. Would it be possible at all to implement an algorithm, which checks Haskell-style patterns for exhaustiveness? What kinds of

RE: Exhaustive Pattern-Matching

2003-08-27 Thread Simon Marlow
> I have a question about pattern-matching. In the Haskell-report it is > not postulated, that > pattern matching has to be exhaustive. Would it be possible at all to > implement an > algorithm, which checks Haskell-style patterns for > exhaustiveness? What > kinds of

Exhaustive Pattern-Matching

2003-08-27 Thread Steffen Mazanek
Hello, I have a question about pattern-matching. In the Haskell-report it is not postulated, that pattern matching has to be exhaustive. Would it be possible at all to implement an algorithm, which checks Haskell-style patterns for exhaustiveness? What kinds of complication can be expected

Re: Completeness of pattern matching

2002-12-06 Thread Ketil Z. Malde
[EMAIL PROTECTED] (Ketil Z. Malde) writes: > Malcolm Wallace <[EMAIL PROTECTED]> writes: > > > Ingo Wechsung <[EMAIL PROTECTED]> writes: > >> I wonder if the compiler could check, if all possible combinations have > >> been checked in a pattern match. > > > In ghc, use the compile-time option -f

Re: slightly too(?) complex list pattern matching

2002-06-18 Thread Yoann Padioleau
Hal Daume III <[EMAIL PROTECTED]> writes: > Hi all, > > I don't think I can do this, but I figured I'd ask anyway. Suppose I > have: > > > data X = X | Y | Z > > and I want to match against a list of Xs. But all I want is to ensure > that there's a Y followed by a Z, but I don't care if ther

Re: pattern-matching with labelled types

2002-03-08 Thread Jorge Adriano
On Friday 08 March 2002 01:52, you wrote: > Andre W B Furtado writes: > | Of course, it is possible to do something like > | > | > update :: MyType -> Int -> MyType > | > update mt newValue = MT {x = newValue, y = oldValue} > | > where oldValue = y mt > | > | but this really annoys me w

pattern-matching with labelled types

2002-03-07 Thread Tom Pledger
Andre W B Furtado writes: : | Of course, it is possible to do something like | | > update :: MyType -> Int -> MyType | > update mt newValue = MT {x = newValue, y = oldValue} | > where oldValue = y mt | | but this really annoys me when MyType has too many fields. Suggestions? update

pattern-matching with labelled types

2002-03-07 Thread Andre W B Furtado
If I have: > data MyType = MT { > x :: Int, > y :: Char > } How do I update the Int value of MyType leaving the Char value unaffected? I tryied something like: > MT {x = newValue} but GHC gave me a warning about the Char value and it indeed caused strange effects. Of course, it is

Re: Problem with 'nested' pattern matching

2002-02-01 Thread Rijk J . C . van Haaften
carlos wrote: Hello. I'm having some trouble trying to understand exactly what's behind the rule for pattern-matching with data constructors. The code I'm having trouble with is similar to this: f (C p1 p2 (C2 p3 p4)) = ... f _ = False What happens is if f is calle

Problem with 'nested' pattern matching

2002-01-31 Thread carlos . scheidegger
Hello. I'm having some trouble trying to understand exactly what's behind the rule for pattern-matching with data constructors. The code I'm having trouble with is similar to this: f (C p1 p2 (C2 p3 p4)) = ... f _ = False What happens is if f is called with (C p1 p2 (NOT_C2

Re: newtype pattern matching

2002-01-25 Thread Jan-Willem Maessen
I think one crucial point is being lost in the ongoing discussion of pattern-matching and newtype: newtype is supposed permit *erasure* of construction and pattern matching. There is *no runtime cost* because the type disappears at compile time. Even a non-optimising Haskell

Re: newtype pattern matching

2002-01-25 Thread David Feuer
case x of C2 x' -> x') (case y of C2 y' -> y')) in the general case where we want to preserve strictness and don't want to analyze it ourselves. Newtypes allow to use the convenient syntax of pattern matching on the lhs. - Surely you could just wri

Re: newtype pattern matching

2002-01-25 Thread Marcin 'Qrczak' Kowalczyk
; y')) in the general case where we want to preserve strictness and don't want to analyze it ourselves. Newtypes allow to use the convenient syntax of pattern matching on the lhs. -- __("< Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/ \__/ ^^ QRCZAK __

Re: newtype pattern matching

2002-01-24 Thread Martin Norbäck
ems that > > newtype T1 [a1 a2 ...] = C1 ... > is the same as > data T2 [a1 a2 ...] = C2 !... !... !... > > Except that pattern matching on C1 is like lazy pattern matching on C2. > Since newtype is supposed to be about efficiency, I am trying to > understand what makes this more ef

Re: newtype pattern matching

2002-01-24 Thread Feuer
...] = C2 !... !... !... Except that pattern matching on C1 is like lazy pattern matching on C2. Since newtype is supposed to be about efficiency, I am trying to understand what makes this more efficient. I have not yet seen any explanation of this. On 22 Jan 2002, Martin [ISO-8859-1] Norbäck wrote: > t

RE: H98 Report: semantics of pattern matching

2002-01-24 Thread Simon Peyton-Jones
| From: Ross Paterson [mailto:[EMAIL PROTECTED]] | Sent: 21 January 2002 17:20 | To: [EMAIL PROTECTED] | Subject: H98 Report: semantics of pattern matching | | | In section 3.17 Pattern Matching, there are some | inconsistencies between the informal and formal semantics: Tbanks very much

Re: newtype pattern matching

2002-01-22 Thread Martin Norbäck
tis 2002-01-22 klockan 15.52 skrev Feuer: > Why is pattern matching on newtypes lazy? Does this add to efficiency > somehow? If not, it seems to be just another rule to keep straight. That's the difference between newtype and data. Newtypes are unboxed, so there is no constructor

newtype pattern matching

2002-01-22 Thread Feuer
Why is pattern matching on newtypes lazy? Does this add to efficiency somehow? If not, it seems to be just another rule to keep straight. ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

H98 Report: semantics of pattern matching

2002-01-21 Thread Ross Paterson
In section 3.17 Pattern Matching, there are some inconsistencies between the informal and formal semantics: (1) Section 3.17.2 Informal Semantics of Pattern Matching needs an extra rule (before rule 2): Matching _|_ against the pattern con pat, where con is a constructor defined

Re: Pattern matching

2000-06-21 Thread Lennart Augustsson
Simon Peyton-Jones wrote: > In Haskell, > case e of { y->b } > is equivalent to > let y=e in b Actually, it's equivalent to (\ y -> b) e since the let could be polymorphic. > That is, case is not strict unless the patterns > make it so. You may think it's curious but that's

RE: Pattern matching

2000-06-21 Thread Simon Peyton-Jones
| 1) In Figure 3 (Semantics of Case Expressions, Part 1) clause c reads: | | case v of { p | g1 -> e1 ; ... | | gn -> en where { decls } | _ -> e' } | | = case e' of | { y -> -- (where y is a completely new variable) | case v of { |p

Pattern matching

2000-06-20 Thread Tommy Thorn
I've looked at the pattern matching semantics as defined in the Haskell 98 report and there is few things I don't understand. 1) In Figure 3 (Semantics of Case Expressions, Part 1) clause c reads: case v of { p | g1 -> e1 ; ... | gn ->

Re: Pattern Matching syntax

1998-09-11 Thread Sigbjorn Finne
Hi, using list comprehensions for the kind filter&map operation you're wanting to express, seems like a good option. border p = check "no border in page" [ x | (Border x) <- p] margin p = check "no margin in page" [ x | (Margin x) <- p] check :: String -> [a] -> a check err_msg []=

Pattern Matching syntax

1998-09-11 Thread S. Alexander Jacobson
I am building a description of page state using a list of pageStyles > data PageStyle=Orientation Orient > | Margin BoxData > | Border BoxData > | CurrentYPos Float > | CurrentXPos Float To extract particular items from the

Opinion poll: Strict vs lazy pattern matching

1997-12-06 Thread John Hughes
The Standard Haskell committee is debating a possible modification to the semantics of pattern matching; the goal is to make the language simpler, but the cost is an incompatible change to a basic part of the semantics. To help us weigh up the cost against the benefit, we'd like to pol

Re: Pattern matching for solitary constructors

1996-11-04 Thread Fergus Henderson
[EMAIL PROTECTED] wrote: > data D2 = D2 Int Int > > d2 (D2 i1 i2) = 42 > > d2' ~(D2 i1 i2) = 42 [...] > If d2 (D2 undefined undefined) == 42, we have to implement d2 in the > same (less efficient) way that we implement d2' under the current > semantics. How do you implement d2', and why

Re: Pattern matching for solitary constructors

1996-11-03 Thread Sverker Nilsson
> As far as I > can see, this change of semantics doesn't break any existing code; it just > executes it a little more lazily. Maybe that will make some existing code get space-leaks. Sverker

Re: Pattern matching for solitary constructors

1996-11-02 Thread reid-alastair
Marnix Klooster <[EMAIL PROTECTED]> writes: > I have a question on 'solitary constructors'; such a constructor is > the only one in its data type. It appears to me that pattern matching > using these constructors can be more lazy. To give an example from >

Pattern matching for solitary constructors

1996-11-01 Thread Marnix Klooster
Hello, I have a question on 'solitary constructors'; such a constructor is the only one in its data type. It appears to me that pattern matching using these constructors can be more lazy. To give an example from the Haskell 1.3 report, with data D1 = D1 Int d1 (D1 i) = 42 cur

Re: bad pattern-matching

1992-11-10 Thread kh
> > Changing the above definition like this: > > nfib 0 = 1 > nfib 1 = 1 > nfib n = nfib (n - 2) + nfib (n - 1) + 1 > > > main = print (nfib 30) > > > results in 2692537 in 142 seconds. > > I think, that is not a desirable implementation >

Re: bad pattern-matching

1992-11-10 Thread Ian Poole
> .. > > But I do not want to program without using the > well-known advantages of such patterns: > > - increased readability > - distinct left-hand-sides Personally I find the second form (ie without n+k patterns) the easier to read, and I've

bad pattern-matching

1992-11-10 Thread Marc Rehmsmeier
= 1 nfib n = nfib (n - 2) + nfib (n - 1) + 1 main = print (nfib 30) results in 2692537 in 142 seconds. I think, that is not a desirable implementation of pattern-matching. To speed up my programs, therefore, I have to avoid (n+k)-patterns. In Miranda the definition using (n+2) is faster (166

Semantics of Irrefutable Pattern Matching

1992-07-23 Thread smk
tter -- matching is side-effect-free. SNA But, SNA When (1,2) is pattern matched with (a,b) for the first time , SNA bindings for both a and b can be created. So when x2'is needed, SNA pattern matching need not be done - the binding created SNA during the first pattern

Re: Semantics of Irrefutable Pattern Matching

1992-07-23 Thread Simon L Peyton Jones
Namrata asks... | So, when x1' + x2' is evaluated, | Is (1,2) pattern matched against (a,b) twice -- once for x1' and once | for x2' ?? The translation you give (correctly I think) expresses the required *semantics*. But the translation is not the required *implementation*. A compiler can do

Semantics of Irrefutable Pattern Matching

1992-07-23 Thread Shah Namrata Abhaykumar
The semantics of irrefutable pattern matching is given as, case e0 of { ~p -> e ; _ -> e' } = let { y = e0 } in let { x1' = case y of { p -> x1 } } in ... let { xn' = case y of { p -> xn } } in e[x1'

Lazy data structures and irrefutable pattern matching

1992-03-31 Thread Paul Hudak
arguments along the lines of "separating data from control", "allowing infinite data structures", etc. But, there is no "proof" that we need them. Indeed, there is no "proof" that we need data structures at all (:-). Besides I/O where do we need irrefutable

Pattern-matching (was Re: LHSes -- SYNTAX only)

1992-01-30 Thread haskell-request
number of gotcha's associated with pattern-matching. A while back on the list, there was some discussion of the fact that overloaded functions can lead to bizarre interactions with pattern-matching, e.g. + can be overloaded so that it is not associative, or that - is not its inverse, etc. So