Re: [Haskell-cafe] Code walking off the right edge of the screen

2009-06-25 Thread Stephan Friedrichs
Henning Thielemann wrote:
 [...]
 
 http://haskell.org/haskellwiki/Case

Maybe we (i. e. someone with a wiki account ;) ) should add Jeremy's
proposal - using let and guards - to the page (under section 2.2,
syntactic suger)? IMHO this is much clearer than case () of _.

foo =
let x | 1  1 = uh-oh
  | otherwise = all is well
in x

Regards,
Stephan

-- 

Früher hieß es ja: Ich denke, also bin ich.
Heute weiß man: Es geht auch so.

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


Re: [Haskell-cafe] Code walking off the right edge of the screen

2009-06-25 Thread Alberto G. Corona
What about extending haskell (or ghc) with mixfix operators, Agda style?. At
first sigth it would permit the creation of custom control structures and
perhaps more readable DSLs.

2009/6/25 Stephan Friedrichs deduktionstheo...@web.de

 Henning Thielemann wrote:
  [...]
 
  http://haskell.org/haskellwiki/Case

 Maybe we (i. e. someone with a wiki account ;) ) should add Jeremy's
 proposal - using let and guards - to the page (under section 2.2,
 syntactic suger)? IMHO this is much clearer than case () of _.

 foo =
let x | 1  1 = uh-oh
  | otherwise = all is well
in x

 Regards,
 Stephan

 --

 Früher hieß es ja: Ich denke, also bin ich.
 Heute weiß man: Es geht auch so.

  - Dieter Nuhr
 ___
 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] Code walking off the right edge of the screen

2009-06-24 Thread Henning Thielemann
Deniz Dogan schrieb:
 2009/6/20 Stephan Friedrichs deduktionstheo...@web.de:
 Deniz Dogan wrote:
 I (too) often find myself writing code such as this:

 if something
   then putStrLn howdy there!
   else if somethingElse
   then putStrLn howdy ho!
   else ...

 [...]

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


Re: [Haskell-cafe] Code walking off the right edge of the screen

2009-06-21 Thread Claus Reinke

I (too) often find myself writing code such as this:

if something
 then putStrLn howdy there!
 else if somethingElse
 then putStrLn howdy ho!
 else ...


1. recognize something odd. done.
2. look for improvements. good.
3. define suitable abstractions for your special case
4. look for general abstractions covering the special case


I recall reading some tutorial about how you can use the Maybe monad
if your code starts looking like this, but as you can see, that
doesn't really apply here. something and somethingElse are simply
booleans and each of them have different actions to take if either of
them is True.


Maybe, or MaybeT (a monad transformer adding Maybe-style
functionality to your base monad, in this case IO) can be used here
as well, but may not be the first choice. As has been pointed out,
guards would seem to cover your use case:

e something somethingElse
 | something = putStrLn howdy there!
 | somethingElse = putStrLn howdy ho!
 | otherwise = putStrLn hmm.. hi?

If you need something more, you can define your own abstractions
to cover the repeated patterns in your code. Perhaps a function to
select one of a list of (condition,action) pairs:

g something somethingElse = oneOf
 [(something, putStrLn howdy there!)
 ,(somethingElse, putStrLn howdy ho!)
 ,(otherwise, putStrLn hmm.. hi?)
 ]
 where oneOf = foldr (\(c,a) r-if c then a else r) (error no match in oneOf)

or some combinators for alternatives of guarded actions instead

h something somethingElse =
 (something -: putStrLn howdy there!)
 `orElse`
 (somethingElse -: putStrLn howdy ho!)
 `orElse`
 (otherwise -: putStrLn hmm.. hi?)
 where
 c -: a  = when c a  return c
 a `orElse` b = a = \ar- if ar then return True else b

