Re: [Haskell-cafe] global variables

2007-05-24 Thread Taral

On 5/24/07, Adrian Hey [EMAIL PROTECTED] wrote:

Taral wrote:
 The other syntaxes proposed don't strike me as sufficiently rigorous.

Me neither. It's always been a great source of puzzlement to me why this
very simple and IMO conservative proposal should be so controversial.
Unless someone can point out some severe semantic difficulty or suggest
something better it seems like a no-brainer to me.


I think it lacks implementation. I don't have time, or I'd look into
hacking this into GHC.

--
Taral [EMAIL PROTECTED]
Please let me know if there's any further trouble I can give you.
   -- Unknown
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Wanted: warning option for usages of unary minus

2007-05-17 Thread Taral

On 5/17/07, Joseph H. Fasel [EMAIL PROTECTED] wrote:

*Sigh*  The problems with unary minus were discussed in the dim mists of
time before we published the first Haskell report.  We considered then
using a separate symbol for unary negation (as does APL, for example),
but (IIRC) this was regarded as unfriendly to Fortran programmers.


[breaking cc list]

Would this kind of thing be eligible for Haskell'? I never had a
problem with _1 in APL-type languages... and I think it's best to be
very clear about intent.

--
Taral [EMAIL PROTECTED]
Please let me know if there's any further trouble I can give you.
   -- Unknown
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: List syntax (was: Re: help from the community?)

2007-02-03 Thread Taral

On 2/3/07, Brian Hulley [EMAIL PROTECTED] wrote:

Of course, but when I said error I meant error with respect to the
intentions of the programmer not syntax error detected by the compiler.
The problem with your proposal is that if optional trailing commas were
allowed, if *I* wrote:

(1,2,)

by mistake, forgetting to add in the last element, the fact that the
compiler would now treat the trailing comma as optional means it would now
accept the code as being syntactically ok.


And invariably your code would fail to typecheck. That makes this a
lot safer for tuples than for lists, for example.

--
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: help from the community?

2007-01-31 Thread Taral

On 1/31/07, Conor McBride [EMAIL PROTECTED] wrote:

So, as far as Haskell' is concerned, I'd favour forbidding non-empty
cases, but only because I favour having some more explicit syntax for
empty cases, further down the line.


I see nothing wrong with case x of {}, with required braces. The
layout rule never generates empty braces.

--
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-22 Thread Taral

On 10/22/06, Benjamin Franksen [EMAIL PROTECTED] wrote:

The problem with this is that in a do block it forces me to use /two/
indentation levels, instead of one, e.g.


+1. This is also my primary reason for wanting the sugar. In some
code, indentation is at a premium. Forcing the extra indentation does
nothing to improve readability, and is a common frustration. The point
of all sugar is to reduce frustration, so I am strongly in favor of
the new syntax.

--
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: Standard syntax for preconditions, postconditions, and invariants

2006-10-19 Thread Taral

On 10/19/06, Neil Mitchell [EMAIL PROTECTED] wrote:

Hi

 reverse @ ensure { reverse (reverse xs) == xs }

Question, does reverse [1..] meet, or not meet this invariant?


This is a good point. You can only do sensible conditions on functions
if appropriate termination constraints are met.


 invariant RedBlackTree a where
   RBNode False _ l _ r == redDepth l == redDepth r

Where does this invariant hold? At all points in time? After a call
has executed? Only between module boundaries?


This invariant holds at the time you build the RBNode. It's
effectively a precondition on the RBNode function.


That said, I think that embedding invariants/pre/postconditions in the
code is very useful, I just don't think that Haskell' is a good target
for this - there is a big design space that no one has yet explored.


I agree that Haskell' will not have this, if only under the must
already be implemented requirement for major features. However, it
seems that Haskell' is a good way to get people thinking about future
improvements, and I'd hate to stifle that.

--
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: map and fmap

2006-08-28 Thread Taral

On 8/28/06, John Hughes [EMAIL PROTECTED] wrote:

As for an example of fmap causing trouble, recall the code I posted last
week sometime:

class Foldable f where
  fold :: (a - a - a) - a - f a - a


I'd call this a case of Foldable causing trouble. :) Fold is
somewhat specific to the structure of the underlying collection (hence
the numerous fold* functions), map is not.

--
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: Re[8]: All Monads are Functors

2006-08-16 Thread Taral

On 8/16/06, Bulat Ziganshin [EMAIL PROTECTED] wrote:

you deleted context of my note, where you wrote something opposite to
All Monads are Functors:

 Not necessarily. If A doesn't have any Functor declarations, it could
 be considered just a Monad without a Functor.

is it possible to declare Monad Foo without Functor Foo with the above
class definition?


You misunderstood what I meant. Monad without a Functor means Monad
*declaration* without an explicit Functor *declaration*, i.e. using
the defaults. The problem happens when a definition implicitly uses
the defaults and then an explicit Functor comes into scope via import.

The current proposal to require people to write instance Functor
isn't so pretty as the hierarchy becomes more fine-grained:

instance Monad [] where
   instance Functor
   instance PointedFunctor
   instance Applicative
   ...

--
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: Re[2]: All Monads are Functors

2006-08-14 Thread Taral

On 8/14/06, Jon Fairbairn [EMAIL PROTECTED] wrote:

of course, there's no reason to do that, but what I'm
proposing is that we allow default instance declarations in
class declarations in much the same way as default methods:


I just realized that default superclass methods have a small problem:

module A contains instance Monad []
module B contains instance Functor []
module C imports A and B.

Do we complain about a duplicate instance declarations? If not, does
the use of fmap in A use the default definition, or the one from B?

--
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: Nested Guards

2006-07-01 Thread Taral

On 7/1/06, Bas van Dijk [EMAIL PROTECTED] wrote:

I would like to propose a feature from the FP language Clean[1] called Nested
Guards.


I do have to bring up that this is excluded from consideration for
Haskell' because it is not already implemented in any existing Haskell
compiler or interpreter.

Perhaps this could be forwarded onto the GHC and other compiler people
for consideration as an extension?

--
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: Class System current status

2006-05-11 Thread Taral

On 5/11/06, Stephanie Weirich [EMAIL PROTECTED] wrote:

a) standardize on MPTC and FDs using rules from CHR paper.



  - We're already in that state. There *is* a lot of Haskell code that
uses FDs, it's just not Haskell 98 code. Whenever ATs take over, we'll
still have to deal with this code.


In my opinion, this one holds the greatest weight. The current mass of
*useful* and *used* code that is written with and requires FDs is
possibly the most important consideration of all.

Given that FD *syntax* is well-defined, I see no reason not to
standardize it. It remains, however, to decide on what level of
*minimum* termination support Haskell' will insist upon. The CHR paper
(with the confluence improvements by Claus) is currently the most
promising option, and has an implementation (another important
consideration) in GHC.

--
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: A modest proposal

2006-04-16 Thread Taral
On 4/15/06, John Goerzen [EMAIL PROTECTED] wrote:
 On the downside, this means that I couldn't just say:

 take 5 mylist

 I'd instead have to write:

 take (5::Int) mylist

Wouldn't defaulting do this?

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


Re: FFI, safe vs unsafe

2006-04-12 Thread Taral
On 4/12/06, Wolfgang Thaller [EMAIL PROTECTED] wrote:
 Personally, I'm still in favour of inverting this. We are not in
 court here, so every foreign function is guilty until proven
 innocent. Every foreign function might be longrunning unless the
 programmer happens to know otherwise. So maybe... returnsquickly?

Hear, hear:

fast - takes very little time to execute
pure - side-effect free
nocallback - does not call back into Haskell

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


Re: preemptive vs cooperative: attempt at formalization

2006-04-11 Thread Taral
On 4/11/06, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:

  [Rule 1]
  * in a cooperative implementation of threading, any thread with value
_|_ may cause the whole program to have value _|_. In a preemtive one,
this is not true.

 I'm afraid that claim may need qualifications:

I was thinking that it might be more useful to express it programatically:

if preemptive then fork _|_  return () = ()

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


Re: deeqSeq proposal

2006-04-04 Thread Taral
On 4/4/06, Simon Marlow [EMAIL PROTECTED] wrote:
 So deepSeq doesn't return _|_ when passed a cyclic structure?  This is a
 bad idea, because it lets you distinguish cyclic structures from
 infinite ones.  deepSeq has to behave like a function, regardless of its
 implementation.

Why is this necessary?

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


Re: Concurrency

2006-03-31 Thread Taral
On 3/31/06, John Meacham [EMAIL PROTECTED] wrote:
- I wouldn't include threadWaitRead, threadWaitWrite,
  or threadDelay at all.  These can all be implemented using
  FFI, so don't belong in the concurrency library.  Their
  presence is largely historical.

 They all have special implementations on a 'epoll' based system.
 threadDelay turns into the timeout parameter to select, waitread/write
 turn into the basic building blocks of your epoll wait-list. We
 definitly want these in the interface as primitves.

And they're all a pain because they don't take sets of files, only
single ones. Can we please have something like:

threadWait :: Timeout - [Handle] - IO ?

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


Re: FFI, safe vs unsafe

2006-03-29 Thread Taral
On 3/29/06, Simon Marlow [EMAIL PROTECTED] wrote:
 If we were to go down this route, we have to make reentrant the default:
 'unsafe' is so-called for a good reason, you should be required to write
 'unsafe' if you're doing something unsafe.  So I'd suggest

   unsafe
   concurrent unsafe
   concurrent  -- the hard one
   {- nothing -}

Can I suggest sef in this? Most cases of unsafe are actually
claims that the call is side-effect free.

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


Re: Re[2]: important news: refocusing discussion

2006-03-27 Thread Taral
On 3/27/06, Ross Paterson [EMAIL PROTECTED] wrote:
 How about STM (minus retry/orElse) and TVars as the portable interface?
 They're trivial for a single-threaded implementation, and provide a
 comfortable interface for everyone.

+1 on STM as the core interface. Why do you suggest omitting retry/orElse?

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


Re: Re[2]: Strict tuples

2006-03-22 Thread Taral
On 3/22/06, Bulat Ziganshin [EMAIL PROTECTED] wrote:
 ghc uses unboxed tuples just for such sort of optimizations. instead
 of returning possibly-unevaluated pair with possibly-unevaluated
 elements it just return, say, two doubles in registers - a huge win

I have no doubt of this. My comment refers to the idea that somehow
such strictness annotations are (a) required at the type level and (b)
required at all to enable such optimization. I believe the
optimization happens without any annotation from the user, and it
should stay that way.

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


Re: Re[2]: Strict tuples

2006-03-22 Thread Taral
On 3/22/06, Manuel M T Chakravarty [EMAIL PROTECTED] wrote:
 It does happen...sometimes!  The trouble is that for certain types of
 programs (eg, numeric intensive ones), you absolutely need that
 optimisation to happen.  Without strict tuples, this means, you have to
 dump the intermediate code of the compiler and inspect it by hand to see
 whether the optimisation happens.  If not, you have to tweak the source
 to nudge the compiler into recognising that it can optimise.  Of course,
 all your efforts may be wasted when the next version of the compiler is
 released or when you have to change your code.

That kind of tweaking isn't required to simulate this. a `seq` b
`seq` (a, b) is perfectly sufficient, and is quite commonly seen in
such programs.

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


Re: Time Library

2006-03-21 Thread Taral
On 3/20/06, Ashley Yakeley [EMAIL PROTECTED] wrote:
 Never as far as I can imagine. The 'a' parameter will be taken by a
 phantom type.
 http://haskell.org/haskellwiki/Phantom_type

Now I don't recall, but is it allowed to do:

data HasResolution a = Fixed a = ...?

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


Re: important news: refocusing discussion

2006-03-21 Thread Taral
On 3/21/06, isaac jones [EMAIL PROTECTED] wrote:
 I'd like to ask folks to please bring currently open threads to a close
 and to document the consensus in tickets.  Anyone can edit tickets, so
 please don't be shy.

Claus, can you document some of your FD work in the
FunctionalDependencies ticket? I think that the new confluence results
lends a lot towards the adoption of FDs in Haskell'.

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


Re: Strict tuples

2006-03-21 Thread Taral
On 3/18/06, Manuel M T Chakravarty [EMAIL PROTECTED] wrote:
 Of course, the caller could invoke addmul using a bang patterns, as in

   let ( !s, !p ) = addmul x y
   in ...

 but that's quite different to statically knowing (from the type) that
 the two results of addmul will already be evaluated.  The latter leaves
 room for more optimisations.

I looked back at this, and I'm not sure that this statement (which
appears to be the core reason for considering this) is true at all. I
don't see that more optimization follows from the availability of
information regarding the strictness of a function result's
subcomponents.

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


Re: Time Library

2006-03-21 Thread Taral
On 3/21/06, Ashley Yakeley [EMAIL PROTECTED] wrote:
 Not usefully.

   data T a = MkT a
   data C a = T a = MkT a

 It's allowed, but it doesn't do what you probably want. All it does is
 change the type of the constructor MkT.

I think it also allows the inference of HasResolution a from Fixed a,
thus removing the HasResolution condition on your instances.

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


Re: Time Library

2006-03-19 Thread Taral
On 3/19/06, Ashley Yakeley [EMAIL PROTECTED] wrote:
 1. Adding my Data.Fixed module to the base package.
   http://semantic.org/TimeLib/doc/html/Data-Fixed.html
   http://darcs.haskell.org/packages/time/fixed/Data/Fixed.hs

When would you used a (Fixed a) without (HasResolution a)?

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


Re: alternative translation of type classes to CHR(was:relaxedinstance rules spec)

2006-03-13 Thread Taral
On 3/13/06, Claus Reinke [EMAIL PROTECTED] wrote:
 [still talking to myself..?]

This is all wonderful stuff! Are you perhaps planning to put it all
together into a paper?

What effect do you think this can have on existing algorithms to resolve FDs?

--
Taral [EMAIL PROTECTED]
Computer science is no more about computers than astronomy is about
telescopes.
-- Edsger Dijkstra
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Implicit Prelude (was Re: Export lists in modules)

2006-02-23 Thread Taral
On 2/23/06, Ben Rudiak-Gould [EMAIL PROTECTED] wrote:
 In fact, this suggests a compromise: how about implicitly importing the
 Prelude only if the module header is omitted? That way there'll be no impact
 on short (single-module) programs.

+1

--
Taral [EMAIL PROTECTED]
Computer science is no more about computers than astronomy is about
telescopes.
-- Edsger Dijkstra
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Comment Syntax

2006-02-02 Thread Taral
On 2/2/06, Wolfgang Jeltsch [EMAIL PROTECTED] wrote:
 Am Montag, 30. Januar 2006 17:24 schrieb Taral:
  On 1/30/06, Thomas Davie [EMAIL PROTECTED] wrote:
   It gives you regexp and nothing more - this makes it a pain in the
   arse to input every possible character that is/isn't allowed.
 
  Steal it from places (vim):
 
  syn match   hsLineComment  ---*\([^-!#$%\*\+./=[EMAIL 
  PROTECTED]|~].*\)\?$

 What about Unicode?

Got a unicode-compliant compiler?

--
Taral [EMAIL PROTECTED]
Computer science is no more about computers than astronomy is about
telescopes.
-- Edsger Dijkstra
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Unary operators [was: Re: ~ patterns]

2006-02-02 Thread Taral
On 2/2/06, Benjamin Franksen [EMAIL PROTECTED] wrote:
 This would open the possibility to allow unary (prefix) operators in
 general which I find rather more useful than sections.

Down that road lies APL.

--
Taral [EMAIL PROTECTED]
Computer science is no more about computers than astronomy is about
telescopes.
-- Edsger Dijkstra
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Unicode, was Comment Syntax

2006-02-02 Thread Taral
On 2/2/06, John Meacham [EMAIL PROTECTED] wrote:
 but it currently doesn't recognize any unicode characters as possible
 operators. which it should, but I am just not sure how to specify that
 yet until some sort of standard develops. Once there are more unicode
 compliant compilers out there something will evolve probably.

Character attributes are defined in unicode:

http://www.unicode.org/Public/UNIDATA/

It's just a matter of mapping. Perhaps this is worth considering
amending for Haskell'? The Haskell98 grammar talks about symbol,
uppercase, lowercase, while Unicode is a bit more... diverse.

--
Taral [EMAIL PROTECTED]
Computer science is no more about computers than astronomy is about
telescopes.
-- Edsger Dijkstra
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime