Re: Indentation of If-Then-Else

2006-10-24 Thread John Meacham
On Tue, Oct 24, 2006 at 05:29:58PM +0100, Neil Mitchell wrote:
> >> Actually if-then-else isn't used that often today. Most programmers
> >> gave it up in favor of guards.
> >
> >I question both these statements. Can you cite some evidence here?
> 
> I have 501 if statements in my current project. Yhc has 626. Hoogle
> has 101. If's seem pretty well used to me!

920 in jhc. "I win!" :)

John

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


Re: digit groups

2006-10-24 Thread Ashley Yakeley

Ketil Malde wrote:

Tempting to use B8 Cedilla, since it looks somewhat like a comma, and
is less useful for other purposes -- but perhaps it would be to easily
confused with a real comma? 


I would advise against this until we have a bit more of a plan for 
extended characters in Haskell source. For instance, it might be 
sensible to use the Unicode "general category" property to decide what 
characters are allowed in identifiers, and so on.


--
Ashley Yakeley

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


Re[2]: Indentation of If-Then-Else

2006-10-24 Thread Bulat Ziganshin
Hello Taral,

Tuesday, October 24, 2006, 8:52:47 PM, you wrote:

>> if' :: Bool -> a -> a -> a
>> if' True  x _ = x
>> if' False _ y = y

> I support the inclusion of if' because it is the Bool catamorphism,
> but I would structure its arguments as (a -> a -> Bool -> a) because
> that facilitates use of the currying.

i has such function in my program. it just like 'either' and 'maybe'
functions, so i named it 'bool'. of course, it's used for partial
applications only



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: Indentation of If-Then-Else

2006-10-24 Thread Taral

On 10/24/06, Henning Thielemann <[EMAIL PROTECTED]> wrote:

For processing conditions, the if-then-else syntax was defined in
Haskell98. However it could be simply replaced by the function if' with

if' :: Bool -> a -> a -> a
if' True  x _ = x
if' False _ y = y


I support the inclusion of if' because it is the Bool catamorphism,
but I would structure its arguments as (a -> a -> Bool -> a) because
that facilitates use of the currying.

I don't think it's an effective replacement for if/then/else because
using if' usually requires a bunch of harder-to-read () instead of
nice delimiting reserved words.

--
Taral <[EMAIL PROTECTED]>
"You can't prove anything."
   -- Gödel's Incompetence Theorem
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Indentation of If-Then-Else

2006-10-24 Thread Henning Thielemann

On Tue, 24 Oct 2006, Neil Mitchell wrote:

> > > Actually if-then-else isn't used that often today. Most programmers
> > > gave it up in favor of guards.
> > 
> > I question both these statements. Can you cite some evidence here?
> 
> I have 501 if statements in my current project. Yhc has 626. Hoogle
> has 101. If's seem pretty well used to me!

I obviously read the wrong code, sorry. :-)

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


Re: Indentation of If-Then-Else

2006-10-24 Thread Henning Thielemann

On Tue, 24 Oct 2006, Dave Menendez wrote:

> Henning Thielemann writes:
> 
> > Actually if-then-else isn't used that often today. Most programmers
> > gave it up in favor of guards. 
> 
> I question both these statements. Can you cite some evidence here?

I have not made statistics. My subjective impression from reading programs
of others is that there are many guards, and only few if-then-elses. If
you are one of the if-users, then hi, I'm the other one! ;-)
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Indentation of If-Then-Else

2006-10-24 Thread Neil Mitchell

> Actually if-then-else isn't used that often today. Most programmers
> gave it up in favor of guards.

I question both these statements. Can you cite some evidence here?


I have 501 if statements in my current project. Yhc has 626. Hoogle
has 101. If's seem pretty well used to me!

Thanks

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


Re: Indentation of If-Then-Else

2006-10-24 Thread Dave Menendez
Henning Thielemann writes:

> Actually if-then-else isn't used that often today. Most programmers
> gave it up in favor of guards. 

I question both these statements. Can you cite some evidence here?
-- 
David Menendez <[EMAIL PROTECTED]> | "In this house, we obey the laws
  |of thermodynamics!"
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


proposal: introduce lambda-match (explicit match failure and fall-through)

2006-10-24 Thread Claus Reinke
name: 
   introduce lambda-match (explicit match failure and fall-through)


summary: 
   Haskell 98 provides *two different translations* of lambda

   abstractions involving pattern matching, only one of which is
   directly accessible (Section 3.3 - the other is embedded in the
   translation of do-notation, see "ok" in Section 3.14).

   providing explicit source notation for the second translation,
   substantially simplifies programmability of pattern-match
   fall-through by reification of pattern-match failure, two 
   central language features that are so far only available

   through the built-in, non-composable case construct.

what:
   in Section 3.3, the translation for conventional lambda
   abstractions with patterns is given as

   [| \p1 .. pn-> e |] = \x1 .. xn-> case (x1,..,xn) of (p1,..,pn) -> e

   with xi fresh identifiers, and pattern-match failure resulting in
   _|_. the latter is unfortunate, and results in partial functions the
   coverage of which cannot be combined, but it is forced by 
   translation into conventional lambda calculus.


   since computational lambda calculus (\-M) has become a central part
   of Haskell programming practice, there shall be an alternative form
   of lambda abstraction, dubbed here lambda-match, with associated
   translation into \-M:

   [| |p1 .. pn-> e |] = \x1 .. xn-> case (x1,..,xn) of 
   { (p1,..,pn) -> return e;

  _ -> fail "no match" }

   [note1: this is the translation in principle - in practice, to
enable composition of lambda-matches without further language
extensions, a slight modification is needed, wrapping the right-hand
sides of the case in a Match constructor, see library and patch]

   a library for composing these lambda-matches shall provide for
   composition of alternative lambda-matches (+++), match failure
   (nomatch) and embedding of the explicit match monad into pure
   expressions (splice, where "splice |p1..pn->e = \p1..pn->e").

   [note2: an alternative translation would use do-notation instead
of case as the target:

[| |p1 .. pn-> e |] = \x1 .. xn-> do { 
   (p1,..,pn) <- return (x1,..,xn); 
   return e }


   both translations easily accomodate guards and pattern guards
   as well, the former by building on existing support for these two
   features in case constructs, the latter without requiring any 
   previous implementation of pattern guards, by lifting (pattern)

   guards into the match monad]

implementation impact:
   minimal - limited to an extension in parser/desugarer, employing
   previously inaccessible syntax for lambda-match, and a slight
   variation of the existing lambda translation; also adds a small
   library to support composition of matches.

   [note3: a first draft of the composition library and a patch for
GHC (about a dozen new lines in the parser) are provided as 
attachments to this proposal, together with some examples]


context:
   as has been pointed out in the thread on replacing and improving
   pattern guards, Haskell's pattern matching support, even before
   pattern guards, is monolithic (built-in case is the only way to handle
   multiple alternative matches) rather than compositional (lambdas
   represent individual alternatives, but cannot be composed on 
   match fall-through). this implies increased complexity of the language
   definition and limited expressiveness of its features, when compared 
   with alternative models (eg, adapting Wolfram's pattern match 
   calculus for Haskell). see, eg.:


   http://www.haskell.org/pipermail/haskell-prime/2006-October/001713.html
   http://www.haskell.org/pipermail/haskell-prime/2006-October/001720.html
   http://www.haskell.org/pipermail/haskell-prime/2006-October/001723.html
   http://www.haskell.org/pipermail/haskell-prime/2006-October/001724.html

   in principle, replacing Haskell's current pattern matching support
   with a simpler, more compositional model, and defining the current
   constructs on top of that new core is the way forward, IMHO. in
   practice, however, I suspect that the committee is less than tempted
   to introduce such a substantial simplification for Haskell'.

   the present proposal is an attempt at a compromise, suggesting a
   minimal language change to introduce compositional pattern-match
   failure and fall-through. with lambda-match, it implements only a 
   single language extension (as syntactic sugar), delegating the rest

   of the functionality to a library. without the sugar, the result of the
   by-hand translation becomes so hard to read as to be near 
   unusable, while the chosen form of sugaring allows to provide

   most of the language features discussed in the earlier threads to
   be provided as a library. this does seem to be a useable balance.

   building constructs of the simpler pattern-match model on top of

Re: Indentation of If-Then-Else

2006-10-24 Thread Henning Thielemann

On Mon, 23 Oct 2006, Philippa Cowderoy wrote:

> On Mon, 23 Oct 2006, Cale Gibbard wrote:
> 
> > Of course I disagree with this course for all the reasons I stated
> > above. The whole point of having high level programming languages is
> > so that you can put more work into the tools so that the end user
> > doesn't have to work as hard. One shouldn't ask "What's easiest to
> > parse?" but "What's easiest to read and write?".
> > 
> 
> A good many tools can, of course, get by on a reversible desugaring. It 
> seems to me that this'd be a sensible candidate for a library.

I have tried to sum up my points about if-then-else syntax and answer some
question that were arised by others. Even if it doesn't influence the
decision about the optional semicolon, it will well become of interest
once HaskellTwo design procedure starts.


http://haskell.org/haskellwiki/If-then-else


===

Replace syntactic sugar by a function 


For processing conditions, the if-then-else syntax was defined in 
Haskell98. However it could be simply replaced by the function if' with 

if' :: Bool -> a -> a -> a
if' True  x _ = x
if' False _ y = y

Unfortunately there is no such function in the Prelude. 


 Advocacy 


 Advantages 


The advantages of the function if' over the syntax if-then-else are the 
same like for all such alternatives. So let me repeat two important 
non-syntactic strengths of Haskell: 

types: classification, documentation 
higher order functions: combinators 

If if' would be a regular function, each language tool can process it 
without hassle. Haddock can generate documentation for it, a text editor 
can make suggestions for values to insert, Hoogle can retrieve that 
function. 


For example, the Hoogle query 

[Bool] -> [a] -> [a] -> [a]

may return 

zipWith3 if'


 


 Use cases 


Each of the following functions could be defined in terms of if'. 
Actually, they do not even need to be in Prelude because they can be 
constructed so easily. 


That function is harder to explain in English, than by its implementation. 
:-) 

zipIf :: [Bool] -> [a] -> [a] -> [a]
zipIf = zipWith3 if'

Select a member of a pair. This resembles the cond?x:y operation of the C 
language. 

infixr 1 ?:
(?:) :: Bool -> (a,a) -> a
(?:) = uncurry . if'

>From a list of expressions choose the one, whose condition is true. The 
first parameter is the default value. It is returned if no condition 
applies. 

select :: a -> [(Bool, a)] -> a
select = foldr (uncurry if')

See Case. 



 


 Why add this function to Prelude? 


Actually people could define if' in each module, where they need it, or 
import it from a Utility module, that must be provided in each project. 
Both solutions are tedious and contradict to modularization and software 
re-usage. The central question is, whether if' is an idiom, that is so 
general that it should be in the Prelude, or not. I think it is, otherwise 
it wouldn't have get a special syntax. 


 If-Then-Else vs. guards 


Actually if-then-else isn't used that often today. Most programmers gave 
it up in favor of guards. This practice has its own drawbacks, see 
Syntactic sugar/Cons and Things to avoid. 



 


 Is If-Then-Else so important? 


Counting if-then-else or if' in today's Haskell programs isn't a good 
measure for the importance a if' function, because 

frequently guards are used instead of if-then-else 
there is no standard function, and this let people stick to work-arounds. 

 What is so bad about the if-then-else sugar? 


Since syntactic sugar introduces its own syntactic rules, it is hard to 
predict how it interferes with other syntactic constructs. This special 
syntax for instance led to conflicts with do notation. A syntactic 
extension to solve this problem is proposed for Haskell'. It is not known 
what conflicts this extension might cause in future. 



 


 Why breaking lots of old and unmaintained code? 


Haskell without if-then-else syntax makes Haskell more logical and 
consistent. There is no longer confusion to beginners like: "What is so 
special about if-then-else, that it needs a separate syntax? I though it 
could be simply replaced by a function. Maybe there is some subtlety that 
I'm not able to see right now." There is no longer confusion with the 
interference of if-then-else syntax with do notation. Removing 
if-then-else simplifies every language tool, say compiler, text editor, 
analyzer and so on. 


If we arrive at Haskell two some day, 
(http://haskell.org/hawiki/HaskellTwo) it will certainly be incompatible 
to former Haskell versions. This does not mean, that old code must be 
thrown away. There should be one tool, that converts Haskell 98 and 
Haskell' to Haskell-2. Having one tool for this purpose is better than 
blowing all language tools with legacy code. Syntactic replacements like 
if-then-else syntax to if' function should be especially simple. 



 


 Summary 

Light proposal, compa

Re: Module imports anywhere

2006-10-24 Thread Ketil Malde
Henning Thielemann <[EMAIL PROTECTED]> writes:

>> #if HUGS
>> import Hugs.Base
>> #elseif GHC
>> import GHC.Base
>> #endif

> We just need a system for plugging together system-dependent modules, 
> that's all. We do not need preprocessor hacks for this issue:
>   http://www.haskell.org/pipermail/haskell-cafe/2006-August/017503.html

But in general, I often find I want to use CPP both to modify imports
and provide function definitions.  E.g. to provide sensible error
messages for some Prelude functions (read, head, fromJust, etc), I
have an include file that imports Prelude hiding the original
definitions, and replace them with macros making use of CPP's __LINE__
and __FILE__.  For some of the support functionality, I'm forced to
write macros instead of functions, since I'd otherwise need to clutter
all my modules with multiple #include statements.

This tends to arise relatively often when I use #include -- if it is
simple to implement, could perhaps this (mixing of imports and
definitions) be allowed when -cpp is specified?

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


Re: digit groups

2006-10-24 Thread Ketil Malde
Henning Thielemann <[EMAIL PROTECTED]> writes:

>> 1. allow to use '_' in number literals. its used in Ruby and i found
>> that this makes long number literals much more readable. for example

> Sounds like something that can be solved with an infix operator:

> (~~) :: Integer -> Integer -> Integer
> a ~~ b  =  a*1000 + b

Nice.  Although the ~~ seems a bit intrusive.  Since its use would be
thouroughly optional, perhaps we could adopt an extended (A0-FF)
character for this?  Some candidates:

   257   175   AF ¯ MACRON
   267   183   B7 · MIDDLE DOT
   270   184   B8 ¸ CEDILLA
   260   176   B0 ° DEGREE SIGN

Tempting to use B8 Cedilla, since it looks somewhat like a comma, and
is less useful for other purposes -- but perhaps it would be to easily
confused with a real comma? 

Ideally, one would also require a group of three digits to the right
of such an operator.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

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