Now, the former can be quite sufficient for many situations, but it
doesn't quite feel like a general solution, and the latter clearly shows
the dangers of defining your own abstractions: if you overdo it, anyone
reading your code will need a translator!-) Which is where the search
for general abstractions comes in - we're looking for something that
will not only cover this special use case, but will be more generally
useful, in a form that only needs to be understand once (not once per
project).

And that brings us to things like MonadPlus: you don't have to use
the Monad combinator for sequencing, but if you do (as in IO),
then it is natural to ask for a second combinator, for alternatives.
Now, IO itself doesn't have a MonadPlus instance, but we can
use a monad transformer to add such functionality. Using MaybeT,
that will be similar to version 'h' above:

i something somethingElse = runMaybeT $
 (guard something  lift (putStrLn howdy there!))
 `mplus`
 (guard somethingElse  lift (putStrLn howdy ho!))
 `mplus`
 (   lift (putStrLn hmm.. hi?))

and it can also be used for related patterns, such as running
a sequence of actions until the first failure:

j something somethingElse = runMaybeT $ do
 (guard something  lift (putStrLn howdy there!))
 (guard somethingElse  lift (putStrLn howdy ho!))
 (   lift (putStrLn hmm.. hi?))

or other combinations of these two patterns.

MaybeT is not the only possibility, and not always the best,
but Maybe is perhaps the best known instance of MonadPlus
(and the only thing that needs to change to use other MonadPlus
instances is the 'runMaybeT').

Hth,
Claus

PS. for a more extensive example of MaybeT vs indentation creep, see 
http://www.haskell.org/haskellwiki/Equational_reasoning_examples#Coding_style:_indentation_creep_with_nested_Maybe


---
data MaybeT m a = MaybeT { runMaybeT :: m (Maybe a) }

instance Monad m = Monad (MaybeT m) where
 return  = MaybeT . return . Just
 a = b = MaybeT $ runMaybeT a = maybe (return Nothing) (runMaybeT . b)
 fail msg= mzero

instance Monad m = MonadPlus (MaybeT m) where
 mzero   = MaybeT $ return Nothing
 a `mplus` b = MaybeT $ runMaybeT a = maybe (runMaybeT b) (return . Just)

instance MonadTrans MaybeT where
 lift m = MaybeT $ m = return . Just


main = do
 putStrLn e:  mapM_ (uncurry e) args
 putStrLn f:  mapM_ (uncurry f) args
 putStrLn g:  mapM_ (uncurry g) args
 putStrLn h:  mapM_ (uncurry h) args
 putStrLn i:  mapM_ (uncurry i) args
 putStrLn j:  mapM_ (uncurry j) args
 where args = [(x,y)|x-[True,False],y-[True,False]]





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


[Haskell-cafe] Code walking off the right edge of the screen

2009-06-20 Thread Deniz Dogan
I (too) often find myself writing code such as this:

if something
  then putStrLn howdy there!
  else if somethingElse
  then putStrLn howdy ho!
  else ...

I recall reading some tutorial about how you can use the Maybe monad
if your code starts looking like this, but as you can see, that
doesn't really apply here. something and somethingElse are simply
booleans and each of them have different actions to take if either of
them is True.

So how do I make code like this prettier?

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


Re: [Haskell-cafe] Code walking off the right edge of the screen

2009-06-20 Thread Stephan Friedrichs
Deniz Dogan wrote:
 I (too) often find myself writing code such as this:
 
 if something
   then putStrLn howdy there!
   else if somethingElse
   then putStrLn howdy ho!
   else ...
 
 [...]
 
 So how do I make code like this prettier?

If it's a function, you can use guards:

foo :: ...
foo something somethingElse
| something - putStrLn howdy there!
| somethingElse - putStrLn howdy ho!
| otherwise - ...

-- 

Früher hieß es ja: Ich denke, also bin ich.
Heute weiß man: Es geht auch so.

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


Re: [Haskell-cafe] Code walking off the right edge of the screen

2009-06-20 Thread Jeremy Shaw
At Sat, 20 Jun 2009 20:45:16 +0200,
Stephan Friedrichs wrote:

 If it's a function, you can use guards:
 
 foo :: ...
 foo something somethingElse
 | something - putStrLn howdy there!
 | somethingElse - putStrLn howdy ho!
 | otherwise - ...

You can also artificially introduce places to use gaurds inside a function:

foo =
let x | 1  1 = uh-oh
  | otherwise = all is well
in x

bar =
case () of
  _ | 1  1 - uh-oh
| otherwise - all is well

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


Re: [Haskell-cafe] Code walking off the right edge of the screen

2009-06-20 Thread Antoine Latter
On Sat, Jun 20, 2009 at 1:05 PM, Deniz Dogandeniz.a.m.do...@gmail.com wrote:
 I (too) often find myself writing code such as this:

 if something
  then putStrLn howdy there!
  else if somethingElse
          then putStrLn howdy ho!
          else ...

 I recall reading some tutorial about how you can use the Maybe monad
 if your code starts looking like this, but as you can see, that
 doesn't really apply here. something and somethingElse are simply
 booleans and each of them have different actions to take if either of
 them is True.

 So how do I make code like this prettier?

I'm not entirely sure if this is haskell'98, but GHC seems to support
this sort of layout:


main = do
  some computation

  if something then someOtherComputation else do

  continue at the same indentation


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


Re: [Haskell-cafe] Code walking off the right edge of the screen

2009-06-20 Thread Daniel Peebles
The when and unless functions might come in handy too (both have type
forall (m :: * - *). (Monad m) = Bool - m () - m ())

On Sat, Jun 20, 2009 at 2:05 PM, Deniz Dogandeniz.a.m.do...@gmail.com wrote:
 I (too) often find myself writing code such as this:

 if something
  then putStrLn howdy there!
  else if somethingElse
          then putStrLn howdy ho!
          else ...

 I recall reading some tutorial about how you can use the Maybe monad
 if your code starts looking like this, but as you can see, that
 doesn't really apply here. something and somethingElse are simply
 booleans and each of them have different actions to take if either of
 them is True.

 So how do I make code like this prettier?

 Thanks,
 Deniz Dogan
 ___
 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] Code walking off the right edge of the screen

2009-06-20 Thread Jochem Berndsen
Antoine Latter wrote:
 On Sat, Jun 20, 2009 at 1:05 PM, Deniz Dogandeniz.a.m.do...@gmail.com wrote:
 I (too) often find myself writing code such as this:

 if something
  then putStrLn howdy there!
  else if somethingElse
  then putStrLn howdy ho!
  else ...

 I recall reading some tutorial about how you can use the Maybe monad
 if your code starts looking like this, but as you can see, that
 doesn't really apply here. something and somethingElse are simply
 booleans and each of them have different actions to take if either of
 them is True.

 So how do I make code like this prettier?
 
 I'm not entirely sure if this is haskell'98, but GHC seems to support
 this sort of layout:
 
 main = do
   some computation
 
   if something then someOtherComputation else do
 
   continue at the same indentation
 

IMHO, this is ugly and counterintuitive; I like having a single point
of exit (to use an imperative programming term) of a function. Your
suggestion is equivalent to

someComputation;
if something then begin
someOtherComputation;
exit;
end;
more;

in, say, Pascal. This obscures the fact that more; is sometimes/often
not executed. (You could argue the same about exceptions, but they are a
necessary evil ;-).

Regards,

-- 
Jochem Berndsen | joc...@functor.nl
GPG: 0xE6FABFAB
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Code walking off the right edge of the screen

2009-06-20 Thread Brandon S. Allbery KF8NH

On Jun 20, 2009, at 14:05 , Deniz Dogan wrote:

if something
 then putStrLn howdy there!
 else if somethingElse
 then putStrLn howdy ho!
 else ...


FWIW, when I see this I generally start looking for a higher order way  
to express it.  The monoid instance for lists can be a good start.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe