Re: [Haskell-cafe] haskell programming guidelines

2006-02-28 Thread John Meacham
On Tue, Feb 28, 2006 at 04:52:40AM -0500, Cale Gibbard wrote:
> > -- collect error messages from all failing parsers
> > [ err | Left err <- map parse xs]
> 
> I don't see how you lose this one at all.

because somewhere else, you might want to use 'parse' as a maybe.
somewhere else, you might want it to throw an IO exception, somewhere
else you might want to compose it with some other arbitrary monad and
not loose the ability to override the return type.

> > -- look up a string transformed by a map in another map, failing if it
> > -- is not in said other map.
> > runIdentity $ Map.lookup (concatMap (`Map.lookup` map) xs) smap
> 
> Suppose Map.lookup returns something in the Maybe monad.
> 
> let lookup k m = fromJust $ Map.lookup k m
> in lookup (map (`lookup` m) xs) sm

and then in 2 months you get a 
"Predule.error: fromJust"

but moreso, you may define a value like so 
> z = Map.lookup (concatMap (`Map.lookup` map) xs) smap

now z can be used for any sort of monad. very handy.

The need for partial functions like fromJust are exactly what I don't
want to see used anywhere.

> Not so hard. How about if Map.lookup is prepared to give us a string
> via the Either String monad and we want to throw an error:
> let lookup k m = either error id $ Map.lookup k m
> in lookup (map (`lookup` m) xs) sm

exactly, if it is in a monad then you don't have to make this decision,
the user of lookup does.


> let lookup k m = either (throwError . strMsg) return $ Map.lookup k m
> in do vs <- mapM (`lookup` m) xs
>   lookup vs sm

now compare that to:

> mapM (`lookup` m) xs >>= (`lookup` sm)

and that is a relatively simple one.


> But note that this is *not* the Identity monad we're working in here.
> It's some MonadError, and as far as I'm concerned, that's quite
> different.

I was never working in the Identity monad either, the routines should
work in an _arbitrary_ monad, of which Identity is one of.

> It's important to note here that  either (throwError . strMsg) return 
> is a useful lifter in its own right, and should probably be extracted
> and put in the library.
> 
> > but the real power is when you combine monadic failure with combinators
> > and monad transformers
> 
> > -- imagine some complicated function
> > f x xs = runWriterT $ mapM (\x -> foofunc x >>= tell) xs
> >
> > the great thing about this is it is transparent to failure! so you can
> > build arbitrarily complicated transformers while still letting the user
> > of 'f' decide what to do with failure. this is a great feature, if
> > foofunc returned a data type, the writer of 'f' would be forced to deal
> > with failure, and might (likely will) do something silly like call
> > 'error'.
> 
> I'm not sure I understand your point here. Why would the writer of f
> be any more forced to deal with failure if foofunc returned a specific
> type here? In fact, it must be at least typed in WriterT, so I'm not
> sure what you mean. The code would be identical regardless of whether
> the transformed monad was fixed or not, and the writer of f doesn't
> have to do anything.

indeed. it is identical only because the inner monad can be an arbitrary
one. if foofunc returned an error in an algebraic type, then the monad
becomes fixed and your function is no longer general.

> > I really don't like it when things fail via 'error'.
> 
> Then why do you advocate the use of 'fail' which is implemented with
> error in half of all monads that people use? Why do you advocate the
> use of runIdentity on a possibly failing computation? That's the same
> as failing via error.

Yup. except for the fact that I am advocating making functions work
in an arbitrary monad. Think about lambda patterns, they cause 'errors'
but arn't indicated as special in the type system, at least with the
'do' notation you can recover and do something interesting when the
pattern doesn't match. bottom is a member of every type in haskell
whether we like it or not. People already use 'error' way to much, we
should be making it easier for them to use recoverable things like
'fail', not harder. Dealing with errors sanely should not take more
effort, but should be the default.

bottoming out is a perfectly valid thing to do on some errors, but such
a thing should _never_ be forced. the choice of Monad is what lets you
do that. The difference is non-trivial and deals with more than just
error handling. A space leaking deterministic parser written correctly
will become constant space when run in the 'Identity' Monad (but might
fill in some values with bottom) while using Either or Just would cause
it to hold onto its entire input until the information can be verified.

Sometimes you want fail to bottom, sometimes you don't, but best of all
in all cases is to defer the decision to an outer monad.


if people can't do 

> "foo" <- getString

without changing all their type signatures, then they are going to do
something like

> x <- getString 
> if x == "foo" then ... else error "expecting foo!"

b

Re: [Haskell-cafe] haskell programming guidelines

2006-02-28 Thread Cale Gibbard
On 28/02/06, John Meacham <[EMAIL PROTECTED]> wrote:
> On Tue, Feb 28, 2006 at 01:09:03AM -0500, Cale Gibbard wrote:
> > > Well, the benefit of the Identity monad is so that the user of a routine
> > > can choose to recover gracefully by using a different monad, you only
> > > use the Identity monad when you are making a choice to bottom out on
> > > errors. using 'error' directly is not an option in said cases because it
> > > would take away the ability of the user of a routine to catch errors
> > > properly. error should only be used for reporting bugs that should never
> > > happen, not user visible failure.
> >
> > I'd argue that it would be better for the user to simply catch the
> > value returned which indicates error explicitly, and throw the error
> > themselves. This indicates that they have put thought into the fact
> > that the function may fail.
>
> so does using runIdentity, that is the point of it. You are saying I
> want failure to bottom out, just like using it as a 'Maybe' means you
> only care about whether it has a result or using it as a 'Either' means
> you want the result string or using it as a WriterT Foo IO means you
> want to possibly collect some results and have fail throw an IO
> exception.
>
> I consider it bad style to spend code on cases you never expect to
> happen, if it takes too much work to write code that fails properly on
> bugs, people arn't (and definitly should not have to) do the extra work,
> they will just write code that fails poorly. Monadic failure is
> absolutely great for writing robust, concise, code.
>
> > > be handled, the user of it should.
> >
> > Right, which is why minimal types for expressing the failure should be
> > used, and the user should convert from those types to whatever larger
> > environment they have in mind. If your function is simply partial, use
> > Maybe, if you want to report error strings, use Either String. These
> > types easily lift into any monad which support similar functionality.
> > It also gives the users of your library more information about the
> > exact way in which your functions may fail, just by looking at the
> > type signatures, and gets them thinking about handling that failure.
> > An arbitrary monad m doesn't indicate anything about the failure modes
> > present.
>
> ack! The user of a library is who should get to choose how to deal with
> the error case, not the library writer.
>
> I'd hate to give up such very common idioms as
>
> -- collect error messages from all failing parsers
> [ err | Left err <- map parse xs]

I don't see how you lose this one at all.

>
> -- look up a string transformed by a map in another map, failing if it
> -- is not in said other map.
> runIdentity $ Map.lookup (concatMap (`Map.lookup` map) xs) smap

Suppose Map.lookup returns something in the Maybe monad.

let lookup k m = fromJust $ Map.lookup k m
in lookup (map (`lookup` m) xs) sm

Not so hard. How about if Map.lookup is prepared to give us a string
via the Either String monad and we want to throw an error:
let lookup k m = either error id $ Map.lookup k m
in lookup (map (`lookup` m) xs) sm

If we had a bigger monadic context, it would be just as easy to lift
the error up into that.

let lookup k m = either (throwError . strMsg) return $ Map.lookup k m
in do vs <- mapM (`lookup` m) xs
  lookup vs sm

Or finally, if Map.lookup uses the MonadError class, like it probably should:
do vs <- mapM (`Map.lookup` m) xs
   Map.lookup vs sm

But note that this is *not* the Identity monad we're working in here.
It's some MonadError, and as far as I'm concerned, that's quite
different.

Also, if Map.lookup was equipped to give us symbolic information about
the error, we could extend this to that. With fail, all we get is a
string. We'd know what's actually available from Map.lookup before we
write any of this.

It's important to note here that  either (throwError . strMsg) return 
is a useful lifter in its own right, and should probably be extracted
and put in the library.

> but the real power is when you combine monadic failure with combinators
> and monad transformers

> -- imagine some complicated function
> f x xs = runWriterT $ mapM (\x -> foofunc x >>= tell) xs
>
> the great thing about this is it is transparent to failure! so you can
> build arbitrarily complicated transformers while still letting the user
> of 'f' decide what to do with failure. this is a great feature, if
> foofunc returned a data type, the writer of 'f' would be forced to deal
> with failure, and might (likely will) do something silly like call
> 'error'.

I'm not sure I understand your point here. Why would the writer of f
be any more forced to deal with failure if foofunc returned a specific
type here? In fact, it must be at least typed in WriterT, so I'm not
sure what you mean. The code would be identical regardless of whether
the transformed monad was fixed or not, and the writer of f doesn't
have to do anything.

What I'm advocating is not the use of n

Re: [Haskell-cafe] haskell programming guidelines

2006-02-27 Thread John Meacham
On Tue, Feb 28, 2006 at 01:09:03AM -0500, Cale Gibbard wrote:
> > Well, the benefit of the Identity monad is so that the user of a routine
> > can choose to recover gracefully by using a different monad, you only
> > use the Identity monad when you are making a choice to bottom out on
> > errors. using 'error' directly is not an option in said cases because it
> > would take away the ability of the user of a routine to catch errors
> > properly. error should only be used for reporting bugs that should never
> > happen, not user visible failure.
> 
> I'd argue that it would be better for the user to simply catch the
> value returned which indicates error explicitly, and throw the error
> themselves. This indicates that they have put thought into the fact
> that the function may fail.

so does using runIdentity, that is the point of it. You are saying I
want failure to bottom out, just like using it as a 'Maybe' means you
only care about whether it has a result or using it as a 'Either' means
you want the result string or using it as a WriterT Foo IO means you
want to possibly collect some results and have fail throw an IO
exception.

I consider it bad style to spend code on cases you never expect to
happen, if it takes too much work to write code that fails properly on
bugs, people arn't (and definitly should not have to) do the extra work,
they will just write code that fails poorly. Monadic failure is
absolutely great for writing robust, concise, code.

> > be handled, the user of it should.
> 
> Right, which is why minimal types for expressing the failure should be
> used, and the user should convert from those types to whatever larger
> environment they have in mind. If your function is simply partial, use
> Maybe, if you want to report error strings, use Either String. These
> types easily lift into any monad which support similar functionality.
> It also gives the users of your library more information about the
> exact way in which your functions may fail, just by looking at the
> type signatures, and gets them thinking about handling that failure.
> An arbitrary monad m doesn't indicate anything about the failure modes
> present.

ack! The user of a library is who should get to choose how to deal with
the error case, not the library writer.

I'd hate to give up such very common idioms as

-- collect error messages from all failing parsers 
[ err | Left err <- map parse xs] 

-- look up a string transformed by a map in another map, failing if it
-- is not in said other map.
runIdentity $ Map.lookup (concatMap (`Map.lookup` map) xs) smap

but the real power is when you combine monadic failure with combinators
and monad transformers

-- imagine some complicated function
f x xs = runWriterT $ mapM (\x -> foofunc x >>= tell) xs

the great thing about this is it is transparent to failure! so you can
build arbitrarily complicated transformers while still letting the user
of 'f' decide what to do with failure. this is a great feature, if
foofunc returned a data type, the writer of 'f' would be forced to deal
with failure, and might (likely will) do something silly like call
'error'. 

I really don't like it when things fail via 'error'. monadic failure
means they don't have to. not only can they let the user decide how
failure should be handled, but Monads provide exactly the compositional
tools needed to combine code in a such a way that preserves that
property.

imagine if Map.lookup returned Maybe Int, but writeInt returned (Either
String Foo).

now suddenly you couldn't do 
> Map.lookup x map >>= writeInt

By prematurely deciding on an algebraic type, you seriously limit the
usability of your code.

you say

"If your function is simply partial, use Maybe, if you want to report
error strings, use Either String."

which is exactly precicely what monadic failure lets you do. use the
routine in the way that makes sense. but more importantly it lets you write
monadic combinators that preserve said property.


> Well, that means that Reader, Writer and State, and any monad based
> upon them or their transformers does not have a meaningful fail. IO
> also does not have an interesting fail. It also means that all custom
> monads based on state transformers, say, don't have interesting fails.
> This is a very large chunk of the monads which people use in everyday
> code! The List monad and Maybe monad have nice fails, and that's why
> they should be in MonadZero.

IO definitly has an interesting fail, it throws a catchable IO
exception. (note, this is not the same as imprecise exceptions)

Reader,Writer, and State are stacked on top of Identity, which has error
as fail on purpose. if you don't like that you have the freedom to
either stack the transformer version on to another monad. Or there are
various transformers that give you an interesting 'fail' if you want it.
When you use Identity, you are saying 'error' is what you want. 


but in any case, you just stated the power of monadic fail right there.

"monad

Re: [Haskell-cafe] haskell programming guidelines

2006-02-27 Thread Cale Gibbard
On 27/02/06, John Meacham <[EMAIL PROTECTED]> wrote:
> On Mon, Feb 27, 2006 at 10:57:17PM -0500, Cale Gibbard wrote:
> > Well, this is an issue. Perhaps a version of error which makes the
> > line/column number available to its parameter would help... something
> > along the lines of
> >
> > type SourcePos = (Integer, Integer)
> > -- possibly a data/newtype with a nicer Show instance
> > errorPos :: (SourcePos -> String) -> a
>
>
> Yes, this is what jhc's SRCLOC_ANNOTATE addreses, more or less.
>
> > This would give all the benefits normally acquired from the expansion
> > of the syntax sugar while allowing you to additionally add any extra
> > messages you'd like. Further, you'd not be required to work in, say
> > the identity monad, in order to get line number messages for failures
> > (though in GHC at least, irrefutable pattern match failures in lambdas
> > and let also get line numbered).
>
> Well, the benefit of the Identity monad is so that the user of a routine
> can choose to recover gracefully by using a different monad, you only
> use the Identity monad when you are making a choice to bottom out on
> errors. using 'error' directly is not an option in said cases because it
> would take away the ability of the user of a routine to catch errors
> properly. error should only be used for reporting bugs that should never
> happen, not user visible failure.

I'd argue that it would be better for the user to simply catch the
value returned which indicates error explicitly, and throw the error
themselves. This indicates that they have put thought into the fact
that the function may fail.

> The writer of a library shouldn't decide how (non-buggy) failure should
> be handled, the user of it should.

Right, which is why minimal types for expressing the failure should be
used, and the user should convert from those types to whatever larger
environment they have in mind. If your function is simply partial, use
Maybe, if you want to report error strings, use Either String. These
types easily lift into any monad which support similar functionality.
It also gives the users of your library more information about the
exact way in which your functions may fail, just by looking at the
type signatures, and gets them thinking about handling that failure.
An arbitrary monad m doesn't indicate anything about the failure modes
present.

>
> > I'm actually really against the inclusion of fail in the Monad class,
> > so finding a reasonable replacement for any constructive uses it might
> > have had is important to me.
>
> I know you keep saying this, We start with the exact same premises and
> goals, yet somehow come to the exact opposite conclusion. I have not
> quite figured out why.
>
> However, a quick survey shows that _every single_ monad defined in the
> standard and fptools libraries has an interesting non-error 'fail'
> method other than Identity, whose sole purpose is to turn 'fail's into
> errors.  Separating out a MonadError with 'fail' seems rather odd as
> every monad will be an instance of it! (including Identity, since
> turning fails into errors is its main purpose)
>
> (the monads like 'Reader' and 'Writer' are actually just shorthand for
> ReaderT a Identity, the inner monad determines the failure mode)
>
> John

Well, that means that Reader, Writer and State, and any monad based
upon them or their transformers does not have a meaningful fail. IO
also does not have an interesting fail. It also means that all custom
monads based on state transformers, say, don't have interesting fails.
This is a very large chunk of the monads which people use in everyday
code! The List monad and Maybe monad have nice fails, and that's why
they should be in MonadZero.

I disagree that Identity, Reader, Writer, or State should be an
instance of MonadError or MonadZero. They should simply not be used
for that purpose. I'd like a monad hierarchy where if there is an
instance of a class for a monad, then none of the methods of that
class are identically bottom. It seems disingenuous to me to say that
some type constructor implements certain functionality, and then
implement it in a way which crashes the program. If you need failure
in your monad, add it explicitly via a transformer, and if you use
failure, you should express that via a class. Types and classes should
be meaningful and informative about this sort of thing.

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


Re: [Haskell-cafe] haskell programming guidelines

2006-02-27 Thread John Meacham
On Mon, Feb 27, 2006 at 10:57:17PM -0500, Cale Gibbard wrote:
> Well, this is an issue. Perhaps a version of error which makes the
> line/column number available to its parameter would help... something
> along the lines of
> 
> type SourcePos = (Integer, Integer)
> -- possibly a data/newtype with a nicer Show instance
> errorPos :: (SourcePos -> String) -> a


Yes, this is what jhc's SRCLOC_ANNOTATE addreses, more or less.

> This would give all the benefits normally acquired from the expansion
> of the syntax sugar while allowing you to additionally add any extra
> messages you'd like. Further, you'd not be required to work in, say
> the identity monad, in order to get line number messages for failures
> (though in GHC at least, irrefutable pattern match failures in lambdas
> and let also get line numbered).

Well, the benefit of the Identity monad is so that the user of a routine
can choose to recover gracefully by using a different monad, you only
use the Identity monad when you are making a choice to bottom out on
errors. using 'error' directly is not an option in said cases because it
would take away the ability of the user of a routine to catch errors
properly. error should only be used for reporting bugs that should never
happen, not user visible failure.

The writer of a library shouldn't decide how (non-buggy) failure should
be handled, the user of it should.

> I'm actually really against the inclusion of fail in the Monad class,
> so finding a reasonable replacement for any constructive uses it might
> have had is important to me.

I know you keep saying this, We start with the exact same premises and
goals, yet somehow come to the exact opposite conclusion. I have not
quite figured out why.

However, a quick survey shows that _every single_ monad defined in the
standard and fptools libraries has an interesting non-error 'fail'
method other than Identity, whose sole purpose is to turn 'fail's into
errors.  Separating out a MonadError with 'fail' seems rather odd as
every monad will be an instance of it! (including Identity, since
turning fails into errors is its main purpose)

(the monads like 'Reader' and 'Writer' are actually just shorthand for
ReaderT a Identity, the inner monad determines the failure mode)

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] haskell programming guidelines

2006-02-27 Thread Cale Gibbard
On 24/02/06, John Meacham <[EMAIL PROTECTED]> wrote:
> On Fri, Feb 24, 2006 at 12:39:27PM -0500, Cale Gibbard wrote:
> > I look at the above as generating a proof obligation for me as the
> > programmer that the lookup will never fail, or at least the ability to
> > convince myself. :) If you want to handle errors, you should actually
> > handle them, not let your users get "Irrefutable pattern failed"
> > messages. Also, if someone else later comes along and wants to catch
> > that error, they have to either do it in IO, which can be fiddly if
> > the error occurs deep in the evaluation of some structure, or they
> > refactor your code so that it returns the error explicitly. Sure,
> > irrefutable pattern matches are useful, but they shouldn't be used if
> > you expect they'll ever fail.
>
> Ah, perhaps I wasn't clear. I don't ever expect these to fail. The
> reason I prefer irrefutable pattern matches to handwritten 'error'
> messages (at first) is so many months later when I introduce a subtle
> heisenbug I don't get a
>
> error: This shouldn't happen
> or worse
> error: Prelude.undefined
>
> but rather a nice error pointing right to the line number.
>
> anything I ever expect to fail for any reason other than a bug I put in
> a failing Monad with a suitably user digestable error message. So, I was
> comparing them to handwritten 'error' messages for announcing
> programming bugs. not handwritten 'error' messages for users to see
> (which really should be using 'fail' in a monad anyway).
>
> John
>
Well, this is an issue. Perhaps a version of error which makes the
line/column number available to its parameter would help... something
along the lines of

type SourcePos = (Integer, Integer)
-- possibly a data/newtype with a nicer Show instance
errorPos :: (SourcePos -> String) -> a

This would give all the benefits normally acquired from the expansion
of the syntax sugar while allowing you to additionally add any extra
messages you'd like. Further, you'd not be required to work in, say
the identity monad, in order to get line number messages for failures
(though in GHC at least, irrefutable pattern match failures in lambdas
and let also get line numbered).

I'm actually really against the inclusion of fail in the Monad class,
so finding a reasonable replacement for any constructive uses it might
have had is important to me.

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


Re: [Haskell-cafe] haskell programming guidelines

2006-02-24 Thread John Meacham
On Fri, Feb 24, 2006 at 12:39:27PM -0500, Cale Gibbard wrote:
> I look at the above as generating a proof obligation for me as the
> programmer that the lookup will never fail, or at least the ability to
> convince myself. :) If you want to handle errors, you should actually
> handle them, not let your users get "Irrefutable pattern failed"
> messages. Also, if someone else later comes along and wants to catch
> that error, they have to either do it in IO, which can be fiddly if
> the error occurs deep in the evaluation of some structure, or they
> refactor your code so that it returns the error explicitly. Sure,
> irrefutable pattern matches are useful, but they shouldn't be used if
> you expect they'll ever fail.

Ah, perhaps I wasn't clear. I don't ever expect these to fail. The
reason I prefer irrefutable pattern matches to handwritten 'error'
messages (at first) is so many months later when I introduce a subtle
heisenbug I don't get a 

error: This shouldn't happen
or worse
error: Prelude.undefined

but rather a nice error pointing right to the line number.

anything I ever expect to fail for any reason other than a bug I put in
a failing Monad with a suitably user digestable error message. So, I was
comparing them to handwritten 'error' messages for announcing
programming bugs. not handwritten 'error' messages for users to see
(which really should be using 'fail' in a monad anyway).

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] haskell programming guidelines

2006-02-24 Thread Cale Gibbard
On 20/02/06, John Meacham <[EMAIL PROTECTED]> wrote:
> There is a more straightforward way to get localized error messages
> rather than using 'maybe' and hand-writing an appropriate error, and
> that is to rely on irrefutable bindings.
>
> f x = ... y ... where
> Just y = Map.lookup x theMap
>
> now if the lookup fails you automatically get an error message pointing
> to the exact line number of the failure. or if the failure message of
> the routine is more important than the source location you can do
>
> f x = ... y ... where
> Identity y = Map.lookup x theMap
>
> it is anoying you have to make a choice between these two possibilities,
> but this can be mitigated with CPP magic or the SRCLOC_ANNOTATE pragma.
>
> John
>

I look at the above as generating a proof obligation for me as the
programmer that the lookup will never fail, or at least the ability to
convince myself. :) If you want to handle errors, you should actually
handle them, not let your users get "Irrefutable pattern failed"
messages. Also, if someone else later comes along and wants to catch
that error, they have to either do it in IO, which can be fiddly if
the error occurs deep in the evaluation of some structure, or they
refactor your code so that it returns the error explicitly. Sure,
irrefutable pattern matches are useful, but they shouldn't be used if
you expect they'll ever fail.

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


Re: [Haskell-cafe] haskell programming guidelines

2006-02-20 Thread John Meacham
There is a more straightforward way to get localized error messages
rather than using 'maybe' and hand-writing an appropriate error, and
that is to rely on irrefutable bindings.

f x = ... y ... where
Just y = Map.lookup x theMap

now if the lookup fails you automatically get an error message pointing
to the exact line number of the failure. or if the failure message of
the routine is more important than the source location you can do

f x = ... y ... where
Identity y = Map.lookup x theMap

it is anoying you have to make a choice between these two possibilities,
but this can be mitigated with CPP magic or the SRCLOC_ANNOTATE pragma.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] haskell programming guidelines

2006-02-20 Thread Donald Bruce Stewart
maeder:
> Hi,
> 
> haskell admits many programming styles and I find it important that 
> several developers of a prject agree on a certain style to ease code review.
> 
> I've set up guidelines (still as plain text) for our (hets) project in

Perhas you'd like to put up a Style page on thew new Haskell wiki,
perhaps under the Idioms category?

You could take some hints from the old style page, 
http://www.haskell.org/hawiki/HaskellStyle

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


Re: [Haskell-cafe] haskell programming guidelines

2006-02-20 Thread ajb
G'day.

Quoting Christian Maeder <[EMAIL PROTECTED]>:

>
http://www.informatik.uni-bremen.de/agbkb/forschung/formal_methods/CoFI/hets/src-distribution/versions/HetCATS/docs/Programming-Guidelines.txt

As mentioned in an earlier discussion, I strongly disapprove of the use
of multiple ($) applications in the same expression.  Or, for that matter,
most uses of ($).  I also disapprove of avoiding parentheses for the hell
of it.

The guideline that I use is: If what you are expressing is a chain of
function applications, the correct operator to express this is function
composition.  Low-priority application may then be used to apply this
composed function to an argument.

So, for example, f (g (h x)) can be expressed well as:

f . g $ h x  -- only use if you need to distinguish h
f . g . h $ x-- better

And poorly as:

f $ g $ h x
f $ g $ h $ x
(f . g . h) $ x  -- except as an intermediate step in refactoring

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


Re: [Haskell-cafe] haskell programming guidelines

2006-02-20 Thread Robert Dockins


On Feb 20, 2006, at 2:26 PM, Henning Thielemann wrote:

On Mon, 20 Feb 2006, Robert Dockins wrote:

I personally disagree with your preference for custom datatypes  
with a value representing failure to lifting types with Maybe.


I understood that part of the guidelines as a pleading for Maybe.


Humm.  Well clearly I read it the opposite way.  I suppose that means  
that whatever technique is being recommended should be put forth with  
more clarity ;-)




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG


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


Re: [Haskell-cafe] haskell programming guidelines

2006-02-20 Thread Henning Thielemann


On Mon, 20 Feb 2006, Robert Dockins wrote:

I personally disagree with your preference for custom datatypes with a value 
representing failure to lifting types with Maybe.


I understood that part of the guidelines as a pleading for Maybe.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] haskell programming guidelines

2006-02-20 Thread Robert Dockins


On Feb 20, 2006, at 12:48 PM, Christian Maeder wrote:

Hi,

haskell admits many programming styles and I find it important that  
several developers of a prject agree on a certain style to ease  
code review.


I've set up guidelines (still as plain text) for our (hets) project in

http://www.informatik.uni-bremen.de/agbkb/forschung/formal_methods/ 
CoFI/hets/src-distribution/versions/HetCATS/docs/Programming- 
Guidelines.txt


These were inspired by C programming guidelines, http://haskell.org/ 
hawiki/ThingsToAvoid and the problems I came across myself.


It like to get comments or proposals for our or other haskell  
grogramming guidelines.


I personally disagree with your preference for custom datatypes with  
a value representing failure to lifting types with Maybe.  I tend to  
like using the Maybe monad for composing large partial functions from  
smaller ones, but your suggestion makes that impossible.  Also, if  
you bake in your failure case into your datatype, you can't use the  
type system to differentiate explicitly partial functions (which use  
Maybe X), from ones that are not expected to be partial (which just  
use X).  Final point, using Maybe gives you an easy route to go to  
"Either String X" or some other richer monad to represent failure.




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG


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


Re: [Haskell-cafe] haskell programming guidelines

2006-02-20 Thread Henning Thielemann


On Mon, 20 Feb 2006, Christian Maeder wrote:


I've set up guidelines (still as plain text) for our (hets) project in

http://www.informatik.uni-bremen.de/agbkb/forschung/formal_methods/CoFI/hets/src-distribution/versions/HetCATS/docs/Programming-Guidelines.txt


It seems we share the preference for 'case', 'let', 'map', 'filter' and 
'fold'. :-)


I prefer a definite choice between all_lower_case_with_underscore and 
camelCase identifier style.


'you should probably"'  -- should probably what?

Is the function size restriction still sensible for Haskell? I think 
Haskell functions should be at most a few lines, but not "one or two 
screenfuls of text".


formJust -> fromJust


These were inspired by C programming guidelines, 
http://haskell.org/hawiki/ThingsToAvoid and the problems I came across 
myself.


It like to get comments or proposals for our or other haskell grogramming 
guidelines.


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


[Haskell-cafe] haskell programming guidelines

2006-02-20 Thread Christian Maeder

Hi,

haskell admits many programming styles and I find it important that 
several developers of a prject agree on a certain style to ease code review.


I've set up guidelines (still as plain text) for our (hets) project in

http://www.informatik.uni-bremen.de/agbkb/forschung/formal_methods/CoFI/hets/src-distribution/versions/HetCATS/docs/Programming-Guidelines.txt

These were inspired by C programming guidelines, 
http://haskell.org/hawiki/ThingsToAvoid and the problems I came across 
myself.


It like to get comments or proposals for our or other haskell 
grogramming guidelines.


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