[Haskell-cafe] Re: Problems interpreting

2006-09-18 Thread Jón Fairbairn
Andrea Rossato [EMAIL PROTECTED] writes:

 On Mon, Sep 18, 2006 at 04:16:55AM -0700, Carajillu wrote:
  
  Wow! I'm starting to love this languaje, and the people who uses it!:)
  
 
 You spoke too early. My code had a bug, a huge one...
 
 this is the right one:
 
 -- Replaces a wildcard in a list with the list given as the third argument
 substitute :: Eq a = a - [a] - [a] - [a]
 substitute e l1 l2= [c | c - check_elem l1]
 where check_elem [] = l1
   check_elem (x:xs) = if x == e then (l2 ++ xs) else [x] ++ 
 check_elem xs


I think it's nicer to do it like this:

   substitute e l l'
   = concat (map subst_elem l)
 where subst_elem x
   | x == e = l'
   | otherwise = [x]

since subst_elem has a more straightforward meaning than
check_elem, and the concatenation is handled by a well
known standard function.

Also, it would usually be more useful to have the argument
to replace /with/ before the argument to replace /in/, so
that (substitute '*' wurble) is a function that replaces
all the '*'s in it's argument with wurbles.

And if you do that, you can write it like this:

   subst e l'
   = concat . map subst_elem
 where subst_elem x
   | x == e = l'
   | otherwise = [x]

-- 
Jón Fairbairn [EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Problems interpreting

2006-09-18 Thread Andrea Rossato
On Mon, Sep 18, 2006 at 12:42:59PM +0100, Jón Fairbairn wrote:
 And if you do that, you can write it like this:
 
subst e l'
= concat . map subst_elem
  where subst_elem x
| x == e = l'
| otherwise = [x]

Pretty. Just to many keystrokes.
This should take two keystrokes less, probably:

subst e l [] = []
subst e l (x:xs) = if x == e then l ++ xs else x : subst e l xs

;-)
andrea
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Re: Problems interpreting

2006-09-18 Thread Bulat Ziganshin
Hello Andrea,

Monday, September 18, 2006, 4:23:21 PM, you wrote:

subst e l'
= concat . map subst_elem
  where subst_elem x
| x == e = l'
| otherwise = [x]

 Pretty. Just to many keystrokes.
 This should take two keystrokes less, probably:

 subst e l [] = []
 subst e l (x:xs) = if x == e then l ++ xs else x : subst e l xs

but the goal is not keystrokes itself but easy of understanding. for
me, first solution looks rather idiomatic and intuitively
understandable. second solution requires more time to got it, but
seems easier for novices that are not yet captured higher-level
Haskell idioms. i just want to said that it will be easier to read it
if you split it into several lines:

subst e l [] = []
subst e l (x:xs) = if x == e
 then l ++ xs
 else x : subst e l xs

or

subst e l [] = []
subst e l (x:xs) | x==e  = l ++ xs
 | otherwise = x : subst e l xs

and that your solution substitutes only first match in a list:

subst 1 [1,1] [0] = [0,1]


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Problems interpreting

2006-09-18 Thread Andrea Rossato
On Mon, Sep 18, 2006 at 04:52:33PM +0400, Bulat Ziganshin wrote:
 but the goal is not keystrokes itself but easy of understanding. for
 me, first solution looks rather idiomatic and intuitively
 understandable. second solution requires more time to got it, but
 seems easier for novices that are not yet captured higher-level
 Haskell idioms. 

I was obviously kidding, as the ;-) should have made clear.
;-)

Apart for the bug (I did not understand that all the occurrences should
be replaced) I wrote something that was as close as possible to
Albert's first attempt.

For the rest, I completely agree with you and find the second one
a lot easier...

Andrea 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Problems interpreting

2006-09-18 Thread Jón Fairbairn
Andrea Rossato [EMAIL PROTECTED] writes:

 On Mon, Sep 18, 2006 at 12:42:59PM +0100, Jón Fairbairn wrote:
  And if you do that, you can write it like this:
  
 subst e l'
 = concat . map subst_elem
   where subst_elem x
 | x == e = l'
 | otherwise = [x]
 
 Pretty. Just to many keystrokes.

Keystrokes? Learn to touchtype!

 This should take two keystrokes less, probably:
 
 subst e l [] = []
 subst e l (x:xs) = if x == e then l ++ xs else x : subst e l xs

but if you want short, do this:

 subst e l' = concat.map (\x-if x==e then l' else [x])

which beats yours by twenty seven characters and one bug ;-P

-- 
Jón Fairbairn [EMAIL PROTECTED]
http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html  (updated 2006-09-13)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Problems interpreting

2006-09-18 Thread Neil Mitchell

Hi


subst e l' = concat.map (\x-if x==e then l' else [x])


subst e l' = concatMap (\x-if x==e then l' else [x])

Let's save an extra character :)

Thanks

Neil
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Problems interpreting

2006-09-18 Thread Joachim Breitner
Hi,

Am Montag, den 18.09.2006, 16:00 +0100 schrieb Neil Mitchell:
  subst e l' = concat.map (\x-if x==e then l' else [x])
 subst e l' = concatMap (\x-if x==e then l' else [x])
 Let's save an extra character :)
We are talking keystrokes here, so count the shift key!

Greetings,
Joachim
-- 
Joachim Breitner
  e-Mail: [EMAIL PROTECTED]
  Homepage: http://www.joachim-breitner.de
  ICQ#: 74513189
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Problems interpreting

2006-09-18 Thread wld

Hi,
On 9/18/06, Joachim Breitner [EMAIL PROTECTED] wrote:

Hi,

Am Montag, den 18.09.2006, 16:00 +0100 schrieb Neil Mitchell:
  subst e l' = concat.map (\x-if x==e then l' else [x])
 subst e l' = concatMap (\x-if x==e then l' else [x])
 Let's save an extra character :)
We are talking keystrokes here, so count the shift key!

Greetings,
Joachim


Sorry, couldn't resist... If we *really* talking keystrokes, it much
depends on auto-completion features of your editor! :)

V.Rudenko
--
λ is the ultimate
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Problems interpreting

2006-09-18 Thread Lennart Augustsson

Or even shorter:

subst e l = concatMap $ \x-if x==e then l else [x]

I kinda like the list comprehension version too

subst e l1 l2 = [ r | x - l2, r - if x==e then l1 else [x] ]


On Sep 18, 2006, at 10:54 , Jón Fairbairn wrote:


Andrea Rossato [EMAIL PROTECTED] writes:


On Mon, Sep 18, 2006 at 12:42:59PM +0100, Jón Fairbairn wrote:

And if you do that, you can write it like this:

   subst e l'
   = concat . map subst_elem
 where subst_elem x
   | x == e = l'
   | otherwise = [x]


Pretty. Just to many keystrokes.


Keystrokes? Learn to touchtype!


This should take two keystrokes less, probably:

subst e l [] = []
subst e l (x:xs) = if x == e then l ++ xs else x : subst e l xs


but if you want short, do this:


subst e l' = concat.map (\x-if x==e then l' else [x])


which beats yours by twenty seven characters and one bug ;-P

--  
Jón Fairbairn  
[EMAIL PROTECTED]
http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html  (updated  
2006-09-13)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Problems interpreting

2006-09-18 Thread Neil Mitchell

Hi,

Out of curiosity, I've been developing a tool called Dr Haskell, for a
sample run:


module Test where

substitute1 :: Eq a = a - [a] - [a] - [a]
substitute1 e l1 l2= [c | c - check_elem l1]
  where check_elem [] = l1
check_elem (x:xs) = if x == e then (l2 ++ xs) else [x] ++ check_elem xs


substitute2 e l l'
 = concat (map subst_elem l)
   where subst_elem x
 | x == e = l'
 | otherwise = [x]

subst3 e l [] = []
subst3 e l (x:xs) = if x == e then l ++ xs else x : subst3 e l xs


subst4 e l' = concat.map (\x-if x==e then l' else [x])



drhaskell Test.hs


I can apply Hints.concat_map in Test.subst4
I can apply Hints.concat_map in Test.substitute2
I can apply Hints.box_append in Test.Test.Prelude.200.check_elem

For the curious, see the darcs repo:

http://www.cs.york.ac.uk/fp/darcs/drhaskell/

(Requires Yhc)

Thanks

Neil

PS. dons also contributed some of the earlier discussion to this tool,
so deserves some credit.


On 9/18/06, wld [EMAIL PROTECTED] wrote:

Hi,
On 9/18/06, Joachim Breitner [EMAIL PROTECTED] wrote:
 Hi,

 Am Montag, den 18.09.2006, 16:00 +0100 schrieb Neil Mitchell:
   subst e l' = concat.map (\x-if x==e then l' else [x])
  subst e l' = concatMap (\x-if x==e then l' else [x])
  Let's save an extra character :)
 We are talking keystrokes here, so count the shift key!

 Greetings,
 Joachim

Sorry, couldn't resist... If we *really* talking keystrokes, it much
depends on auto-completion features of your editor! :)

V.Rudenko
--
λ is the ultimate

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Problems interpreting

2006-09-18 Thread Aaron Denney
On 2006-09-18, Jón Fairbairn [EMAIL PROTECTED] wrote:
 Andrea Rossato [EMAIL PROTECTED] writes:

 On Mon, Sep 18, 2006 at 12:42:59PM +0100, Jón Fairbairn wrote:
  And if you do that, you can write it like this:
  
 subst e l'
 = concat . map subst_elem
   where subst_elem x
 | x == e = l'
 | otherwise = [x]
 
 Pretty. Just to many keystrokes.

 Keystrokes? Learn to touchtype!

One has only a finite number of keystrokes before one's hands give out.
Use them wisely.

-- 
Aaron Denney
--

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Problems interpreting

2006-09-18 Thread Sam Pointon

On 18/09/06, Aaron Denney [EMAIL PROTECTED] wrote:

One has only a finite number of keystrokes before one's hands give out.
Use them wisely.


i agr rdndncy = bd  shd b stmpd out wsts bndwth 2

Slightly more seriously, a few extra keystrokes can -really- improve
clarity. For example, you can write English and still be understood
(reasonably) well without most of the vowels. But how on Earth do you
interpret ld mn gd t shp? Or any Perl/Ruby/whatever golf entry?

I'd rather waste keystrokes writing clearer code than brain cycles
understanding obfuscated code, personally.

--Sam
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Problems interpreting

2006-09-18 Thread Andrea Rossato
On Mon, Sep 18, 2006 at 11:04:27AM -0400, Lennart Augustsson wrote:
 Or even shorter:
 
 subst e l = concatMap $ \x-if x==e then l else [x]
 
 I kinda like the list comprehension version too
 
 subst e l1 l2 = [ r | x - l2, r - if x==e then l1 else [x] ]

This is the version I first wanted to (try to) implement (improvements
thanks to the thread, obviously :-):

newtype SF a b = SF { runSF :: [a] - [b] } 
instance Arrow SF where
arr f = SF (map f)
SF f  SF g = SF (f  g)
first (SF f) = SF (unzip  first f  uncurry zip)

substitute e l = arr (\x-if x==e then l else [x])  SF concat

I was studying Hughes when I read the first mail of this thread. But
you can see it yourself...

Andrea
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe