Layout rules. (was Re: Another bug in the 98 Report?)

1999-07-01 Thread Kevin Atkinson
Malcolm Wallace wrote: > Mark P Jobes wrote: > > | Something like the following can be used in Hugs 98: > | > | f x = case x of > | (a,b) -> case a of > | (c,d) -> case b of > | (e,f) -> [c,d,e,f] > > You can't be serious! This is a great example of mis-using layout t

Re: Field names

1999-07-01 Thread Lennart Augustsson
Koen Claessen wrote: > Hello all, > > I believe the following program is valid Haskell'98: > > >>> > module Main where > > data Hash = Hash{ (#) :: Int } > deriving (Show, Read) > > main = > do print s > print (read s :: Hash) > where > s = show (Hash 3) > <<< > > The problem is the us

Field names

1999-07-01 Thread Koen Claessen
Hello all, I believe the following program is valid Haskell'98: >>> module Main where data Hash = Hash{ (#) :: Int } deriving (Show, Read) main = do print s print (read s :: Hash) where s = show (Hash 3) <<< The problem is the use of (#) as a field name. The expected output of the

Re: Another bug in the 98 Report?

1999-07-01 Thread Malcolm Wallace
First, a preface to my comments on layout processing: it seems to me that the purpose of the layout rules is to give the programmer FOWIM (Figure Out What I Mean) syntax. Hence, if it isn't immediately clear to a human reader what grouping is intended, then the layout rules are not helping. Fur

RE: Strange lexical syntax

1999-07-01 Thread Hans Aberg
At 00:59 -0700 1999/07/01, Mark P Jones wrote: >| Quick quiz: how many Haskell lexemes are represented by the following >| sequences of characters? >| >| 1) M.x >| 2) M.let >| 3)M.as >| 4) M.. >| 5) M... >| 6) M.! > >Interesting examples!

Re: Zipping two sequences together with only cons, empty, foldr

1999-07-01 Thread Lennart Augustsson
Kevin Atkinson wrote: > Ok you haskell experts. I have an interesting challenge (or maybe just > a question if you have seen it before). > > Is it possible to zip two sequences together with just: > > cons :: a -> c a -> c a > empty :: c > foldr :: (a -> b -> b) -> b -> c a -> b > > And if s

RE: Strange lexical syntax

1999-07-01 Thread Mark P Jones
Hi Simon (again!) | I just uncovered a couple of strange cases in the Haskell lexical syntax. | If you're not especially bothered about such things, don't bother to read | on! | | Quick quiz: how many Haskell lexemes are represented by the following | sequences of characters? | | 1) M

Re: Zipping two sequences together with only cons, empty, foldr

1999-07-01 Thread Kevin Atkinson
Lennart Augustsson wrote: > > Kevin Atkinson wrote: > > > Ok you haskell experts. I have an interesting challenge (or maybe just > > a question if you have seen it before). > > > > Is it possible to zip two sequences together with just: > > > > cons :: a -> c a -> c a > > empty :: c > > fold

Re: Zipping two sequences together with only cons, empty, foldr

1999-07-01 Thread Lennart Augustsson
Kevin Atkinson wrote: > > Assuming that > > you allow pairs and lambda expressions you can do it like this: > > > > caseList xs n c = > > fst (foldr (\ x (_, xs) -> (\ n c -> c x xs, x `cons` xs)) > >(\ n c -> n, empty) xs) n c > > > > zip = > > foldr (\ a g ys -> caseList

Re: Zipping two sequences together with only cons, empty, foldr

1999-07-01 Thread Laszlo Nemeth
Kevin Atkinson wrote: > cons :: a -> c a -> c a > empty :: c > foldr :: (a -> b -> b) -> b -> c a -> b I am not an expert. I have a minor problem with this, the type of empty: if c stands for a type constructor then empty should have type (c a). Moreover, I don't understand why you use 'c'

Re: Zipping two sequences together with only cons, empty, foldr

1999-07-01 Thread Kevin Atkinson
Mike Gunter wrote: > > Remember you may ONLY use the three functions given above and NOTHING > > else. Creating a list with "foldr (:) []" is also not allowed. > > Only? How do I construct a pair? (I'm probably misunderstanding you.) What I meant to say is that those three functions are the

Re: Zipping two sequences together with only cons, empty, foldr

1999-07-01 Thread Kevin Atkinson
Laszlo Nemeth wrote: > > Kevin Atkinson wrote: > > > cons :: a -> c a -> c a > > empty :: c > > foldr :: (a -> b -> b) -> b -> c a -> b > > I am not an expert. I have a minor problem with this, the type of > empty: if c stands for a type constructor then empty should have type > (c a). Ye

Re: Zipping two sequences together with only cons, empty, foldr

1999-07-01 Thread Lennart Augustsson
Kevin Atkinson wrote: > Lennart Augustsson wrote: > > > No, it will not be as efficient. foldr is not the right primitive for making > > functions on lists. You want the more general > > recurse :: (a -> c a -> b -> b) -> b -> c a -> b > > Could you give me some refrence on how that function

Re: Zipping two sequences together with only cons, empty, foldr

1999-07-01 Thread Kevin Atkinson
Lennart Augustsson wrote: > No, it will not be as efficient. foldr is not the right primitive for making > functions on lists. You want the more general > recurse :: (a -> c a -> b -> b) -> b -> c a -> b Could you give me some refrence on how that function is used as this is the first time

Re: Zipping two sequences together with only cons, empty, foldr

1999-07-01 Thread Valery Trifonov
Kevin Atkinson wrote: > > Laszlo Nemeth wrote: [snip] > > foldr (\ a g ys -> case ys of > > [] -> empty > > (b:bs) -> (a,b) `cons` g bs) > > (\ _ -> []) > > But only for lists. As you are patern matching on ":". Apply the old "predecessor" tric

Zipping two sequences together with only cons, empty, foldr

1999-07-01 Thread Kevin Atkinson
Ok you haskell experts. I have an interesting challenge (or maybe just a question if you have seen it before). Is it possible to zip two sequences together with just: cons :: a -> c a -> c a empty :: c foldr :: (a -> b -> b) -> b -> c a -> b And if so how would one do so. Remember you may

RE: Another bug in the 98 Report?

1999-07-01 Thread Mark P Jones
Hi Simon, You asked for comments, so here we go! In my opinion, it is a mistake to insist on strictly increasing indentation for nested layout. I didn't notice this change in the Haskell 98 (which is why Hugs 98 doesn't follow it!) because the posted list of changes for Haskell 98 said only tha

Re: Zipping two sequences together with only cons, empty, foldr

1999-07-01 Thread Kevin Atkinson
Lennart Augustsson wrote: > > Kevin Atkinson wrote: > > > Lennart Augustsson wrote: > > > > > No, it will not be as efficient. foldr is not the right primitive for making > > > functions on lists. You want the more general > > > recurse :: (a -> c a -> b -> b) -> b -> c a -> b > > > > Could