Re: [Haskell-cafe] abs minBound < (0 :: Int) && negate minBound == (minBound :: Int)

2013-08-20 Thread Ketil Malde

> fact 0 = 1
> fact n = n * fact (n-1)
>
> Now I ran it as fact 100 with signature Int -> Int and with
> Integer -> Integer
>
> In the first case I got 0 in about 3 seconds
  [...]
> And if that sounds like a unreal argument, consider representing and
> storing Graham's number.

So, since computers are finite anyway, we can just arbitrarily (well,
almost) redefine large constants, and set all factorials above some
threshold to zero?  Perhaps we should also set pi=3, that would simplify
lots of things :-)

> Pragmatically: 32-bits is unwise for a bank-balance, 64 should be a
> bit more safe

Please start a bank using modulo arithmetic, I'm looking forward to
overdrafting my account!  

> So yes, Haskell's Int, should have been called FastInt or Int29 or somethin'

On a more serious note, I accept that Int (and other limited precision
numbers) is a fact of life, and sometimes useful for performance
reasons.  

I would have liked, however, to have a compiler option or some other way
to make my programs throw an exception on overflow - even if this turned
out to be slower, I could at least use it when testing my programs,
which would have caught a few bugs.

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

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


Re: [Haskell-cafe] abs minBound < (0 :: Int) && negate minBound == (minBound :: Int)

2013-08-20 Thread Richard A. O'Keefe

On 20/08/2013, at 6:44 PM, Kyle Miller wrote:
> By "working as expected" I actually just meant that they distribute (as in 
> a(b+c)=ab+ac) and commute (ab=ba and a+b=b+a),

That is a tiny fraction of "working as expected".
The whole "modular arithmetic" argument would come close to
having some virtue, *except* that division just plain does not
fit.  In particular, it's painfully easy to find x y such that
 (x*y) div y is not congruent to x modulo 2**n.

The existence of division makes the "everything's OK because
it's modular" argument look very sick indeed.

>  The interpretation of any of these numbers being positive or negative is 
> specious, but people still do it because it works reasonably well for small 
> integers.

No, they do it because their programming language specifications
encourage them to do it, because their introductory courses teach
them to do it, and their compilers, on seeing x < 0, do not scream
at them "that is not well defined!", so the idea that it is
supposed to work is constantly reinforced.  And above all, "people
still do it because" in most programming languages they have no
practical alternative.

>  Also, there's the definite advantage that you can use the same instructions 
> for adding/multiplying signed and unsigned integers (for instance, pointer 
> arithmetic).

As the user of a programming language, what conceivable advantage
is that to me?  All the machines I have access to these days have
two sets of multiply and divide instructions, and there have been
machines with two sets of add and subtract instructions, and it is
no big deal.

The B6700 had one set of instructions (which actually dealt with both
integers and floating point).  It didn't have _any_ instructions for
unsigned integer arithmetic, and Fortran, COBOL, BASIC, Pascal, Algol,
and PL/I programmers didn't miss them.  (In particular, to a B6700
programmer familiar with his/her machine's instruction set, the idea
that variable access might have anything to do with unsigned
operations would have seemed, heck, did seem quite bizarre.)

For that matter, IBM mainframes have had, since the 1960s,
A   signed Add
AL  unsigned Add Logical
S   signed Subtract
SL  unsigned Subtract Logical
M   signed Multiply \ 
ML  unsigned Multiply Logical   | these four
D   signed Divide   | are common
DL  unsigned Divide Logical /
and it never stopped them being fast.  I doubt that the presence of
these instructions had any significant effect on the complexity of
the machines.  Even some 1980s single-chip machines did this.

> You mention that the B6700 trapped on overflows.  While this is a nice 
> feature, this has nothing to do with the number format.

That's half true.  The B6700 number format was such that there was nothing
sensible they _could_ do on integer overflow.  (Look it up or trust me;
truncation would have been violently unnatural on those lovely machines.)

> One example of a nice thing about doing computations modulo 2^n is that you 
> can do a bit twiddling trick called reciprocal multiplication (maybe 
> sometimes called magic number multiplication).  One reference for this is at 
> [1].  Another reference is Hacker's Delight.  But maybe you can save this for 
> your ear's fingers.

I have a copy of Hacker's Delight within arm's reach.
This is not really something that people writing applications want.
Usually, what they need is affordable multiplication and division
that give right answers when right answers are to be had and don't
drive the program insane with rubbish when right answers are not to
be had.

There are plenty of clever things computer architects can do, up to
and including keeping a "last divisor" cache in the division unit
to accelerate divisions that reuse a recent divisor.

> I can't really say I understand why anyone would actually want to use Int 
> (unless they knew they wanted a modulo 2^n Int).

Because they are calling an existing function that requires it.

It's just like the question "the only integral type in standard C that
*cannot* be used safely to hold an 8-bit character is char, so why
would anyone want to use char*?"  Answer: "because of all the library
functions that demand it."

> but Integer is actually (if you're using GMP with your ghc):

Yes, that's tolerably well known.  You only pay the space overhead
when you need it (like Lisp or Smalltalk).  But you always pay the
time overhead.

> Where are you getting that about C?  Do you mean that it's careful to allow 
> implementations to decide to trap overflows?  Because as far as I can tell, 
> the C standard just says signed overflows give undefined behavior.

The thing is that the standardisers *could* have defined signed int arithmetic
to wrap (just like the benighted Java designers did) but they *chose* to leave
the effect undefined (just like the Pascal standard) *so that* implem

Re: [Haskell-cafe] ANN: hspec-test-framework - Run test-framework tests with Hspec

2013-08-20 Thread Roman Cheplyaka
My answer to this and many similar questions regarding tasty is:

- I am probably not going to work on this
- but I would be happy to see someone doing it

Note that hspec-test-framework is a separate package, and it didn't have
to be written or even approved by Simon. Same here — please write more
supplementary packages if you feel a need.

Roman

* Alfredo Di Napoli  [2013-08-18 15:18:07+0200]
> Hi Simon,
> 
> this is an exciting news!
> 
> May I ask the question that maybe is lurking in the shadow?
> 
> Due to the recent announcement of Roman's "tasty" library, are there plans
> to basically release something similar to hspec-test-framework and
> hspec-test-framework-th but targeting tasty instead?
> 
> Bye :)
> A.
> 
> 
> On 18 August 2013 14:50, Simon Hengel  wrote:
> 
> > Hi,
> > I just released hspec-test-framework[1] and hspec-test-framework-th[2]
> > to Hackage.
> >
> > They can be used to run test-framework tests with Hspec unmodified.
> >
> > This can also be used to work around test-framework's incompatibility
> > with QuickCheck-2.6 and base-4.7.0 ;)
> >
> > Have a look at the README for usage instructions:
> >
> > https://github.com/sol/hspec-test-framework#readme
> >
> > Cheers,
> > Simon
> >
> > [1] http://hackage.haskell.org/package/hspec-test-framework
> > [2] http://hackage.haskell.org/package/hspec-test-framework-th
> >
> > ___
> > 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



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


Re: [Haskell-cafe] [Haskell] ANNOUNCE: haskell-src-exts 1.14.0

2013-08-20 Thread Tommy Thorn
On Aug 20, 2013, at 02:19 , Niklas Broberg  wrote:
> Sadly not - it's theoretically impossible. The fact that you can put comments 
> literally wherever, means that it's impossible to treat them as nodes of the 
> AST. E.g.
> 
>   f {- WHERE -} x = -- WOULD
>   -- THESE
>   do -- COMMENTS
>  a {- END -} <- g x -- UP
>  return {- ? -} a

"Theoretically impossible". I wouldn't say so. In fact, a system like this
was implemented for BETA in the mid 1980'es [1].  The comments where
attached to the nearest AST node in an expanded AST.  While not _perfect_,
it worked pretty well. Granted, it likely is much harder to do for Haskell than
BETA, but impossible is a strong word.

Tommy
[1] http://www.cs.au.dk/~beta/doc/mjolner-overview/mjolner-overview.pdf


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


Re: [Haskell-cafe] [Haskell] ANNOUNCE: haskell-src-exts 1.14.0

2013-08-20 Thread Tommy Thorn
+1

When I worked on the font-lock support for haskell-mode, the irony
of trying to approximate the classification that the hugs/ghc/whatnot parser
was already doing wasn't lost on me.  I still would like to tap into more
of the knowledge generated and lost in the compiler:

- A list of all tokens (source position, span, classification). Comments are 
conventionally
  treated as whitespace, but it's not very hard to capture them before dropping
  them.

- All identifiers can be classified into def and use with enough lexical scope 
information
  to get from use to def and from def to all uses. Take this one step further 
and type
  information can be stored with the def.

- Tokens should be mapped to the underlying AST if possible, and vice versa.

I'm sure there's more, but with this, one could build an awesome editor, code 
navigator.

I think it's possible, but I don't have time to work on it, alas. I'd like 
suggestions as to
to realize this.

Tommy -- ponding hacking the parser combinators to keep this information.





On Aug 20, 2013, at 03:00 , Niklas Hambüchen  wrote:

> On 20/08/13 18:19, Niklas Broberg wrote:
>> Sadly not - it's theoretically impossible. The fact that you can put
>> comments literally wherever, means that it's impossible to treat them as
>> nodes of the AST. E.g.
>> 
>>  f {- WHERE -} x = -- WOULD
>>  -- THESE
>>  do -- COMMENTS
>> a {- END -} <- g x -- UP
>> return {- ? -} a
> 
> Oh, I see what you mean.
> 
> I guess what I mean instead is:
> 
> * A lex list that contains *everything*, including comments and white space
> 
> * A full syntax tree of which each node points to (indexes) a position
> in the lex list to get the precise original position; comments in
> between two nodes can then be determined and more easily played with
> because they are between their positions in the lex list
> 
> * An abstract syntax tree that has whitespace and comments discarded
> (what HSE has now)
> 
> ___
> 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] ANNOUNCE: posix-paths, for faster file system operations

2013-08-20 Thread Niklas Hambüchen
John Lato and I would like to announce our posix-paths package.

https://github.com/JohnLato/posix-paths

It implements a large portion of System.Posix.FilePath using ByteString
based RawFilePaths instead of String based FilePaths, and on top of that
provides a Traversal module with a fast replacement for
`getDirectoryContents` and a recursive `allDirectoryContents`.

`getDirectoryContents` is (unsurprisingly?) really slow.
Our replacement is 11 times faster in the recursive use case [1], and
only 20% slower than `find`.

Benchmarks are at [2], code is at [3].

We hope that these improvements will eventually make it into base some day.

Until then, we propose our package as a base for discussion and further
improvements.

Contributions are welcome:
Some FilePath operations are not in it yet (especially the Windows /
drive related ones), and our traversals might not work on Windows.
We would also appreciate some thorough looks at their low level
implementations.
If you find our benchmarks against getDirectoryContents unfair or would
like to add another one, please send a pull request.

We have been running this on Linux production machines for a few months
now, and are pleased by the speed-up.



[1] For the recursive version of the original `getDirectoryContents`, we
used the implementation given in Real World Haskell:
http://book.realworldhaskell.org/read/io-case-study-a-library-for-searching-the-filesystem.html

[2] Benchmarks:
On a real file system: http://johnlato.github.io/posix-paths/usrLocal.html
On tmpfs: http://johnlato.github.io/posix-paths/tmpfs.html (note that
here find is slow because of process starting overhead)

[3] Code:
Github: https://github.com/JohnLato/posix-paths
RawFilePath operations:
https://github.com/JohnLato/posix-paths/blob/master/src/System/Posix/FilePath.hs
Traversals:
https://github.com/JohnLato/posix-paths/blob/master/src/System/Posix/Directory/Traversals.hs
Benchmarks:
https://github.com/JohnLato/posix-paths/blob/master/benchmarks/Bench.hs

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


[Haskell-cafe] A question about laziness and performance in document serialization.

2013-08-20 Thread Kyle Hanson
So I am not entirely clear on how to optimize for performance for lazy
bytestrings.

Currently I have a (Lazy) Map that contains large BSON values (more than
1mb when serialized each). I can serialize BSON documents to Lazy
ByteStrings using Data.Binary.runPut. I then write this bytestring to a
socket using Network.Socket.ByteString.Lazy.

My question is this, if the Map object doesn't change (no updates) when it
serializes the same document to the socket 2x in a row, does it re-evaluate
the whole BSON value and convert it to a bytestring each time?

Lets say I wanted to have a cache of bytestings so I have another Map
object that has the serialized bytestrings that I populate it with every
time the original BSON Map changes. Should the map be strict or lazy?
Should the bytestrings it stores be strict or lazy?

Any help in understanding laziness would be appreciated.

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


[Haskell-cafe] Looking for ICFP roommate

2013-08-20 Thread Conal Elliott
I'm looking for an ICFP roommate. I plan to attend Sunday through Saturday
and stay the nights of Saturday the 21st through Saturday the 28th. I
missed the discounted price of $225 (yipes) at the Airport Hilton (sold
out). Perhaps someone already has a room reserved with two beds or could
switch to one with two beds and would like to reduce their cost by
room-sharing for part or all of their stay. If so, please let me know.

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


Re: [Haskell-cafe] What am I missing? Cycle in type synonym declarations

2013-08-20 Thread David Fox
On Tue, Aug 20, 2013 at 2:35 PM, adam vogt  wrote:
> On Tue, Aug 20, 2013 at 5:00 PM, David Fox  wrote:
>> This file gives me the error "Cycle in type synonym declarations"  Can
>> anyone tell me why?  I'm just trying to write a function to create a
>> type that is a FooT with the type parameter fixed.
>>
>> {-# LANGUAGE TemplateHaskell #-}
>> import Language.Haskell.TH (Q, Dec, TypeQ)
>>
>> data FooT a = FooT a
>>
>> foo :: TypeQ -> Q [Dec]
>> foo t = [d| type Bar = FooT $t |]
>
> Hi David,
>
> That's strange considering you can accomplish  the same thing with:
>
> foo t = fmap (:[]) $ tySynD (mkName "Bar") [] [t| FooT $t |]
>
> Bugs like  are a similar
> problem. In your case it seems that GHC is too eager to prevent the
> cycle you could make with  foo (conT (mkName "Bar")))
>
> Regards,
> Adam

Thanks Adam, this must be the answer.  And thanks for the equivalent expression.

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


Re: [Haskell-cafe] What am I missing? Cycle in type synonym declarations

2013-08-20 Thread adam vogt
On Tue, Aug 20, 2013 at 5:00 PM, David Fox  wrote:
> This file gives me the error "Cycle in type synonym declarations"  Can
> anyone tell me why?  I'm just trying to write a function to create a
> type that is a FooT with the type parameter fixed.
>
> {-# LANGUAGE TemplateHaskell #-}
> import Language.Haskell.TH (Q, Dec, TypeQ)
>
> data FooT a = FooT a
>
> foo :: TypeQ -> Q [Dec]
> foo t = [d| type Bar = FooT $t |]

Hi David,

That's strange considering you can accomplish  the same thing with:

foo t = fmap (:[]) $ tySynD (mkName "Bar") [] [t| FooT $t |]

Bugs like  are a similar
problem. In your case it seems that GHC is too eager to prevent the
cycle you could make with  foo (conT (mkName "Bar")))

Regards,
Adam

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


Re: [Haskell-cafe] What am I missing? Cycle in type synonym declarations

2013-08-20 Thread jabolopes
Hi,

In this case, you have two 'FooT' names: one is the Type and the other
is the Constructor.  Perhaps Template Haskell is capturing the wrong
one inside the quote (probably the constructor).  When you have name
shadowing, you should always use a lookup function.  You can find
these lookup functions in the Template Haskell library.

In the meantime, just for a quick test, you can try to change the name
of the constructor to something else to avoid capturing, and you can
see if the rest of the code works.

Jose

On Tue, Aug 20, 2013 at 02:00:29PM -0700, David Fox wrote:
> This file gives me the error "Cycle in type synonym declarations"  Can
> anyone tell me why?  I'm just trying to write a function to create a
> type that is a FooT with the type parameter fixed.
> 
> {-# LANGUAGE TemplateHaskell #-}
> import Language.Haskell.TH (Q, Dec, TypeQ)
> 
> data FooT a = FooT a
> 
> foo :: TypeQ -> Q [Dec]
> foo t = [d| type Bar = FooT $t |]
> 
> ___
> 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] What am I missing? Cycle in type synonym declarations

2013-08-20 Thread David Fox
This file gives me the error "Cycle in type synonym declarations"  Can
anyone tell me why?  I'm just trying to write a function to create a
type that is a FooT with the type parameter fixed.

{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH (Q, Dec, TypeQ)

data FooT a = FooT a

foo :: TypeQ -> Q [Dec]
foo t = [d| type Bar = FooT $t |]

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


Re: [Haskell-cafe] wxHaskell mailinglist

2013-08-20 Thread Henk-Jan van Tuyl
On Tue, 20 Aug 2013 15:24:41 +0200, Nathan Hüsken  
 wrote:



Hey,

Then something is wrong. When I try to subscribe here:
https://lists.sourceforge.net/lists/listinfo/wxhaskell-users

I get a mail: Mailman privacy alert, telling me that I am already  
subscribed.


But when I send a mail to: wxhaskell-us...@lists.sourceforge.net

I get a mail: Your message to wxhaskell-users awaits moderator approval
The reason it is being held:
Post to moderated list

I am sure I used the same address. Am I confusing something? Or is  
something wrong with the list?




It seems that there is something wrong with the settings of the mailing  
list; I cc-ed the mailing list owners.


Regards,
Henk-Jan van Tuyl


--
Folding@home
What if you could share your unused computer power to help find a cure? In  
just 5 minutes you can join the world's biggest networked computer and get  
us closer sooner. Watch the video.

http://folding.stanford.edu/


http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
Haskell programming
--

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


[Haskell-cafe] monoids induced by Applicative/Alternative/Monad/MonadPlus?

2013-08-20 Thread Petr Pudlák
Dear Haskellers,

are these monoids defined somewhere?

import Control.Applicativeimport Data.Monoid
newtype AppMonoid m a = AppMonoid (m a)instance (Monoid a, Applicative
m) => Monoid (AppMonoid m a) where
mempty = AppMonoid $ pure mempty
mappend (AppMonoid x) (AppMonoid y) = AppMonoid $ mappend <$> x
<*> y-- With the () monoid for `a` this becames the monoid of effects.
newtype AltMonoid m a = AltMonoid (m a)instance Alternative m =>
Monoid (AltMonoid m a) where
mempty = AltMonoid empty
mappend (AltMonoid x) (AltMonoid y) = AltMonoid $ x <|> y

(and similarly for Monad/MonadPlus, until they become subclasses of
Applicative?)

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


Re: [Haskell-cafe] Compiling stringable with GHC 7.0.4

2013-08-20 Thread Ketil Malde

I took the liberty of implementing this fix and uploading
stringable-0.1.1.1 to HackageDB.  I tested it on GHC 7.0.4 (you know,
shipped with the cutting-edge Fedora distribution one year ago, but
ancient and no longer to be bothered with by Haskell standards :-) and
on 7.6.2.

-k

Ketil Malde  writes:

> Hi,
>
> ---
> I don't think FlexibleInstances works with this GHC, I get:
>
> % cabal install --prefix=$G stringable
> Resolving dependencies...
> Configuring stringable-0.1.1...
> Building stringable-0.1.1...
> Preprocessing library stringable-0.1.1...
> [1 of 1] Compiling Data.Stringable  ( Data/Stringable.hs, 
> dist/build/Data/Stringable.o )
>
> Data/Stringable.hs:54:10:
> Illegal instance declaration for `Stringable String'
>   (All instance types must be of the form (T t1 ... tn)
>where T is not a synonym.
>Use -XTypeSynonymInstances if you want to disable this.)
> In the instance declaration for `Stringable String'
> ---
>
> I changed the first line of Data/Stringable.hs to:
>
> {-# LANGUAGE FlexibleInstances, TypeSynonymInstances #-}
>
> and then it compiled.  Is there any reason not to retain the TSI pragma?
>
> -k


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

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


Re: [Haskell-cafe] abs minBound < (0 :: Int) && negate minBound == (minBound :: Int)

2013-08-20 Thread Ketil Malde

Richard A. O'Keefe  writes:

>> I think a better argument for twos complement is that you're just
>> doing all of your computations modulo 2^n (where n is 32 or 64 or
>> whatever), and addition and multiplication work as expected modulo
>> anything.

> To me, that's not a better argument.  It isn't even a _good_ argument.
> It amounts to saying "if you do things wrong, you can justify it by
> saying you're really doing something else right, and it's the programmer's
> fault for wanting the wrong thing."

Not only that, but in Haskell, you don't really know 'n', it is only
specified to be at least 23, or something like that.  Which basically
means that any code that relies on this behaviour without rigorously
checking it basically is wrong.

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

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


Re: [Haskell-cafe] abs minBound < (0 :: Int) && negate minBound == (minBound :: Int)

2013-08-20 Thread Rustom Mody
On Tue, Aug 20, 2013 at 6:37 AM, Richard A. O'Keefe  wrote:
>
> On 20/08/2013, at 3:43 AM, Kyle Miller wrote:
>
>> On Sun, Aug 18, 2013 at 8:04 PM, Richard A. O'Keefe  
>> wrote:
>> The argument for twos-complement, which always puzzled me, is that the other
>> systems have two ways to represent zero.  I never found this to be a problem,
>> not even for bitwise operations, on the B6700.  I *did* find "abs x < 0"
>> succeeding to be a pain in the posterior.  (The B6700 had two different 
>> tests:
>> 'are these two numbers equal' and 'are these two bit patterns equal'.)
>>
>> I think a better argument for twos complement is that you're just doing all 
>> of your computations modulo 2^n (where n is 32 or 64 or whatever), and 
>> addition and multiplication work as expected modulo anything.
>
> To me, that's not a better argument.

These kinds of argument usually come down to a question of framing --
whether pragmatic, philosophical or pedagogical.  Let me start with
the philosophical

> It isn't even a _good_ argument.
> It amounts to saying "if you do things wrong, you can justify it by
> saying you're really doing something else right, and it's the programmer's
> fault for wanting the wrong thing."

This argument works if 'doing something right' is an available option.
 What if its not?

>
> One great thing about the B6700 was that you were guaranteed
> EITHER the mathematically correct answer in the numbers you were
> thinking in terms of OR an exception telling you the machine couldn't
> do what you wanted.  When it comes to *applications* programming,
> the number of times I have *wanted* arithmetic modulo 2^n (in the last
> 40 years) can be counted on the fingers of one ear.
>
> You may call it "multiplication work[ing] as expected" when the product of two
> positive numbers comes out negative; I call it a wrong answer.
>
> Prelude> let tens = 1 : map (*10) tens :: [Int]
> Prelude> take 19 tens
> [1,10,100,1000,1,10,
100,1000,1,
10,100,
1000,1,10,100,
1000,1,10,100]
> Prelude> [x * x | x <- take 19 tens]
> [1,100,1,100,1,100,
1,100,1,100,
7766279631452241920,1864712049423024128,2003764205206896640,
-2537764290115403776,4477988020393345024,5076944270305263616,
-8814407033341083648,4003012203950112768,-5527149226598858752]
>
> Yes, I know that Haskell has Integer.
> If I want to do more arithmetic than a bit of simple counting,
> I like to use it.
> The gibberish that Int multiplication spewed out above is why.
>
> Roughly speaking, there are three ways to handle integer
> arithmetic: the Lisp way, the Ada way, and the Java way.
> Lisp just gets it right (think Haskell's "Integer" type).
> Java *defines* wrong answers to be "right".
> Ada recognises that sometimes you want modular arithmetic (so it offers you
> modular types) and sometimes you don't (so it offers you bounded but
> non-modular types, where overflow is trapped).

This issue is really a specific instance of the question:
Are computers finite or infinite?

If one says finite then the infinite-taped Turing machine has nothing
to do with computers
If one says infinite then the abstraction we are talking of is
unrelated to the boxes on our desks/palmtops.

If one recognises that in juggling between these two views -- dare I
say a central project for a programmer?? -- we need to stuff an
infinite conceptual object into a finite actual one.  And in doing so
some corners will be cut willy-nilly.

So to say Lisp is 'right' because arithmetic does not overflow at
machine word size limits misses the fact that it overflows more
unpredictably when the machine memory fills out. Lets look at good ol
factorial

fact 0 = 1
fact n = n * fact (n-1)

Now I ran it as fact 100 with signature Int -> Int and with
Integer -> Integer

In the first case I got 0 in about 3 seconds
In the second... I thought I'd see what happens but after about 2
minutes of the CPU fans maxing out, firefox started giving me alarms
about an 'unresponsive script'; I felt my machine had had enough
punishment and gave in with C-c!

And if that sounds like a unreal argument, consider representing and
storing Graham's number.

Of course I am arguing philosophically not pragmatically.
Philosophically: Graham's number is 'just' a finite number, though a
rather obese one
Pragmatically: 32-bits is unwise for a bank-balance, 64 should be a
bit more safe

So coming to the pragmatic and to lisp...
I remember a story (maybe apocryphal) about a robot in the MIT(?) lab
that did a lot of clever things and then tumbled down the stairs. When
asked, the concerned researcher/academic shrugged it off: "It was
garbage collecting"

If the robot had been programmed in C its real-time behavior would
have been sturdier though its integer overflow properties would have
been flimsier.

Mor

Re: [Haskell-cafe] ANNOUNCE: haskell-src-exts 1.14.0

2013-08-20 Thread Dag Odenhall
Wouldn't it be better to only enable Haskell2010 and XmlSyntax and then
rely on LANGUAGE pragmas? I guess optimally we want to add support for
-Xoptions to
hsx2hs but in the mean time…

BTW I think hsx2hs is in fact affected by these backwards-incompatible
changes, and lacks an upper bound on its HSE dependency!

Is hub.darcs.net the official location of the hsx2hs repository these days?


On Tue, Aug 20, 2013 at 4:49 PM, Niklas Broberg wrote:

> HSE parses based on pragmas by default. This can be configured through the
> ParseMode [1].
>
> But your question regards HSP, Haskell Server Pages, which indeed just
> enables most extensions by default. Right now there's no way to configure
> that, but it shouldn't be hard for a skilled programmer to fix. Patches
> most welcome.  :-)
>
> Cheers, Niklas
>
> [1]
> http://hackage.haskell.org/packages/archive/haskell-src-exts/1.13.5/doc/html/Language-Haskell-Exts-Parser.html#t:ParseMode
>  On 20 Aug 2013 12:57, "Dag Odenhall"  wrote:
>
>> Good stuff!
>>
>> Is there any way, or plans for a way, to parse a file based on its
>> LANGUAGE pragmas? Last I checked e.g. HSP simply enabled all extensions
>> when parsing, which can cause code to be parsed incorrectly in some cases.
>>
>>
>> On Tue, Aug 20, 2013 at 10:15 AM, Niklas Broberg <
>> niklas.brob...@gmail.com> wrote:
>>
>>> Fellow Haskelleers,
>>>
>>> I'm pleased to announce the release of haskell-src-exts-1.14.0!
>>>
>>> * On hackage: http://hackage.haskell.org/package/haskell-src-exts
>>> * Via cabal: cabal install haskell-src-exts
>>> * git repo: 
>>> https://github.com/haskell-suite/haskell-src-exts
>>>
>>> There are two primary reasons for this release, and a number of smaller
>>> ones.
>>>
>>> The first primary reason is technical: haskell-src-exts 1.14 revamps the
>>> Extension datatype, among other things to allow turning extensions on and
>>> off (similar to what Cabal allows). We also introduce the concept of a
>>> Language, separate from a set of extensions. This is the only
>>> backwards-incompatible change in this release.
>>>
>>> The second reason is structural: haskell-src-exts is now part of a
>>> larger context -- the Haskell Suite. The package has a new home on github
>>> (see above), alongside its new cool friends: haskell-names and
>>> haskell-packages. There is also a really nice issue tracker there - please
>>> help me fill it, or better yet, empty it!
>>>
>>> What this release does *not* cover is support for the extensions added
>>> to GHC in recent time (with the exceptions of CApiFFI and
>>> InterruptibleFFI). Work is in progress on many of these, and there will be
>>> another major release not far off in the future.
>>>
>>>
>>> This release owes many thanks to Roman Cheplyaka in particular, as well
>>> as Erik Hesselink, Simon Meier and David Fox. Thanks a lot!
>>>
>>>
>>> Complete changelog:
>>>
>>> 1.13.6 --> 1.14.0
>>> ===
>>>
>>> * Modernize the Extension datatype in L.H.E.Extension, following the lead
>>>   of Cabal, to allow negative and positive extension modifiers (turning
>>>   features on and off). You need to worry about backwards-incompatible
>>>   changes if any of the following pertains to you:
>>>   1) If you use the Extension datatype programmatically - it has changed
>>>  significantly (see documentation).
>>>   2) The ParseMode record now has one more field
>>>  (baseLanguage :: Language), which might give you a type error.
>>>   3) The behavior of the (extensions :: [Extension]) field has changed,
>>>  which could bite you if you pass custom extensions in the
>>> ParseMode.
>>>  Previously, the ParseMode defaulted to the list of extensions
>>> accepted
>>>  by Haskell2010, and if you set the list explicitly you would
>>> override
>>>  this. Now, the defaults are { baseLanguage = Haskell2010,
>>> extensions = [] },
>>>  and explicitly setting a list of extensions will be interpreted on
>>> top of
>>>  Haskell2010. See further the documentation for L.H.E.Extension.
>>>
>>> * Add support for the 'capi' calling convention. It is enabled with the
>>> CApiFFI
>>>   extension. It's been included since GHC 7.4, and advertised since 7.6.
>>>
>>> * Add support for the 'interruptible' FFI safety annotation, enabled with
>>>   the InterruptibleFFI extension.
>>>
>>> * Give better error message when lexing newline fails. In particular,
>>> fix the bug
>>>   when the parser would crash if the file didn't end with a newline.
>>>
>>> * Support unboxed tuple expressions and patterns.
>>>
>>> * Fix bug in lexing of primitive integer literals in hex or octal
>>> notation.
>>>
>>> * Disallow negative primitive word literals
>>>   (such as W# (-0x8000##)).
>>>
>>> * Allow phase control for SPECIALIZE pragma.
>>>
>>> * Derive Foldable and Traversable instances for all annotated AST types.
>>>
>>> * Fix bug with pretty-printing WARNING and DEPRECATED pragmas.
>>>
>>>
>>> Cheers, Niklas
>>>
>>> --
>>

Re: [Haskell-cafe] ANNOUNCE: haskell-src-exts 1.14.0

2013-08-20 Thread Niklas Broberg
> The first primary reason is
> technical: haskell-src-exts
> 1.14 revamps the Extension
> datatype, among other things
> to allow turning extensions on
> and off (similar to what Cabal
> allows). We also introduce the
> concept of a Language,
> separate from a set of
> extensions. This is the only
> backwards-incompatible
> change in this release.

Heads-up: as was pointed out to me, the above is not true. The constructors
of the Tuple type have also changed, which means greater risks for
breakage. Proceed with this in mind.

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


Re: [Haskell-cafe] ANNOUNCE: haskell-src-exts 1.14.0

2013-08-20 Thread Niklas Broberg
HSE parses based on pragmas by default. This can be configured through the
ParseMode [1].

But your question regards HSP, Haskell Server Pages, which indeed just
enables most extensions by default. Right now there's no way to configure
that, but it shouldn't be hard for a skilled programmer to fix. Patches
most welcome.  :-)

Cheers, Niklas

[1]
http://hackage.haskell.org/packages/archive/haskell-src-exts/1.13.5/doc/html/Language-Haskell-Exts-Parser.html#t:ParseMode
On 20 Aug 2013 12:57, "Dag Odenhall"  wrote:

> Good stuff!
>
> Is there any way, or plans for a way, to parse a file based on its
> LANGUAGE pragmas? Last I checked e.g. HSP simply enabled all extensions
> when parsing, which can cause code to be parsed incorrectly in some cases.
>
>
> On Tue, Aug 20, 2013 at 10:15 AM, Niklas Broberg  > wrote:
>
>> Fellow Haskelleers,
>>
>> I'm pleased to announce the release of haskell-src-exts-1.14.0!
>>
>> * On hackage: http://hackage.haskell.org/package/haskell-src-exts
>> * Via cabal: cabal install haskell-src-exts
>> * git repo: 
>> https://github.com/haskell-suite/haskell-src-exts
>>
>> There are two primary reasons for this release, and a number of smaller
>> ones.
>>
>> The first primary reason is technical: haskell-src-exts 1.14 revamps the
>> Extension datatype, among other things to allow turning extensions on and
>> off (similar to what Cabal allows). We also introduce the concept of a
>> Language, separate from a set of extensions. This is the only
>> backwards-incompatible change in this release.
>>
>> The second reason is structural: haskell-src-exts is now part of a larger
>> context -- the Haskell Suite. The package has a new home on github (see
>> above), alongside its new cool friends: haskell-names and haskell-packages.
>> There is also a really nice issue tracker there - please help me fill it,
>> or better yet, empty it!
>>
>> What this release does *not* cover is support for the extensions added to
>> GHC in recent time (with the exceptions of CApiFFI and InterruptibleFFI).
>> Work is in progress on many of these, and there will be another major
>> release not far off in the future.
>>
>>
>> This release owes many thanks to Roman Cheplyaka in particular, as well
>> as Erik Hesselink, Simon Meier and David Fox. Thanks a lot!
>>
>>
>> Complete changelog:
>>
>> 1.13.6 --> 1.14.0
>> ===
>>
>> * Modernize the Extension datatype in L.H.E.Extension, following the lead
>>   of Cabal, to allow negative and positive extension modifiers (turning
>>   features on and off). You need to worry about backwards-incompatible
>>   changes if any of the following pertains to you:
>>   1) If you use the Extension datatype programmatically - it has changed
>>  significantly (see documentation).
>>   2) The ParseMode record now has one more field
>>  (baseLanguage :: Language), which might give you a type error.
>>   3) The behavior of the (extensions :: [Extension]) field has changed,
>>  which could bite you if you pass custom extensions in the ParseMode.
>>  Previously, the ParseMode defaulted to the list of extensions
>> accepted
>>  by Haskell2010, and if you set the list explicitly you would
>> override
>>  this. Now, the defaults are { baseLanguage = Haskell2010, extensions
>> = [] },
>>  and explicitly setting a list of extensions will be interpreted on
>> top of
>>  Haskell2010. See further the documentation for L.H.E.Extension.
>>
>> * Add support for the 'capi' calling convention. It is enabled with the
>> CApiFFI
>>   extension. It's been included since GHC 7.4, and advertised since 7.6.
>>
>> * Add support for the 'interruptible' FFI safety annotation, enabled with
>>   the InterruptibleFFI extension.
>>
>> * Give better error message when lexing newline fails. In particular, fix
>> the bug
>>   when the parser would crash if the file didn't end with a newline.
>>
>> * Support unboxed tuple expressions and patterns.
>>
>> * Fix bug in lexing of primitive integer literals in hex or octal
>> notation.
>>
>> * Disallow negative primitive word literals
>>   (such as W# (-0x8000##)).
>>
>> * Allow phase control for SPECIALIZE pragma.
>>
>> * Derive Foldable and Traversable instances for all annotated AST types.
>>
>> * Fix bug with pretty-printing WARNING and DEPRECATED pragmas.
>>
>>
>> Cheers, Niklas
>>
>> --
>> You received this message because you are subscribed to the Google Groups
>> "Haskell Server Pages" group.
>> To unsubscribe from this group and stop receiving emails from it, send an
>> email to haskell-server-pages+unsubscr...@googlegroups.com.
>> To post to this group, send email to
>> haskell-server-pa...@googlegroups.com.
>> Visit this group at http://groups.google.com/group/haskell-server-pages.
>> For more options, visit https://groups.google.com/groups/opt_out.
>>
>
>  --
> You received this message because you are subscribed to the Google Groups
> "Haskell Server Pages" group.
> To unsu

Re: [Haskell-cafe] wxHaskell mailinglist

2013-08-20 Thread Nathan Hüsken

Hey,

Then something is wrong. When I try to subscribe here:
https://lists.sourceforge.net/lists/listinfo/wxhaskell-users

I get a mail: Mailman privacy alert, telling me that I am already 
subscribed.


But when I send a mail to: wxhaskell-us...@lists.sourceforge.net

I get a mail: Your message to wxhaskell-users awaits moderator approval
The reason it is being held:
Post to moderated list

I am sure I used the same address. Am I confusing something? Or is 
something wrong with the list?


Regards,
Nathan

On 08/20/2013 02:49 PM, Henk-Jan van Tuyl wrote:
On Mon, 19 Aug 2013 20:18:53 +0200, Nathan Hüsken 
 wrote:


Anyone knows what the proper channel for reporting bugs and asking 
questions about wxHaskell is?
The github page https://github.com/wxHaskell/wxHaskell/wiki seems to 
have issues disabled, and when I post to the wxHaskell user 
mailinglist, it tells me that the list is moderated. But my post did 
not get accepted for the last 2 days.


Hello Nathan,

Bugs and feature requests can be entered at:
  http://sourceforge.net/p/wxhaskell/_list/tickets

The wxHaskell user mailing list is the right channel for questions; if 
you subscribe to the mailing list[0], your mails will not be moderated.


Regards,
Henk-Jan van Tuyl


[0] https://lists.sourceforge.net/lists/listinfo/wxhaskell-users





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


Re: [Haskell-cafe] wxHaskell mailinglist

2013-08-20 Thread Henk-Jan van Tuyl
On Mon, 19 Aug 2013 20:18:53 +0200, Nathan Hüsken  
 wrote:


Anyone knows what the proper channel for reporting bugs and asking  
questions about wxHaskell is?
The github page https://github.com/wxHaskell/wxHaskell/wiki seems to  
have issues disabled, and when I post to the wxHaskell user mailinglist,  
it tells me that the list is moderated. But my post did not get accepted  
for the last 2 days.


Hello Nathan,

Bugs and feature requests can be entered at:
  http://sourceforge.net/p/wxhaskell/_list/tickets

The wxHaskell user mailing list is the right channel for questions; if you  
subscribe to the mailing list[0], your mails will not be moderated.


Regards,
Henk-Jan van Tuyl


[0] https://lists.sourceforge.net/lists/listinfo/wxhaskell-users


--
Folding@home
What if you could share your unused computer power to help find a cure? In  
just 5 minutes you can join the world's biggest networked computer and get  
us closer sooner. Watch the video.

http://folding.stanford.edu/


http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
Haskell programming
--

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


Re: [Haskell-cafe] One-element tuple

2013-08-20 Thread AntC
> adam vogt  gmail.com> writes:
> 
> This preprocessor I just threw together doesn't seem to suffers from
> those issues . This kind of approach probably
> might let you steal T(..) while still allowing `T (..)' to refer to
> whatever is the original, though I think that would require working
> with the messier Annotated syntax tree.
> 

wow! Adam, thank you. 

Even copes with multiple nested parens nested parens

instance C ((a, b))  c  ...

==> instance C ((a, b)) (OneT.OneTuple (OneT.OneTuple c)) ...


AntC



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


Re: [Haskell-cafe] ANNOUNCE: haskell-src-exts 1.14.0

2013-08-20 Thread Dag Odenhall
Well if you enable TemplateHaskell then code like foo$bar gets a new
meaning and if you enable Arrows then proc is a reserved keyword, etc etc.


On Tue, Aug 20, 2013 at 1:06 PM, Mateusz Kowalczyk
wrote:

> On 20/08/13 11:56, Dag Odenhall wrote:
> > Good stuff!
> >
> > Is there any way, or plans for a way, to parse a file based on its
> LANGUAGE
> > pragmas? Last I checked e.g. HSP simply enabled all extensions when
> > parsing, which can cause code to be parsed incorrectly in some cases.
> >
> >
>
> Can you give any examples of such cases? I had recently been asked about
> this and could not come up with much at all.
>
>
> --
> Mateusz K.
>
> ___
> 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] ANNOUNCE: haskell-src-exts 1.14.0

2013-08-20 Thread Mateusz Kowalczyk
On 20/08/13 11:56, Dag Odenhall wrote:
> Good stuff!
> 
> Is there any way, or plans for a way, to parse a file based on its LANGUAGE
> pragmas? Last I checked e.g. HSP simply enabled all extensions when
> parsing, which can cause code to be parsed incorrectly in some cases.
> 
> 

Can you give any examples of such cases? I had recently been asked about
this and could not come up with much at all.


-- 
Mateusz K.


0x2ADA9A97.asc
Description: application/pgp-keys
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Haskell] ANNOUNCE: haskell-src-exts 1.14.0

2013-08-20 Thread AlanKim Zimmerman
This is not using haskell-src-exts, but the Haskell Refactorer has a
structure to keep a parallel tree of tokens indexed by SrcSpan, which
attempts to allocate comments to the appropriate point.

See
https://github.com/alanz/HaRe/blob/master/src/Language/Haskell/Refact/Utils/TokenUtils.hs.
It does not make use of the AST itself, so may be usable with
haskell-src-exts

Alan




On Tue, Aug 20, 2013 at 11:19 AM, Niklas Broberg
wrote:

> Hi Niklas,
>
> 1) My most desired feature would be a syntax tree that does not pluck
>> pluck comments out and make me treat them separately. It looks much
>> easier to me to have a fully descriptive tree and (filter . concatMap) /
>> traverse them out in some way than getting a list of comments and having
>> to insert them back in the right places myself.
>> Is that possible?
>>
>
> Sadly not - it's theoretically impossible. The fact that you can put
> comments literally wherever, means that it's impossible to treat them as
> nodes of the AST. E.g.
>
>   f {- WHERE -} x = -- WOULD
>   -- THESE
>   do -- COMMENTS
>  a {- END -} <- g x -- UP
>  return {- ? -} a
>
> What would be theoretically possible is to define a restricted language
> that allows comments only in certain well-defined places (cf haddock), and
> ignores any others. That's a lot of work though, and it's not clear how big
> the gain is. :-\
>
> A different solution could be to improve the support, through better
> helper functions, for handling a syntax tree and a list of comments
> together. That's something I think could be worthwhile.
>
>
>> 2) Have you considered downloading the all-of-Hackage tarball and
>> running haskell-src-exts over it to get a benchmark of how much HSE can
>> already parse of the Haskell code out there?
>>
>
> Considered, yes. Done, no. Would love to see the results :-). The crew at
> OdHac (Roman, Erik, Simon) ensured that the current version handles all of
> 'base', which is a good start.
>
> Cheers, Niklas
>
> ___
> 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] ANNOUNCE: haskell-src-exts 1.14.0

2013-08-20 Thread Dag Odenhall
Good stuff!

Is there any way, or plans for a way, to parse a file based on its LANGUAGE
pragmas? Last I checked e.g. HSP simply enabled all extensions when
parsing, which can cause code to be parsed incorrectly in some cases.


On Tue, Aug 20, 2013 at 10:15 AM, Niklas Broberg
wrote:

> Fellow Haskelleers,
>
> I'm pleased to announce the release of haskell-src-exts-1.14.0!
>
> * On hackage: http://hackage.haskell.org/package/haskell-src-exts
> * Via cabal: cabal install haskell-src-exts
> * git repo: 
> https://github.com/haskell-suite/haskell-src-exts
>
> There are two primary reasons for this release, and a number of smaller
> ones.
>
> The first primary reason is technical: haskell-src-exts 1.14 revamps the
> Extension datatype, among other things to allow turning extensions on and
> off (similar to what Cabal allows). We also introduce the concept of a
> Language, separate from a set of extensions. This is the only
> backwards-incompatible change in this release.
>
> The second reason is structural: haskell-src-exts is now part of a larger
> context -- the Haskell Suite. The package has a new home on github (see
> above), alongside its new cool friends: haskell-names and haskell-packages.
> There is also a really nice issue tracker there - please help me fill it,
> or better yet, empty it!
>
> What this release does *not* cover is support for the extensions added to
> GHC in recent time (with the exceptions of CApiFFI and InterruptibleFFI).
> Work is in progress on many of these, and there will be another major
> release not far off in the future.
>
>
> This release owes many thanks to Roman Cheplyaka in particular, as well as
> Erik Hesselink, Simon Meier and David Fox. Thanks a lot!
>
>
> Complete changelog:
>
> 1.13.6 --> 1.14.0
> ===
>
> * Modernize the Extension datatype in L.H.E.Extension, following the lead
>   of Cabal, to allow negative and positive extension modifiers (turning
>   features on and off). You need to worry about backwards-incompatible
>   changes if any of the following pertains to you:
>   1) If you use the Extension datatype programmatically - it has changed
>  significantly (see documentation).
>   2) The ParseMode record now has one more field
>  (baseLanguage :: Language), which might give you a type error.
>   3) The behavior of the (extensions :: [Extension]) field has changed,
>  which could bite you if you pass custom extensions in the ParseMode.
>  Previously, the ParseMode defaulted to the list of extensions
> accepted
>  by Haskell2010, and if you set the list explicitly you would override
>  this. Now, the defaults are { baseLanguage = Haskell2010, extensions
> = [] },
>  and explicitly setting a list of extensions will be interpreted on
> top of
>  Haskell2010. See further the documentation for L.H.E.Extension.
>
> * Add support for the 'capi' calling convention. It is enabled with the
> CApiFFI
>   extension. It's been included since GHC 7.4, and advertised since 7.6.
>
> * Add support for the 'interruptible' FFI safety annotation, enabled with
>   the InterruptibleFFI extension.
>
> * Give better error message when lexing newline fails. In particular, fix
> the bug
>   when the parser would crash if the file didn't end with a newline.
>
> * Support unboxed tuple expressions and patterns.
>
> * Fix bug in lexing of primitive integer literals in hex or octal notation.
>
> * Disallow negative primitive word literals
>   (such as W# (-0x8000##)).
>
> * Allow phase control for SPECIALIZE pragma.
>
> * Derive Foldable and Traversable instances for all annotated AST types.
>
> * Fix bug with pretty-printing WARNING and DEPRECATED pragmas.
>
>
> Cheers, Niklas
>
> --
> You received this message because you are subscribed to the Google Groups
> "Haskell Server Pages" group.
> To unsubscribe from this group and stop receiving emails from it, send an
> email to haskell-server-pages+unsubscr...@googlegroups.com.
> To post to this group, send email to haskell-server-pa...@googlegroups.com
> .
> Visit this group at http://groups.google.com/group/haskell-server-pages.
> For more options, visit https://groups.google.com/groups/opt_out.
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Haskell] ANNOUNCE: haskell-src-exts 1.14.0

2013-08-20 Thread Mateusz Kowalczyk
On 20/08/13 11:02, JP Moresmau wrote:
> BuildWrapper has some code that tries to link back the comments to the
> declaration from the AST generated by haskell-src-exts and the comments.
> See
> https://github.com/JPMoresmau/BuildWrapper/blob/master/src/Language/Haskell/BuildWrapper/Src.hs.
> The unit tests provide some samples:
> https://github.com/JPMoresmau/BuildWrapper/blob/master/test/Language/Haskell/BuildWrapper/CMDTests.hs#L572-L638.
> Maybe this can help you.
> 
> JP
It certainly look like I might be able to learn from this.

Thank you.
-- 
Mateusz K.


0x2ADA9A97.asc
Description: application/pgp-keys
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Haskell] ANNOUNCE: haskell-src-exts 1.14.0

2013-08-20 Thread Sean Leather
On Tue, Aug 20, 2013 at 11:19 AM, Niklas Broberg wrote:

> On Tue, Aug 20, 2013 at 10:48 AM, Niklas Hambüchen wrote:

 2) Have you considered downloading the all-of-Hackage tarball and
>>
> running haskell-src-exts over it to get a benchmark of how much HSE can
>> already parse of the Haskell code out there?
>>
>
> Considered, yes. Done, no. Would love to see the results :-). The crew at
> OdHac (Roman, Erik, Simon) ensured that the current version handles all of
> 'base', which is a good start.
>

See:

Nikolaos Bezirgiannis, Johan Jeuring and Sean Leather. Usage of Generic
Programming on Hackage - Experience Report. WGP 2013.
http://www.cs.uu.nl/research/techreps/repo/CS-2013/2013-014.pdf
http://hackage.haskell.org/package/gpah

Unfortunately, it seems we don't mention which version of haskell-src-exts
is used for the article. But I'm certain it's 1.13.*, probably 1.13.5.

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


Re: [Haskell-cafe] [Haskell] ANNOUNCE: haskell-src-exts 1.14.0

2013-08-20 Thread JP Moresmau
BuildWrapper has some code that tries to link back the comments to the
declaration from the AST generated by haskell-src-exts and the comments.
See
https://github.com/JPMoresmau/BuildWrapper/blob/master/src/Language/Haskell/BuildWrapper/Src.hs.
The unit tests provide some samples:
https://github.com/JPMoresmau/BuildWrapper/blob/master/test/Language/Haskell/BuildWrapper/CMDTests.hs#L572-L638.
Maybe this can help you.

JP


On Tue, Aug 20, 2013 at 11:21 AM, Mateusz Kowalczyk  wrote:

> On 20/08/13 09:48, Niklas Hambüchen wrote:
> > Nice!
> >
> > I hope that haskell-suite will eventually become awesome and solve most
> > of our automation-on-Haskell-code needs.
> >
> > Two questions:
> >
> > 1) My most desired feature would be a syntax tree that does not pluck
> > pluck comments out and make me treat them separately. It looks much
> > easier to me to have a fully descriptive tree and (filter . concatMap) /
> > traverse them out in some way than getting a list of comments and having
> > to insert them back in the right places myself.
> > Is that possible?
> >
> +1 for this. There was a small discussion relevant to this on café
> recently, if anyone is interested:
> http://comments.gmane.org/gmane.comp.lang.haskell.cafe/106768
>
> > 2) Have you considered downloading the all-of-Hackage tarball and
> > running haskell-src-exts over it to get a benchmark of how much HSE can
> > already parse of the Haskell code out there?
> >
> > Thanks!
> >
>
>
> --
> Mateusz K.
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>


-- 
JP Moresmau
http://jpmoresmau.blogspot.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Haskell] ANNOUNCE: haskell-src-exts 1.14.0

2013-08-20 Thread Niklas Hambüchen
On 20/08/13 18:19, Niklas Broberg wrote:
> Sadly not - it's theoretically impossible. The fact that you can put
> comments literally wherever, means that it's impossible to treat them as
> nodes of the AST. E.g.
> 
>   f {- WHERE -} x = -- WOULD
>   -- THESE
>   do -- COMMENTS
>  a {- END -} <- g x -- UP
>  return {- ? -} a

Oh, I see what you mean.

I guess what I mean instead is:

* A lex list that contains *everything*, including comments and white space

* A full syntax tree of which each node points to (indexes) a position
in the lex list to get the precise original position; comments in
between two nodes can then be determined and more easily played with
because they are between their positions in the lex list

* An abstract syntax tree that has whitespace and comments discarded
(what HSE has now)

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


Re: [Haskell-cafe] [Haskell] ANNOUNCE: haskell-src-exts 1.14.0

2013-08-20 Thread Mateusz Kowalczyk
On 20/08/13 09:48, Niklas Hambüchen wrote:
> Nice!
> 
> I hope that haskell-suite will eventually become awesome and solve most
> of our automation-on-Haskell-code needs.
> 
> Two questions:
> 
> 1) My most desired feature would be a syntax tree that does not pluck
> pluck comments out and make me treat them separately. It looks much
> easier to me to have a fully descriptive tree and (filter . concatMap) /
> traverse them out in some way than getting a list of comments and having
> to insert them back in the right places myself.
> Is that possible?
> 
+1 for this. There was a small discussion relevant to this on café
recently, if anyone is interested:
http://comments.gmane.org/gmane.comp.lang.haskell.cafe/106768

> 2) Have you considered downloading the all-of-Hackage tarball and
> running haskell-src-exts over it to get a benchmark of how much HSE can
> already parse of the Haskell code out there?
> 
> Thanks!
> 


-- 
Mateusz K.


0x2ADA9A97.asc
Description: application/pgp-keys
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Haskell] ANNOUNCE: haskell-src-exts 1.14.0

2013-08-20 Thread Niklas Broberg
Hi Niklas,

1) My most desired feature would be a syntax tree that does not pluck
> pluck comments out and make me treat them separately. It looks much
> easier to me to have a fully descriptive tree and (filter . concatMap) /
> traverse them out in some way than getting a list of comments and having
> to insert them back in the right places myself.
> Is that possible?
>

Sadly not - it's theoretically impossible. The fact that you can put
comments literally wherever, means that it's impossible to treat them as
nodes of the AST. E.g.

  f {- WHERE -} x = -- WOULD
  -- THESE
  do -- COMMENTS
 a {- END -} <- g x -- UP
 return {- ? -} a

What would be theoretically possible is to define a restricted language
that allows comments only in certain well-defined places (cf haddock), and
ignores any others. That's a lot of work though, and it's not clear how big
the gain is. :-\

A different solution could be to improve the support, through better helper
functions, for handling a syntax tree and a list of comments together.
That's something I think could be worthwhile.


> 2) Have you considered downloading the all-of-Hackage tarball and
> running haskell-src-exts over it to get a benchmark of how much HSE can
> already parse of the Haskell code out there?
>

Considered, yes. Done, no. Would love to see the results :-). The crew at
OdHac (Roman, Erik, Simon) ensured that the current version handles all of
'base', which is a good start.

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


Re: [Haskell-cafe] llvm on macos

2013-08-20 Thread Dominic Steinitz
Dominic Steinitz  steinitz.org> writes:

Thanks for all the help everyone :-)


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


Re: [Haskell-cafe] [Haskell] ANNOUNCE: haskell-src-exts 1.14.0

2013-08-20 Thread Niklas Hambüchen
Nice!

I hope that haskell-suite will eventually become awesome and solve most
of our automation-on-Haskell-code needs.

Two questions:

1) My most desired feature would be a syntax tree that does not pluck
pluck comments out and make me treat them separately. It looks much
easier to me to have a fully descriptive tree and (filter . concatMap) /
traverse them out in some way than getting a list of comments and having
to insert them back in the right places myself.
Is that possible?

2) Have you considered downloading the all-of-Hackage tarball and
running haskell-src-exts over it to get a benchmark of how much HSE can
already parse of the Haskell code out there?

Thanks!

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


[Haskell-cafe] ANNOUNCE: haskell-src-exts 1.14.0

2013-08-20 Thread Niklas Broberg
Fellow Haskelleers,

I'm pleased to announce the release of haskell-src-exts-1.14.0!

* On hackage: http://hackage.haskell.org/package/haskell-src-exts
* Via cabal: cabal install haskell-src-exts
* git repo: 
https://github.com/haskell-suite/haskell-src-exts

There are two primary reasons for this release, and a number of smaller
ones.

The first primary reason is technical: haskell-src-exts 1.14 revamps the
Extension datatype, among other things to allow turning extensions on and
off (similar to what Cabal allows). We also introduce the concept of a
Language, separate from a set of extensions. This is the only
backwards-incompatible change in this release.

The second reason is structural: haskell-src-exts is now part of a larger
context -- the Haskell Suite. The package has a new home on github (see
above), alongside its new cool friends: haskell-names and haskell-packages.
There is also a really nice issue tracker there - please help me fill it,
or better yet, empty it!

What this release does *not* cover is support for the extensions added to
GHC in recent time (with the exceptions of CApiFFI and InterruptibleFFI).
Work is in progress on many of these, and there will be another major
release not far off in the future.


This release owes many thanks to Roman Cheplyaka in particular, as well as
Erik Hesselink, Simon Meier and David Fox. Thanks a lot!


Complete changelog:

1.13.6 --> 1.14.0
===

* Modernize the Extension datatype in L.H.E.Extension, following the lead
  of Cabal, to allow negative and positive extension modifiers (turning
  features on and off). You need to worry about backwards-incompatible
  changes if any of the following pertains to you:
  1) If you use the Extension datatype programmatically - it has changed
 significantly (see documentation).
  2) The ParseMode record now has one more field
 (baseLanguage :: Language), which might give you a type error.
  3) The behavior of the (extensions :: [Extension]) field has changed,
 which could bite you if you pass custom extensions in the ParseMode.
 Previously, the ParseMode defaulted to the list of extensions accepted
 by Haskell2010, and if you set the list explicitly you would override
 this. Now, the defaults are { baseLanguage = Haskell2010, extensions =
[] },
 and explicitly setting a list of extensions will be interpreted on top
of
 Haskell2010. See further the documentation for L.H.E.Extension.

* Add support for the 'capi' calling convention. It is enabled with the
CApiFFI
  extension. It's been included since GHC 7.4, and advertised since 7.6.

* Add support for the 'interruptible' FFI safety annotation, enabled with
  the InterruptibleFFI extension.

* Give better error message when lexing newline fails. In particular, fix
the bug
  when the parser would crash if the file didn't end with a newline.

* Support unboxed tuple expressions and patterns.

* Fix bug in lexing of primitive integer literals in hex or octal notation.

* Disallow negative primitive word literals
  (such as W# (-0x8000##)).

* Allow phase control for SPECIALIZE pragma.

* Derive Foldable and Traversable instances for all annotated AST types.

* Fix bug with pretty-printing WARNING and DEPRECATED pragmas.


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