Re: Proposal: Fix a "bug" in the layout interpretation algorithm in Section 10.3 of Report 2010

2019-04-29 Thread Mario Blažević

On 2019-04-29 3:54 a.m., 佐藤玄基 wrote:

Hello,

I found that the layout interpretation algorithm in Section 10.3 of 
Report 2010

produces parse-error when applied to the following code snippet:

[Snippet 1 : The code that fails to be parsed by Report]
main = print t where { t = s where s = 1 :: Int }
[/Snippet 1]

GHC 8.4.4 and GHC 8.6.4 accept this code, which is a good behavior in my 
opinion.


	It's worth noting that the snippet is accepted by GHC even with 
-XAlternativeLayoutRule. Overall, I think I'd rather just have the 
concrete AlternativeLayoutRule algorithm in the specification than tweak 
the current broken and vague pseudo-code.




If we regard the behavior of those current GHCs as correct,
this "bug" in the Report lies in the following lines in the definition 
of the function L:


[Snippet 2 : A part of the layout interpretation algorithm in the Report]
L (} : ts) (0 : ms) = } : L ts ms (Note 3)
L (} : ts) ms = parse-error (Note 3)
[/Snippet 2]

I suggest this be modified to what follows:

[Snippet 3 : A Suggested modification to Snippet 2]
L (} : ts) (m : ms)
   | m == 0 = } : L ts ms
   | m > 0 = } : L (} : ts) ms
L (} : ts) [] = parse-error
[/Snippet 3]



Let me explain in detail.
First of all, how is Snippet 1 refused by the Report 2010 algorithm?
Let us emulate it by hand. Firstly pre-process Snippet 1:

[Snippet 4 : Pre-processed Snippet 1]
{1} main = print t where { t = s where {36} s = 1 :: Int }
[/Snippet 4]

I assumed that Snippet 1 is the only line in a file.
We may compute:

[Computation 5 : Apply L to Snippet 4]
L  []
  = "{ main = print t where { t = s where { s = 1 :: Int"
        ++ L "}" [36,0,1]
[/Computation 5]

Wait here. What does L do next?
Looking from top to bottom, we hit the second line in Snippet 2,
which leads us to parse-error.
Now you might expect that the line

[Snippet 6 : Another part of the Report algorithm]
L (t : ts) (m : ms) = } : (L (t : ts) ms)   if m /= 0 and parse-error(t) 
(Note 5)

[/Snippet 6]

would help, but unfortunately it doesn't work.
Even if we put aside the fact that Snippet 6 is lower in the text than 
Snippet 2
and has lower priority of execution according to the usual Haskell 
matching rule,

this line in L won't be triggered by this parse error at all,
since *parse-error('}') is false!*
Let us go back to the definition of parse-error(t).

[Quotation 7 : Note 5 in the Report algorithm]
The side condition parse-error(t) is to be interpreted as follows:
if the tokens generated so far by L together with the next token t
represent an invalid prefix of the Haskell grammar,
and the tokens generated so far by L followed by the token "}"
represent a valid prefix of the Haskell grammar, then parse-error(t) is 
true.

[/Quotation 7]

Now, this is the point.
In this case, "the tokens generated so far by L together with the next 
token t" is:


[Snippet 8]
{ main = print t where { t = s where { s = 1 :: Int }
[/Snippet 8]

This is a *valid prefix of the Haskell grammar*, and hence 
parse-error('}') is false.




Therefore, any Haskell2010-compliant compiler should reject Snippet 1,
and this doesn't seem to be any sensible choice of specification.
Speaking generally, I guess the Report 2010's authors wanted
the case where a inner implicit brace and a outer explicit brace is 
closed at the same time

to be processed by the rule in Snippet 6,
but it doesn't work since Snippet 2 is before Snippet 6 in the 
definition of L

and parse-error(t) is always false if t = '}'.

The fix of this problem is easy: replace Snippet 2 with Snippet 3.
The added case of m > 0 is doing almost the same thing as Snippet 6, but 
parse-error(t) is removed.

If we distinguish implicit close-braces and explicit close-braces,
the condition m > 0 fully does the job of parse-error('}'),
so I expect there will be no problem with this modification.



I apologize you if this long text has exhausted your eyes.
I hope this suggestion would help.

Sincerely yours,
Genki SATO

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime



___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime


Proposal: Fix a "bug" in the layout interpretation algorithm in Section 10.3 of Report 2010

2019-04-29 Thread 佐藤玄基
Hello,

I found that the layout interpretation algorithm in Section 10.3 of Report
2010
produces parse-error when applied to the following code snippet:

[Snippet 1 : The code that fails to be parsed by Report]
main = print t where { t = s where s = 1 :: Int }
[/Snippet 1]

GHC 8.4.4 and GHC 8.6.4 accept this code, which is a good behavior in my
opinion.
If we regard the behavior of those current GHCs as correct,
this "bug" in the Report lies in the following lines in the definition of
the function L:

[Snippet 2 : A part of the layout interpretation algorithm in the Report]
L (} : ts) (0 : ms) = } : L ts ms (Note 3)
L (} : ts) ms = parse-error (Note 3)
[/Snippet 2]

I suggest this be modified to what follows:

[Snippet 3 : A Suggested modification to Snippet 2]
L (} : ts) (m : ms)
  | m == 0 = } : L ts ms
  | m > 0 = } : L (} : ts) ms
L (} : ts) [] = parse-error
[/Snippet 3]



Let me explain in detail.
First of all, how is Snippet 1 refused by the Report 2010 algorithm?
Let us emulate it by hand. Firstly pre-process Snippet 1:

[Snippet 4 : Pre-processed Snippet 1]
{1} main = print t where { t = s where {36} s = 1 :: Int }
[/Snippet 4]

I assumed that Snippet 1 is the only line in a file.
We may compute:

[Computation 5 : Apply L to Snippet 4]
L  []
 = "{ main = print t where { t = s where { s = 1 :: Int"
   ++ L "}" [36,0,1]
[/Computation 5]

Wait here. What does L do next?
Looking from top to bottom, we hit the second line in Snippet 2,
which leads us to parse-error.
Now you might expect that the line

[Snippet 6 : Another part of the Report algorithm]
L (t : ts) (m : ms) = } : (L (t : ts) ms)   if m /= 0 and parse-error(t)
(Note 5)
[/Snippet 6]

would help, but unfortunately it doesn't work.
Even if we put aside the fact that Snippet 6 is lower in the text than
Snippet 2
and has lower priority of execution according to the usual Haskell matching
rule,
this line in L won't be triggered by this parse error at all,
since *parse-error('}') is false!*
Let us go back to the definition of parse-error(t).

[Quotation 7 : Note 5 in the Report algorithm]
The side condition parse-error(t) is to be interpreted as follows:
if the tokens generated so far by L together with the next token t
represent an invalid prefix of the Haskell grammar,
and the tokens generated so far by L followed by the token "}"
represent a valid prefix of the Haskell grammar, then parse-error(t) is
true.
[/Quotation 7]

Now, this is the point.
In this case, "the tokens generated so far by L together with the next
token t" is:

[Snippet 8]
{ main = print t where { t = s where { s = 1 :: Int }
[/Snippet 8]

This is a *valid prefix of the Haskell grammar*, and hence parse-error('}')
is false.



Therefore, any Haskell2010-compliant compiler should reject Snippet 1,
and this doesn't seem to be any sensible choice of specification.
Speaking generally, I guess the Report 2010's authors wanted
the case where a inner implicit brace and a outer explicit brace is closed
at the same time
to be processed by the rule in Snippet 6,
but it doesn't work since Snippet 2 is before Snippet 6 in the definition
of L
and parse-error(t) is always false if t = '}'.

The fix of this problem is easy: replace Snippet 2 with Snippet 3.
The added case of m > 0 is doing almost the same thing as Snippet 6, but
parse-error(t) is removed.
If we distinguish implicit close-braces and explicit close-braces,
the condition m > 0 fully does the job of parse-error('}'),
so I expect there will be no problem with this modification.



I apologize you if this long text has exhausted your eyes.
I hope this suggestion would help.

Sincerely yours,
Genki SATO
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime


[Haskell-cafe] Are type families really this slow, or is this a GHC bug?

2013-07-26 Thread Mike Izbicki
I'm using the TypeFamilies extension to generate types that are quite
large.  GHC can handle these large types fine when they are created
manually, but when type families get involved, GHC's performance dies.
It's doing in quadratic time what looks to me like it should be linear
time.  I don't know if this is expected behavior, if I'm doing something
wrong, or if this is a GHC bug.

I've attached a code sample below that demonstrates the problem.  Types.hs
generates other haskell files.  The first parameter is the size of the type
(which is type list of that length), and the second specifies which test to
run.  All tests generate the same type in the end, but some use type
families and some don't.

Here's an example of running it:

These tests show quadratic time when using the type family.  I have to
increase the context stack size to be greater than the recursion depth of
the type family.  I don't know if this is a bad sign or to be expected.

$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 7.6.3
$ ghc Types

$ ./Types 200 a  test.hs  time ghc test.hs  /dev/null
-fcontext-stack=250
real0m2.973s
$ ./Types 300 a  test.hs  time ghc test.hs  /dev/null
-fcontext-stack=350
real0m6.018s
$ ./Types 400 a  test.hs  time ghc test.hs  /dev/null
-fcontext-stack=450
real0m9.995s
$ ./Types 500 a  test.hs  time ghc test.hs  /dev/null
-fcontext-stack=550
real0m15.645s

Without the type family, I get MUCH better performance:

$ ./Types 1 d  test.hs  time ghc test.hs  /dev/null
real0m2.271s


-- Types.hs below


import System.Environment

code :: Int - String - String
code i test = concat $ map (++\n) $
[ {-# LANGUAGE TypeOperators,DataKinds,
KindSignatures,TypeFamilies,PolyKinds #-}
, import GHC.TypeLits

, data Nat1 = Zero | Succ Nat1

, type family Replicate1 (n :: Nat1) (x::a) :: [a]
, type instance Replicate1 Zero x = '[]
, type instance Replicate1 (Succ n) x = x ': (Replicate1 n x)

, class Class a where
, f :: a - a

, data Data (xs::a) = X | Y
, deriving (Read,Show)

, main = print test1
]
++
case head test of
'a' -
[ instance (xs ~ Replicate1 (++mkNat1 i++) ()) = Class
(Data xs) where
, f X = Y
, f Y = X
, test1 = f (X :: Data ( Replicate1 (++mkNat1 i++) () ))
]
'b' -
[ instance (xs ~ (++mkList i++) ) = Class (Data xs) where
, f X = Y
, f Y = X
, test1 = f (X :: Data ( Replicate1 (++mkNat1 i++) () ))
]
'c' -
[ instance (xs ~ Replicate1 (++mkNat1 i++) ()) = Class
(Data xs) where
, f X = Y
, f Y = X
, test1 = f (X :: Data ( (++mkList i++) ))
]
otherwise -
[ instance (xs ~ (++mkList i++) ) = Class (Data xs) where
, f X = Y
, f Y = X
, test1 = f (X :: Data ( (++mkList i++) ))
]

mkList :: Int - String
mkList 0 =  '[] 
mkList i =  () ':  ++ mkList (i-1)

mkNat1 :: Int - String
mkNat1 0 =  Zero 
mkNat1 i =  Succ (  ++ mkNat1 (i-1) ++ )

main = do
numstr : test : xs - getArgs
let num = read numstr :: Int

putStrLn $ code num test
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Are type families really this slow, or is this a GHC bug?

2013-07-26 Thread Jan Stolarek
I don't know much about type families, but I recall this: 
http://ghc.haskell.org/trac/ghc/ticket/5321

The bug is marked as fixed, but perhaps behaviour you observed shows that there 
are other cases 
where constraqint solver is slow. I'd consider reporting this as GHC bug.

Janek

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


Re: [Haskell-cafe] Are type families really this slow, or is this a GHC bug?

2013-07-26 Thread Mike Izbicki
Thanks for pointing to that ticket.  At first after reading through it, I
thought my mistake was not using tail call recursion.  But I updated the
type families and they actually ran slower!

I've gone ahead and reported a bug:
http://ghc.haskell.org/trac/ghc/ticket/8095


On Fri, Jul 26, 2013 at 1:31 PM, Jan Stolarek jan.stola...@p.lodz.plwrote:

 I don't know much about type families, but I recall this:
 http://ghc.haskell.org/trac/ghc/ticket/5321

 The bug is marked as fixed, but perhaps behaviour you observed shows that
 there are other cases
 where constraqint solver is slow. I'd consider reporting this as GHC bug.

 Janek

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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-15 Thread J. Stutterheim
The IDE still works for Windows, but it isn't actively developed anymore (though bugs and minor annoyances are still being fixed). For Mac and Linux we now have a command line tool that uses the IDE's codebase. Personally, I just use vim (of course you can use any editor you prefer; vim comes with syntax colouring for Clean out of the box) for coding and then use a new CLI tool called CPM (Clean Project Manager) to build my project. This tool will be included by default with the next Clean release. I doubt the IDE will be resurrected on Mac and Linux, because it is just too much work to port Object IO (the GUI library) to those platforms and our own Mac/Linux users strongly prefer their own editors over the IDE anyway. For people that prefer a non-CLI workflow, we are actually looking into making a web-based IDE in iTasks (although it doesn't have a very high priority at the moment).The OS dependency for dynamics stems from the fact that the Clean dynamics are quite a bit more powerful than Haskell's. For example, using dynamics, it is possible to send arbitrary functions to another Clean application, which can then dynamically link these functions in at runtime and immediately execute them. It doesn't even need to be the same program, which Cloud Haskell does require(and theoretically, it can even be another OS). This advanced dynamic linking feature requires intimate knowledge of the target OS' binary representation. (I would actually really like to see Haskell's dynamics system to become as powerful as Clean's; it also supports polymorphism, for example)On Jul 15, 2013, at 04:31 AM, "Richard A. O'Keefe" o...@cs.otago.ac.nz wrote: On 13/07/2013, at 11:27 PM, J. Stutterheim wrote:- they then abandoned the Macintosh world forWindows. The Mac IDE was killed off; there isnow an IDE for Windows but not MacOS or Linux.The good news is that the latest version of Clean[2] and its code generator[3] now works fine again on 64 bit Mac OS X Is that still the command-line tools, or has the IDE been resurrected? - other major features remain Windows-onlyThe bad news is that this is true to some extend; the dynamics system is still largely Windows-only. However, this is the only language feature I can think of that really is Windows-only. I have never been able to understand why there should be ANY OS-dependency in the dynamics feature. - the available books about Clean are way out ofdate, several drafts of other books remainincomplete.- the documentation (like the Report) has always beenrather amateurish and incomplete. Certainlycompared with the Haskell documentation.An iTasks book is actually in the works, which will contain a fair bit of Clean (although it is not a dedicated Clean book). There are also concrete plans to update the language manual soon-ish. Not to be offensive, because after saying "Denk U" I have no more Dutch words I can use, but it would really pay to find a native speaker of English to give the manual a final polish.- there is nothing to compare with the Haskell Platform.Actually, yes there is[4]. A misundertanding. "Nothing to compare with" is idiomatic for "nothing of comparable size to". Yes, you _can_ compare the Clean Platform with the Haskell Platform; it's a lot smaller. It can be described as a mix between Haskell Platform and a mini Hackage-like repository. There is no such thing as a Clean alternative to cabal install, though.Keep in mind that there is only a handful of people working on Clean, while Haskell has a huge community in comparison. Haskell has always benefited from - openness - multiple implementations - documentation ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-15 Thread Richard A. O'Keefe

On 15/07/2013, at 8:23 PM, J. Stutterheim wrote:
 The OS dependency for dynamics stems from the fact that the Clean dynamics 
 are quite a bit more powerful than Haskell's. For example, using dynamics, it 
 is possible to send arbitrary functions to another Clean application, which 
 can then dynamically link these functions in at runtime and immediately 
 execute them. It doesn't even need to be the same program, which Cloud 
 Haskell does require (and theoretically, it can even be another OS). This 
 advanced dynamic linking feature requires intimate knowledge of the target 
 OS' binary representation.

There is no obvious reason why it should.
Imagine a programming language implementation where a function
is compiled to some abstract representation (like Kistler's Juice)
and a native representation is added on loading or on first use.
For Oberon, Kistler found that transmitting compressed abstract
syntax trees and generating native code on reception took less
time and yielded better code than sending native code.  Even when
reading from a local disc, loading compressed ASTs and generating
native code on the fly was faster than a conventional dynamic linker.

A major issue here, of course, is that Windows could be 32-bit or
64-bit, x86 or ARM, and even if you restrict attention to one of
these combinations, there are things like exactly what SIMD
instructions are available.

 (I would actually really like to see Haskell's dynamics system to become as 
 powerful as Clean's; it also supports polymorphism, for example)

Perhaps you could say something about the following problem:

I have a data structure that includes some functions.
These functions use version X of module M.
I send that data structure to another application,
which is using version Y of module M, where Y /= X.

What happens?  This is the primary reason why Erlang has not
imitated Kali Scheme, which could also send functions.
For that matter, what happens if the function is sent to another
application (on a remote machine) that doesn't have _any_
version of module M and doesn't know where to find one?

I am _not_ suggesting that these are problems that Clean could not solve
or has not solved.  On the contrary, I'm saying that it would be very
interesting to hear how Clean has solved them.

From a security point of view, of course, failing to practice Safe Hex
is a bit worrying, but proof-carrying code and signatures can go some
way towards addressing that concern.


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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-14 Thread Richard A. O'Keefe

On 12/07/2013, at 6:12 PM, Andreas Abel wrote:
[I can't try your F# example but ocaml does something different.]

Yes.  They are different languages.

By the way, I used the F# that comes with Mono.

 On 12.07.2013 02:22, Richard A. O'Keefe wrote:
 For what it's worth,
 
 let x = 1 in
 -   let x = x+1 in
 - let x = x+2 in
 -   x;;
 
 prints
 
 val it : int = 4
 
 in the F# interactive system, but
 
 let x = 1 in
 - let x = x+1 in
 - let x = x+2 in
 -   x;;
 
  let p = e in body
 
 is just
 
  (\ p - body) e
 
 it cannot be simpler than that.

True.  But it *can* be more complex than that,
and in F# it *is*.

  So I do not see your point.

The differently indented versions of the nested let do
different things.  Although F# is a descendant of Ocaml,
it is not the case that all lets in F# allow shadowing.

That's the point.


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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-14 Thread Richard A. O'Keefe

On 13/07/2013, at 11:27 PM, J. Stutterheim wrote:
 - they then abandoned the Macintosh world for
  Windows.  The Mac IDE was killed off; there is
  now an IDE for Windows but not MacOS or Linux.
 
 The good news is that the latest version of Clean[2] and its code 
 generator[3] now works fine again on 64 bit Mac OS X

Is that still the command-line tools, or has the IDE been resurrected?

 - other major features remain Windows-only
 
 The bad news is that this is true to some extend; the dynamics system is 
 still largely Windows-only. However, this is the only language feature I can 
 think of that really is Windows-only.

I have never been able to understand why there should be ANY
OS-dependency in the dynamics feature.

 - the available books about Clean are way out of
  date, several drafts of other books remain
  incomplete.
 - the documentation (like the Report) has always been
  rather amateurish and incomplete.  Certainly
  compared with the Haskell documentation.
 
 An iTasks book is actually in the works, which will contain a fair bit of 
 Clean (although it is not a dedicated Clean book). There are also concrete 
 plans to update the language manual soon-ish.

Not to be offensive, because after saying Denk U I have no more
Dutch words I can use, but it would really pay to find a native
speaker of English to give the manual a final polish.
 
 - there is nothing to compare with the Haskell Platform.
 
 Actually, yes there is[4].

A misundertanding.  Nothing to compare with is idiomatic for
nothing of comparable size to.  Yes, you _can_ compare the
Clean Platform with the Haskell Platform; it's a lot smaller.

 It can be described as a mix between Haskell Platform and a mini Hackage-like 
 repository. There is no such thing as a Clean alternative to cabal install, 
 though.
 
 Keep in mind that there is only a handful of people working on Clean, while 
 Haskell has a huge community in comparison. 

Haskell has always benefited from
- openness
- multiple implementations
- documentation


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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-13 Thread J. Stutterheim
I currently work at the Radboud University where Clean is being developed. As 
such, I use it daily. Coming from Haskell, I have to admit that I never really 
got used to the let-before syntax, exactly for the reasons described in the 
previous emails. However, it does have some merit. In combination with 
uniqueness typing, the compiler can do destructive updates on the variables in 
the let-before blocks, making the generated code more efficient.

Possibly a bit off-topic, but please allow me to give an update about the 
latest status of Clean (mixed with some personal opinion ;)

 Clean is relatively unknown because
 - they started in the Macintosh world, and when
   they provided a compiler for the Unix world,
   they did not port their modern graphics and
   I/O library to it.  So you could never write
   a program that would run on Macs and other things.

Object IO (the graphics library) will probably never work for systems other 
than Windows because f low priority and a lack of manpower. This is admittedly 
unfortunate if you want to write native client-side GUIs. Currently, most of 
Clean's progress is driven by the iTask System[1], which provides a web GUI.

 - they then abandoned the Macintosh world for
   Windows.  The Mac IDE was killed off; there is
   now an IDE for Windows but not MacOS or Linux.

The good news is that the latest version of Clean[2] and its code generator[3] 
now works fine again on 64 bit Mac OS X (I would rate it as advanced beta, or 
perhaps even RC quality). Linux 64 support is currently being stabilised 
(currently alpha quality). Hopefully we will be able to create a new Clean 
release for Mac OS X, Linux and Windows this year. It will then also contain a 
command-line based build tool for Clean IDE project files.

 - other major features remain Windows-only

The bad news is that this is true to some extend; the dynamics system is still 
largely Windows-only. However, this is the only language feature I can think of 
that really is Windows-only.

 - the change from Clean 1.3 to Clean 2 was huge,
   like I mentioned above, none of my code survived
   the change, and there was at that time no
   conversion program

Warning, personal opinion ahead: that's the price of progress I suppose :) 
Because Clean has a very small user base, the language itself is still 
evolving, and there is no release schedule of any kind, it doesn't really pay 
to have a complicated deprecation process.

 - the available books about Clean are way out of
   date, several drafts of other books remain
   incomplete.
 - the documentation (like the Report) has always been
   rather amateurish and incomplete.  Certainly
   compared with the Haskell documentation.

An iTasks book is actually in the works, which will contain a fair bit of Clean 
(although it is not a dedicated Clean book). There are also concrete plans to 
update the language manual soon-ish.

 - there is nothing to compare with the Haskell Platform.

Actually, yes there is[4]. It can be described as a mix between Haskell 
Platform and a mini Hackage-like repository. There is no such thing as a Clean 
alternative to cabal install, though.

Keep in mind that there is only a handful of people working on Clean, while 
Haskell has a huge community in comparison. This makes it hard to keep up with 
advanced language features.


- Jurriën

[1] http://wiki.clean.cs.ru.nl/ITasks
[2] https://svn.cs.ru.nl/cgi-bin/admin/info/clean-compiler
[3] https://svn.cs.ru.nl/cgi-bin/admin/info/clean-code-generator
[4] https://svn.cs.ru.nl/cgi-bin/admin/info/clean-platform
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-12 Thread Andreas Abel

On 12.07.2013 02:22, Richard A. O'Keefe wrote:

For what it's worth,


let x = 1 in

-   let x = x+1 in
- let x = x+2 in
-   x;;

prints

val it : int = 4

in the F# interactive system, but


let x = 1 in

- let x = x+1 in
- let x = x+2 in
-   x;;

prints Duplicate definition of x at the second line.


Since silverlight does not work properly on my systems, I cannot 
tryfsharp.org.  I can try ocaml, which does not use indentation, and 
there the value is 4, and there is no ambiguity at all.


  let p = e in body

is just

  (\ p - body) e

it cannot be simpler than that.  So I do not see your point.

--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-11 Thread oleg

I'd like to emphasize that there is a precedent to non-recursive let
in the world of (relatively pure) lazy functional programming.
The programming language Clean has such non-recursive let and uses
it and the shadowing extensively. They consider shadowing a virtue,
for uniquely typed data.

Richard A. O'Keefe wrote
  let (x,s) = foo 1 [] in
  let (y,s) = bar x s in
  let (z,s) = baz x y s in ...
 I really wish you wouldn't do that.
 ...
 I find that that when the same name gets reused like
 that I get very confused indeed about which one I am
 looking at right now.
 ...
 If each instance of the variable is labelled with a
 sequence number, I don't get confused because each
 variable has a different name and I can *see* which
 one this is.

 Yes, sequence numbering variable states is a chore for
 the person writing the code, but it's a boon for the
 person reading the code.

Let me point out the latest Report on the programming language Clean
http://clean.cs.ru.nl/download/doc/CleanLangRep.2.2.pdf
specifically PDF pages 38-40 (Sec 3.5.4 Let-Before Expression). Let me
quote the relevant part:

Many of the functions for input and output in the CLEAN I/O library
are state transition functions. Such a state is often passed from one
function to another in a single threaded way (see Chapter 9) to force
a specific order of evaluation. This is certainly the case when the
state is of unique type. The threading parameter has to be renamed to
distinguish its different versions. The following example shows a
typical example: Use of state transition functions. The uniquely typed
state file is passed from one function to another involving a number
of renamings: file, file1, file2)

readchars:: *File - ([Char], *File)
readchars file
| not ok   = ([],file1)
| otherwise = ([char:chars], file2)
where
  (ok,char,file1) = freadc file
  (chars,file2)   = readchars file1

This explicit renaming of threaded parameters not only looks very
ugly, these kind of definitions are sometimes also hard to read as
well (in which order do things happen? which state is passed in which
situation?). We have to admit: an imperative style of programming is
much easier to read when things have to happen in a certain order such
as is the case when doing I/O. That is why we have introduced
let-before expressions.

It seems the designers of Clean have the opposite view on the explicit
renaming (that is, sequential numbering of unique variables).

Let-before expressions have a special scope rule to obtain an
imperative programming look. The variables in the left- hand side of
these definitions do not appear in the scope of the right-hand side of
that definition, but they do appear in the scope of the other
definitions that follow (including the root expression, excluding
local definitions in where blocks.

Notice that a variable defined in a let-before expression cannot be
used in a where expression. The reverse is true however: definitions
in the where expression can be used in the let before expression.  Use
of let before expressions, short notation, re-using names taking use
of the special scope of the let before)

readchars:: *File - ([Char], *File)
readchars file
#(ok,char,file)   = freadc file
|not ok   = ([],file)
#(chars,file) = readchars file
=([char:chars], file)

The code uses the same name 'file' all throughout, shadowing it
appropriately. Clean programmers truly do all IO in this style, see
the examples in
http://clean.cs.ru.nl/download/supported/ObjectIO.1.2/doc/tutorial.pdf

[To be sure I do not advocate using Clean notation '#' for
non-recursive let in Haskell. Clean is well-known for its somewhat
Spartan notation.]

State monad is frequently mentioned as an alternative. But monads are
a poor alternative to uniqueness typing. Granted, if a function has
one unique argument, e.g., World, then it is equivalent to the ST (or
IO) monad. However, a function may have several unique arguments. For
example, Arrays in Clean are uniquely typed so they can be updated
destructively. A function may have several argument arrays. Operations
on one array have to be serialized (which is what uniqueness typing
accomplishes) but the relative order among operations on distinct
arrays may be left unspecified, for the compiler to determine.

Monads, typical of imperative programs, overspecify the order. For
example,
do
  x - readSTRef ref1
  y - readSTRef ref2
  writeSTRef ref2 (x+y)

the write to ref2 must happen after reading ref2, but ref1 could be
read either before or after ref2. (Assuming ref2 and ref1 are distinct
-- the uniqueness typing will make sure of it.)  Alas, in a monad we
cannot leave the order of reading ref1 and ref2 

Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-11 Thread Richard A. O'Keefe

On 11/07/2013, at 6:16 PM, o...@okmij.org wrote:

 
 I'd like to emphasize that there is a precedent to non-recursive let
 in the world of (relatively pure) lazy functional programming.

So what?  You can find precedents for almost anything.
I could even point you to a lazy mostly-functional language
with assignment statements in which an identifier occurrence
may refer to two different variables in the course of execution.

Having a precedent doesn't mean that it's a good thing.

 The programming language Clean has such non-recursive let

I am familiar with Clean and used it quite a bit for several years.
My experience with that Clean idiom is *WHY* I hate this usage and
love monads.
 
 Let me point out the latest Report on the programming language Clean
http://clean.cs.ru.nl/download/doc/CleanLangRep.2.2.pdf

which I already have.  If the Clean developers hadn't decided to
concentrate on Windows, leaving the systems I used to wither,
and if they hadn't made fairly massive changes to the language
that broke all my code, it's _possible_ that I might eventually have
come to regard this style as acceptable.

 It seems the designers of Clean have the opposite view on the explicit
 renaming (that is, sequential numbering of unique variables).

That is so.  If that's what you want, you know where to find it.

Like I said, precedent is not proof of goodness.

 
readchars:: *File - ([Char], *File)
readchars file
#(ok,char,file)   = freadc file
|not ok   = ([],file)
#(chars,file) = readchars file
=([char:chars], file)

This is *PRECISELY* the kind of stuff that I find confusing.
If they would just *NUMBER* the states so that I can tell what
is happening when, I would be so much happier.

 The code uses the same name 'file' all throughout, shadowing it
 appropriately. Clean programmers truly do all IO in this style, see
 the examples in
http://clean.cs.ru.nl/download/supported/ObjectIO.1.2/doc/tutorial.pdf
 
 [To be sure I do not advocate using Clean notation '#' for
 non-recursive let in Haskell. Clean is well-known for its somewhat
 Spartan notation.]

I wouldn't call Clean Spartan.  Clean syntax is elaborate.
It achieves brevity not by avoiding keywords but by using
punctuation marks for them, as in [t] vs [!t] vs [|t]
-- does it leap to the eye that [t] is lazy, [!t] is head
strict, and [|t] is strictness-polymorphic? --
and the very important distinction between
a *function* f x = e and a *macro* f x :== e.
(There's a reason why the higher-order list processing
'functions' are actually 'macros'.  See page 109 of the report.
There's precedent for a LOT of things that I don't want in Haskell.)

 State monad is frequently mentioned as an alternative. But monads are
 a poor alternative to uniqueness typing.

In this particular case, uniqueness typing is an utter red herring.
People are advocating state monads JUST TO HIDE THE WIRING, not to
get the effect of destructive assignment.
I *agree* that uniqueness typing is a fine thing and recommended it
to the Mercury developers, who adopted it.

I don't care whether they are called monads, state combinators,
or weeblefretzers.  What I care about is that that
 - the states are HIDDEN from the human reader and
 - they are AUTOMATICALLY wired up correctly for the author.

Suppose we have

# (x,s) = foo s
# (y,z) = bar x s
# (z,s) = ugh x y s

where my finger slipped on the s key in the second line and
pressed the z key instead.  Precisely BECAUSE the variable name
is the same each time, nobody notices, not the compiler, not you,
not me.  The program just goes wrong.

With numbered variables,

let (x,s1) = foo s0
(y,z2) = bar x s1
(z,s3) = ugh x y s2
in ...

the compiler notices that s2 isn't defined.

With suitable combinators,

foo = \x - bar x = \y - ugh x y ...

nobody can make the mistake in the first place,
because the state variable isn't _there_ to get wrong.
 
 Why Clean is relatively unknown? Well, why is Amiga?

Clean is relatively unknown because
 - they started in the Macintosh world, and when
   they provided a compiler for the Unix world,
   they did not port their modern graphics and
   I/O library to it.  So you could never write
   a program that would run on Macs and other things.
 - they then abandoned the Macintosh world for
   Windows.  The Mac IDE was killed off; there is
   now an IDE for Windows but not MacOS or Linux.
 - other major features remain Windows-only
 - the change from Clean 1.3 to Clean 2 was huge,
   like I mentioned above, none of my code survived
   the change, and there was at that time no
   conversion program
 - the available books about Clean are way out of
   date, several drafts of other books remain
   incomplete.
 - the documentation (like the Report) has always been
   rather amateurish and incomplete.  Certainly
   compared with the Haskell documentation.
 - 

[Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread oleg

Andreas wrote: 
 The greater evil is that Haskell does not have a non-recursive let.
 This is source of many non-termination bugs, including this one here.
 let should be non-recursive by default, and for recursion we could have
 the good old let rec.

Hear, hear! In OCaml, I can (and often do) write

let (x,s) = foo 1 [] in
let (y,s) = bar x s in
let (z,s) = baz x y s in ...

In Haskell I'll have to uniquely number the s's:

let (x,s1)  = foo 1 [] in
let (y,s2)  = bar x s1 in
let (z,s3)  = baz x y s2 in ...

and re-number them if I insert a new statement. BASIC comes to mind. I
tried to lobby Simon Peyton-Jones for the non-recursive let a couple
of years ago. He said, write a proposal. It's still being
written... Perhaps you might want to write it now.

In the meanwhile, there is a very ugly workaround:

test = runIdentity $ do
 (x,s) - return $ foo 1 []
 (y,s) - return $ bar x s
 (z,s) - return $ baz x y s
 return (z,s)

After all, bind is non-recursive let.



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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread Andreas Abel

Hi Oleg,

just now I wrote a message to haskell-pr...@haskell.org to propose a 
non-recursive let.  Unfortunately, the default let is recursive, so we 
only have names like let' for it.  I also mentioned the ugly workaround 
(- return $) that I was shocked to see the first time, but use myself 
sometimes now.


Cheers,
Andreas

On 10.07.2013 09:34, o...@okmij.org wrote:

Andreas wrote:

The greater evil is that Haskell does not have a non-recursive let.
This is source of many non-termination bugs, including this one here.
let should be non-recursive by default, and for recursion we could have
the good old let rec.


Hear, hear! In OCaml, I can (and often do) write

 let (x,s) = foo 1 [] in
 let (y,s) = bar x s in
 let (z,s) = baz x y s in ...

In Haskell I'll have to uniquely number the s's:

 let (x,s1)  = foo 1 [] in
 let (y,s2)  = bar x s1 in
 let (z,s3)  = baz x y s2 in ...

and re-number them if I insert a new statement. BASIC comes to mind. I
tried to lobby Simon Peyton-Jones for the non-recursive let a couple
of years ago. He said, write a proposal. It's still being
written... Perhaps you might want to write it now.

In the meanwhile, there is a very ugly workaround:

 test = runIdentity $ do
  (x,s) - return $ foo 1 []
  (y,s) - return $ bar x s
  (z,s) - return $ baz x y s
  return (z,s)

After all, bind is non-recursive let.






--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread Edward Z. Yang
In my opinion, when you are rebinding a variable with the same name,
there is usually another way to structure your code which eliminates
the variable.

If you would like to write:

let x = foo input in
let x = bar x in
let x = baz x in

instead, write

baz . bar . foo $ input

If you would like to write

let (x,s) = foo 1 [] in
let (y,s) = bar x s in
let (z,s) = baz x y s in

instead, use a state monad.

Clearly this will not work in all cases, but it goes pretty far,
in my experience.

Edward

Excerpts from Andreas Abel's message of Wed Jul 10 00:47:48 -0700 2013:
 Hi Oleg,
 
 just now I wrote a message to haskell-pr...@haskell.org to propose a 
 non-recursive let.  Unfortunately, the default let is recursive, so we 
 only have names like let' for it.  I also mentioned the ugly workaround 
 (- return $) that I was shocked to see the first time, but use myself 
 sometimes now.
 
 Cheers,
 Andreas
 
 On 10.07.2013 09:34, o...@okmij.org wrote:
  Andreas wrote:
  The greater evil is that Haskell does not have a non-recursive let.
  This is source of many non-termination bugs, including this one here.
  let should be non-recursive by default, and for recursion we could have
  the good old let rec.
 
  Hear, hear! In OCaml, I can (and often do) write
 
   let (x,s) = foo 1 [] in
   let (y,s) = bar x s in
   let (z,s) = baz x y s in ...
 
  In Haskell I'll have to uniquely number the s's:
 
   let (x,s1)  = foo 1 [] in
   let (y,s2)  = bar x s1 in
   let (z,s3)  = baz x y s2 in ...
 
  and re-number them if I insert a new statement. BASIC comes to mind. I
  tried to lobby Simon Peyton-Jones for the non-recursive let a couple
  of years ago. He said, write a proposal. It's still being
  written... Perhaps you might want to write it now.
 
  In the meanwhile, there is a very ugly workaround:
 
   test = runIdentity $ do
(x,s) - return $ foo 1 []
(y,s) - return $ bar x s
(z,s) - return $ baz x y s
return (z,s)
 
  After all, bind is non-recursive let.
 
 
 
 

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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread Ertugrul Söylemez
o...@okmij.org wrote:

 Hear, hear! In OCaml, I can (and often do) write

 let (x,s) = foo 1 [] in
 let (y,s) = bar x s in
 let (z,s) = baz x y s in ...

 In Haskell I'll have to uniquely number the s's:

 let (x,s1)  = foo 1 [] in
 let (y,s2)  = bar x s1 in
 let (z,s3)  = baz x y s2 in ...

This isn't a case for non-recursive let.  It is one of the rare cases
where you might actually consider using a state monad.


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.


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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread Andreas Abel

On 10.07.2013 10:16, Ertugrul Söylemez wrote:

o...@okmij.org wrote:


Hear, hear! In OCaml, I can (and often do) write

 let (x,s) = foo 1 [] in
 let (y,s) = bar x s in
 let (z,s) = baz x y s in ...

In Haskell I'll have to uniquely number the s's:

 let (x,s1)  = foo 1 [] in
 let (y,s2)  = bar x s1 in
 let (z,s3)  = baz x y s2 in ...


This isn't a case for non-recursive let.  It is one of the rare cases
where you might actually consider using a state monad.


Except when you are implementing the state monad (giggle):


http://hackage.haskell.org/packages/archive/mtl/2.1/doc/html/src/Control-Monad-State-Class.html#state


--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread Alberto G. Corona
I think that a non-non recursive let could be not compatible with the pure
nature of Haskell.

Let is recursive because, unlike in the case of other
languages, variables are not locations for storing values, but the
expressions on the right side of the equality themselves. And obviously it
is not possible for a variable-expression to be two expressions at the same
time. The recursiveness is buildt-in. It comes from its pure nature.

For a non recursive version of let, it would be necessary to create a new
closure on each line, to create a new variable-expression with the same
name, but within the new closure. A different variable after all. That is
what the example with the Identity (and the state monad) does.

So I think that the ugly return example or the more elegant state monad
alternative is the right thing to do.


2013/7/10 Ertugrul Söylemez e...@ertes.de

 o...@okmij.org wrote:

  Hear, hear! In OCaml, I can (and often do) write
 
  let (x,s) = foo 1 [] in
  let (y,s) = bar x s in
  let (z,s) = baz x y s in ...
 
  In Haskell I'll have to uniquely number the s's:
 
  let (x,s1)  = foo 1 [] in
  let (y,s2)  = bar x s1 in
  let (z,s3)  = baz x y s2 in ...

 This isn't a case for non-recursive let.  It is one of the rare cases
 where you might actually consider using a state monad.


 Greets,
 Ertugrul

 --
 Not to be or to be and (not to be or to be and (not to be or to be and
 (not to be or to be and ... that is the list monad.

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




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


[Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread oleg

 If you would like to write

 let (x,s) = foo 1 [] in
 let (y,s) = bar x s in
 let (z,s) = baz x y s in

 instead, use a state monad.

Incidentally I did write almost exactly this code once. Ironically, it
was meant as a lead-on to the State monad. 

But there have been other cases where State monad was better
avoided. For instance, functions like foo and bar are already written
and they are not in the state monad. For example, foo may take a
non-empty Set and return the minimal element and the set without the
minimal element. There are several such handy functions in Data.Set
and Data.Map. Injecting such functions into a Set monad for the sake
of three lines seems overkill. 

Also, in the code above s's don't have to have the same type.

I particularly like repeated lets when I am writing the code to apply
transformations to it. Being explicit with state passing improves the
confidence. It is simpler to reason with the pure code.



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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread Ertugrul Söylemez
o...@okmij.org wrote:

  If you would like to write
 
  let (x,s) = foo 1 [] in
  let (y,s) = bar x s in
  let (z,s) = baz x y s in
 
  instead, use a state monad.

 Incidentally I did write almost exactly this code once. Ironically, it
 was meant as a lead-on to the State monad.

 But there have been other cases where State monad was better
 avoided. For instance, functions like foo and bar are already written
 and they are not in the state monad.

It's fine to use `state` or the StateT constructor here.


 For example, foo may take a non-empty Set and return the minimal
 element and the set without the minimal element. There are several
 such handy functions in Data.Set and Data.Map. Injecting such
 functions into a Set monad for the sake of three lines seems overkill.

Not a Set monad, but a state monad.  Other examples include 'random' and
'randomR', where you can just apply 'state':

getRandom  = state random
getRandomR = state . randomR

I do this a lot.


 Also, in the code above s's don't have to have the same type.

For this purpose we have indexed state monads.


 I particularly like repeated lets when I am writing the code to apply
 transformations to it. Being explicit with state passing improves the
 confidence. It is simpler to reason with the pure code.

Really?  I'm more confident that I got the updates right when I use a
state monad, possibly together with lenses.  The idea is to disallow
`get` and only allow `modify` and `put`.

The thing is, your code is really imperative, and it exhibits all the
usual effects of imperative programming:  If you mess up the order of
things, you get wrong results.  In fact the let-style makes things worse
by requiring you to renumber your variables all the time.  A
non-recursive let would really just cover up this problem by imposing an
arbitrary constraint on you.  I think we are all aware that shadowing is
a bad idea, no matter whether you do it through Identity or
non-recursive let.

Also if you are serious about this, you would have to make non-recursive
let the default to get OCaml-style behavior, which would be an extremely
invasive change.  We would have to fix pretty much all packages, all
tutorials, all books, all wiki pages, etc.  Otherwise just like you may
forget to renumber your variables, you may just as well forget to add
the norec keyword or whatever the syntax would be.

State monads are actually a nice abstraction to limit the number of
things that could go wrong in this setting.  I suggest using them
instead of changing the language.


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.


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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guardsloops]

2013-07-10 Thread Donn Cave
quoth Alberto G. Corona,

 Let is recursive because, unlike in the case of other
 languages, variables are not locations for storing values, but the
 expressions on the right side of the equality themselves. And obviously it
 is not possible for a variable-expression to be two expressions at the same
 time. The recursiveness is buildt-in. It comes from its pure nature.

I'm surprised that it would come down to purity.  It looks to me like
simply a question of scope.  I had to write an example program to see
what actually happens, because with me it isn't intuitive at all that
the name bound to an expression would be visible from within the
expression itself.  I suppose this is considered by some to be a feature,
obviously to others it's a bug.

I've gone to some trouble to dig up an nhc98 install (but can't seem to
find one among my computers and GHC 7 won't build the source thanks to
library re-orgs etc.)  Because, I vaguely recall that nhc98's rules
were different here?  Anyone in a position to prove me wrong?

thanks,
Donn

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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guardsloops]

2013-07-10 Thread Ertugrul Söylemez
Donn Cave d...@avvanta.com wrote:

  Let is recursive because, unlike in the case of other languages,
  variables are not locations for storing values, but the expressions
  on the right side of the equality themselves. And obviously it is
  not possible for a variable-expression to be two expressions at the
  same time. The recursiveness is buildt-in. It comes from its pure
  nature.

 I'm surprised that it would come down to purity.  It looks to me like
 simply a question of scope.  I had to write an example program to see
 what actually happens, because with me it isn't intuitive at all
 that the name bound to an expression would be visible from within
 the expression itself.  I suppose this is considered by some to be a
 feature, obviously to others it's a bug.

In a non-strict-by-default language like Haskell it's certainly a
feature.  A sufficiently smart compiler can figure out whether a
definition is recursive or not and apply the proper transformation, so
from a language-theoretic standpoint there is really no reason to have a
non-recursive let.

I think the proper solution is to identify the underlying problem:
general recursion.  Haskell does not enforce totality.  I'd really love
to see some optional totality checking in Haskell.  If Oleg decides not
to use a state monad, he will still have to be careful not to confuse
the numbers, but if he does, then the compiler will reject his code
instead of producing looping code.


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.


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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guardsloops]

2013-07-10 Thread Andreas Abel

Totality checking will generate a lot of false positives.

One would like an analysis that prints an error message if an expression 
is *definitely* looping in all cases.  While I have studied termination, 
I have not studied non-termination analyses.  It is harder than 
termination.  For termination checking, you can over-approximate the 
control-flows and just scream if you find a *potential* control flow 
that *might* lead to non-termination.  If you do not find such a control 
flow you can be sure things are terminating.  This is how Agda does it.


To be sure that something is definitely non-terminating, you need to 
show it is non-terminating on all *actual* control flows.  But usually 
you cannot statically tell whether in if c then d else e d or e is 
evaluated, so a non-termination analysis without false positives seems 
very restricted.  Still it might be could useful.


Having said this, having a termination analysis is not the proper 
solution to the lack of a non-recursive let, it does not establish 
shadowing behavior I want.


Cheers,
Andreas

On 10.07.13 7:44 PM, Ertugrul Söylemez wrote:

Donn Cave d...@avvanta.com wrote:


Let is recursive because, unlike in the case of other languages,
variables are not locations for storing values, but the expressions
on the right side of the equality themselves. And obviously it is
not possible for a variable-expression to be two expressions at the
same time. The recursiveness is buildt-in. It comes from its pure
nature.


I'm surprised that it would come down to purity.  It looks to me like
simply a question of scope.  I had to write an example program to see
what actually happens, because with me it isn't intuitive at all
that the name bound to an expression would be visible from within
the expression itself.  I suppose this is considered by some to be a
feature, obviously to others it's a bug.


In a non-strict-by-default language like Haskell it's certainly a
feature.  A sufficiently smart compiler can figure out whether a
definition is recursive or not and apply the proper transformation, so
from a language-theoretic standpoint there is really no reason to have a
non-recursive let.

I think the proper solution is to identify the underlying problem:
general recursion.  Haskell does not enforce totality.  I'd really love
to see some optional totality checking in Haskell.  If Oleg decides not
to use a state monad, he will still have to be careful not to confuse
the numbers, but if he does, then the compiler will reject his code
instead of producing looping code.


Greets,
Ertugrul



--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guardsloops]

2013-07-10 Thread Andreas Abel

On 10.07.13 6:00 PM, Donn Cave wrote:

quoth Alberto G. Corona,


Let is recursive because, unlike in the case of other
languages, variables are not locations for storing values, but the
expressions on the right side of the equality themselves. And obviously it
is not possible for a variable-expression to be two expressions at the same
time. The recursiveness is buildt-in. It comes from its pure nature.


@Alberto: you must have misunderstood my proposal.


I'm surprised that it would come down to purity.  It looks to me like
simply a question of scope.  I had to write an example program to see
what actually happens, because with me it isn't intuitive at all that
the name bound to an expression would be visible from within the
expression itself.  I suppose this is considered by some to be a feature,
obviously to others it's a bug.


Value-recursion *is* useful in a lazy language, e.g.

  let xs = 0 : xs

builds an infinite (in fact, circular) list of 0s.  But it is not always 
meaningful, e.g.


  let x = x + 1

simply loops.  I would like to be in the position to tell Haskell what I 
mean, whether I want recursion or not.



I've gone to some trouble to dig up an nhc98 install (but can't seem to
find one among my computers and GHC 7 won't build the source thanks to
library re-orgs etc.)  Because, I vaguely recall that nhc98's rules
were different here?  Anyone in a position to prove me wrong?


I would doubt that nhc98 would interpret  let xs = 0 : xs  differently 
than ghc if it implemented anything close to the Haskell 98 standard. 
But I am not in a position to prove you wrong.


Cheers,
Andreas

--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread Andreas Abel

On 10.07.13 11:42 AM, Ertugrul Söylemez wrote:

I think we are all aware that shadowing is
a bad idea, no matter whether you do it through Identity or
non-recursive let.


WHAT??

[This is Richard Bird's WHAT?? when someone said that using folds is 
like programming in assembly language.]


How can you think this if we say we WANT shadowing?!


Also if you are serious about this, you would have to make non-recursive
let the default to get OCaml-style behavior, which would be an extremely
invasive change.  We would have to fix pretty much all packages, all
tutorials, all books, all wiki pages, etc.  Otherwise just like you may
forget to renumber your variables, you may just as well forget to add
the norec keyword or whatever the syntax would be.


Wow, this is getting really dramatic now.  Don't be afraid, now one will 
force you to shadow any of your identifiers...


--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guardsloops]

2013-07-10 Thread Donn Cave
quoth Andreas Abel andreas.a...@ifi.lmu.de,
...
 I would doubt that nhc98 would interpret  let xs = 0 : xs  differently 
 than ghc if it implemented anything close to the Haskell 98 standard. 

What I (so vaguely) remember was a compile error, for some reuse of
an identifier where GHC permitted it.  I suppose you're right, anyway,
probably something else - maybe unambiguous nested shadowing?

  let x = t + 1 in
  let y = x in
  let x = y + 1 in x

GHC allows this, and of course there's no recursion.

Donn

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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread Richard A. O'Keefe

On 10/07/2013, at 8:42 PM, Andreas Abel wrote:
 
 Hear, hear! In OCaml, I can (and often do) write
 
 let (x,s) = foo 1 [] in
 let (y,s) = bar x s in
 let (z,s) = baz x y s in ...

I really wish you wouldn't do that.

After reading Dijkstra's paper on the fact that we have
small heads many years ago -- long enough to forget the
actual title, sorry -- I realised that I too was a Bear
of Very Little Brain and Get Confused Very Easily.

I find that that when the same name gets reused like
that I get very confused indeed about which one I am
looking at right now.

If the variable is hidden (as by the DCG transformation
in Prolog, or a state monad, I don't get confused about
the variable because it isn't visible.

If each instance of the variable is labelled with a
sequence number, I don't get confused because each
variable has a different name and I can *see* which
one this is.

Yes, sequence numbering variable states is a chore for
the person writing the code, but it's a boon for the
person reading the code.

Me, I'd be perfectly happy with

setup (x,s) = state (\_ - (x,s))

(setup $ foo 1 []) = \x -
bar x = \y -
baz x y = \z -
...

One reason for this is that it makes refactorings like
extracting bar ... = ... baz ... thinkable.  A long
sequence of updates is probably crying out for such a
refactoring.


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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guardsloops]

2013-07-10 Thread Richard A. O'Keefe

On 11/07/2013, at 4:00 AM, Donn Cave wrote:
 I've gone to some trouble to dig up an nhc98 install (but can't seem to
 find one among my computers and GHC 7 won't build the source thanks to
 library re-orgs etc.)  Because, I vaguely recall that nhc98's rules
 were different here?  Anyone in a position to prove me wrong?

I have a copy of nhc98 running (v1.16 of 2003-03-08).
Program:

main = let ones = 1 : ones in print $ take 10 $ ones

Output:

[1,1,1,1,1,1,1,1,1,1]

So no, nhc98's rules were _not_ different.
It would have been no use as a Haskell98 compiler if they had been.


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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guardsloops]

2013-07-10 Thread Richard A. O'Keefe

On 11/07/2013, at 11:09 AM, Donn Cave wrote:

 let x = t + 1 in
  let y = x in
  let x = y + 1 in x
 

Still no cigar.
nhc98 v1.16
Program:
main = print $ (let t = 0 in let x = t + 1 in let y = x in let x = y + 1 in x)
Output:
2



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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread oleg

Alberto G. Corona wrote:
 I think that a non-non recursive let could be not compatible with the pure
 nature of Haskell.

I have seen this sentiment before. It is quite a mis-understanding. In
fact, the opposite is true. One may say that Haskell is not quite pure
_because_ it has recursive let.

Let's take pure the simply-typed lambda-calculus, or System F, or
System Fomega. Or the Calculus of Inductive Constructions. These
calculi are pure in the sense that the result of evaluation of each
expression does not depend on the evaluation strategy. One can use
call-by-name, call-by-need, call-by-value, pick the next redex at
random or some other evaluation strategy -- and the result will be
just the same. Although the simply-typed lambda-calculus is quite
limited in its expressiveness, already System F is quite powerful
(e.g., allowing for the list library), to say nothing of CIC. In all
these systems, the non-recursive let

let x = e1 in e2
is merely the syntactic sugar for
(\x. e2) e1

OTH, the recursive let is not expressible. (Incidentally, although
System F and above express self-application (\x.x x), a fix-point
combinator is not typeable.) Adding the recursive let introduces
general recursion and hence the dependence on the evaluation
strategy. There are a few people who say non-termination is an
effect. The language with non-termination is no longer pure.


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


[Haskell-cafe] GHC bug? Let with guards loops

2013-07-09 Thread Andreas Abel

Hi, is this a known bug or feature of GHC (7.4.1, 7.6.3)?:

I got a looping behavior in one of my programs and could not explain 
why.  When I rewrote an irrefutable let with guards to use a case 
instead, the loop disappeared.  Cut-down:


  works = case Just 1 of { Just x | x  0 - x }

  loops = let Just x | x  0 = Just 1 in x

works returns 1, loops loops.  If x is unused on the rhs, the 
non-termination disappears.


  works' = let Just x | x  0 = Just 1 in 42

Is this intended by the Haskell semantics or is this a bug?  I would 
have assumed that non-recursive let and single-branch case are 
interchangeable, but apparently, not...


Cheers,
Andreas

--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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


Re: [Haskell-cafe] GHC bug? Let with guards loops

2013-07-09 Thread Dan Doel
The definition

Just x | x  0 = Just 1

is recursive. It conditionally defines Just x as Just 1 when x  0 (and as
bottom otherwise). So it must know the result before it can test the guard,
but it cannot know the result until the guard is tested. Consider an
augmented definition:

Just x | x  0  = Just 1
   | x = 0 = Just 0

What is x?


On Tue, Jul 9, 2013 at 10:42 AM, Andreas Abel andreas.a...@ifi.lmu.dewrote:

 Hi, is this a known bug or feature of GHC (7.4.1, 7.6.3)?:

 I got a looping behavior in one of my programs and could not explain why.
  When I rewrote an irrefutable let with guards to use a case instead, the
 loop disappeared.  Cut-down:

   works = case Just 1 of { Just x | x  0 - x }

   loops = let Just x | x  0 = Just 1 in x

 works returns 1, loops loops.  If x is unused on the rhs, the
 non-termination disappears.

   works' = let Just x | x  0 = Just 1 in 42

 Is this intended by the Haskell semantics or is this a bug?  I would have
 assumed that non-recursive let and single-branch case are interchangeable,
 but apparently, not...

 Cheers,
 Andreas

 --
 Andreas AbelDu bist der geliebte Mensch.

 Theoretical Computer Science, University of Munich
 Oettingenstr. 67, D-80538 Munich, GERMANY

 andreas.a...@ifi.lmu.de
 http://www2.tcs.ifi.lmu.de/~**abel/ http://www2.tcs.ifi.lmu.de/~abel/

 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://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] GHC bug? Let with guards loops

2013-07-09 Thread Roman Cheplyaka
As Dan said, this behaviour is correct.

The confusing thing here is that in case expressions guards are attached
to the patterns (i.e. to the lhs), while in let expressions they are
attached to the rhs.

So, despite the common Just x | x  0 part, your examples mean rather
different things.

Here's the translation of 'loops' according to the Report:

  loops =
let Just x =
  case () of
() | x  0 - Just 1
in x

Here it's obvious that 'x' is used in the rhs of its own definition.

Roman

* Andreas Abel andreas.a...@ifi.lmu.de [2013-07-09 16:42:00+0200]
 Hi, is this a known bug or feature of GHC (7.4.1, 7.6.3)?:
 
 I got a looping behavior in one of my programs and could not explain
 why.  When I rewrote an irrefutable let with guards to use a case
 instead, the loop disappeared.  Cut-down:
 
   works = case Just 1 of { Just x | x  0 - x }
 
   loops = let Just x | x  0 = Just 1 in x
 
 works returns 1, loops loops.  If x is unused on the rhs, the
 non-termination disappears.
 
   works' = let Just x | x  0 = Just 1 in 42
 
 Is this intended by the Haskell semantics or is this a bug?  I would
 have assumed that non-recursive let and single-branch case are
 interchangeable, but apparently, not...
 
 Cheers,
 Andreas
 
 -- 
 Andreas AbelDu bist der geliebte Mensch.
 
 Theoretical Computer Science, University of Munich
 Oettingenstr. 67, D-80538 Munich, GERMANY
 
 andreas.a...@ifi.lmu.de
 http://www2.tcs.ifi.lmu.de/~abel/
 
 ___
 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] GHC bug? Let with guards loops

2013-07-09 Thread Andreas Abel
Thanks, Dan and Roman, for the explanation.  So I have to delete the 
explanation non-recursive let = single-branch case from my brain.


I thought the guards in a let are assertations, but in fact it is more 
like an if.  Ok.


But then I do not see why the pattern variables are in scope in the 
guards in


  let p | g = e

The variables in p are only bound to their values (given by e) if the 
guard g evaluates to True.  But how can g evaluate if it has yet unbound 
variables?  How can ever a pattern variable of p be *needed* to compute 
the value of the guard?  My conjecture is that it cannot, so it does not 
make sense to consider variables of g bound by p.  Maybe you can cook up 
some counterexample.


I think the pattern variables of p should not be in scope in g, and 
shadowing free variables of g by pattern variables of p should be forbidden.


Cheers,
Andreas

On 09.07.2013 17:05, Dan Doel wrote: The definition

  Just x | x  0 = Just 1

 is recursive. It conditionally defines Just x as Just 1 when x  0 (and
 as bottom otherwise). So it must know the result before it can test the
 guard, but it cannot know the result until the guard is tested. Consider
 an augmented definition:

  Just x | x  0  = Just 1
 | x = 0 = Just 0

 What is x?

On 09.07.2013 17:49, Roman Cheplyaka wrote:

As Dan said, this behaviour is correct.

The confusing thing here is that in case expressions guards are attached
to the patterns (i.e. to the lhs), while in let expressions they are
attached to the rhs.

So, despite the common Just x | x  0 part, your examples mean rather
different things.

Here's the translation of 'loops' according to the Report:

   loops =
 let Just x =
   case () of
 () | x  0 - Just 1
 in x

Here it's obvious that 'x' is used in the rhs of its own definition.

Roman

* Andreas Abel andreas.a...@ifi.lmu.de [2013-07-09 16:42:00+0200]

Hi, is this a known bug or feature of GHC (7.4.1, 7.6.3)?:

I got a looping behavior in one of my programs and could not explain
why.  When I rewrote an irrefutable let with guards to use a case
instead, the loop disappeared.  Cut-down:

   works = case Just 1 of { Just x | x  0 - x }

   loops = let Just x | x  0 = Just 1 in x

works returns 1, loops loops.  If x is unused on the rhs, the
non-termination disappears.

   works' = let Just x | x  0 = Just 1 in 42

Is this intended by the Haskell semantics or is this a bug?  I would
have assumed that non-recursive let and single-branch case are
interchangeable, but apparently, not...

Cheers,
Andreas

--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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





--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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


Re: [Haskell-cafe] GHC bug? Let with guards loops

2013-07-09 Thread Felipe Almeida Lessa
Well, you could use p's type for something.

  let x | foo (undefined `asTypeOf` x) = 3
  foo _ = True
  in x

Arguably not very useful.  It seems to me that the most compelling
rationale is being consistent with the cases where, instead of being a
data type, p is a function.  Even so most of the time you won't be
recursing on the guard.  But, since you could use something from the
where clause on the guard, and we certainly won't be restricting
recursing on the where clause, it also seems compelling to allow
recursion on the guard.

My 2 centavos, =)


On Tue, Jul 9, 2013 at 2:12 PM, Andreas Abel andreas.a...@ifi.lmu.de wrote:
 Thanks, Dan and Roman, for the explanation.  So I have to delete the
 explanation non-recursive let = single-branch case from my brain.

 I thought the guards in a let are assertations, but in fact it is more like
 an if.  Ok.

 But then I do not see why the pattern variables are in scope in the guards
 in

   let p | g = e

 The variables in p are only bound to their values (given by e) if the guard
 g evaluates to True.  But how can g evaluate if it has yet unbound
 variables?  How can ever a pattern variable of p be *needed* to compute the
 value of the guard?  My conjecture is that it cannot, so it does not make
 sense to consider variables of g bound by p.  Maybe you can cook up some
 counterexample.

 I think the pattern variables of p should not be in scope in g, and
 shadowing free variables of g by pattern variables of p should be forbidden.

 Cheers,
 Andreas

 On 09.07.2013 17:05, Dan Doel wrote: The definition


  Just x | x  0 = Just 1

 is recursive. It conditionally defines Just x as Just 1 when x  0 (and
 as bottom otherwise). So it must know the result before it can test the
 guard, but it cannot know the result until the guard is tested. Consider
 an augmented definition:

  Just x | x  0  = Just 1
 | x = 0 = Just 0

 What is x?

 On 09.07.2013 17:49, Roman Cheplyaka wrote:

 As Dan said, this behaviour is correct.

 The confusing thing here is that in case expressions guards are attached
 to the patterns (i.e. to the lhs), while in let expressions they are
 attached to the rhs.

 So, despite the common Just x | x  0 part, your examples mean rather
 different things.

 Here's the translation of 'loops' according to the Report:

loops =
  let Just x =
case () of
  () | x  0 - Just 1
  in x

 Here it's obvious that 'x' is used in the rhs of its own definition.

 Roman

 * Andreas Abel andreas.a...@ifi.lmu.de [2013-07-09 16:42:00+0200]

 Hi, is this a known bug or feature of GHC (7.4.1, 7.6.3)?:

 I got a looping behavior in one of my programs and could not explain
 why.  When I rewrote an irrefutable let with guards to use a case
 instead, the loop disappeared.  Cut-down:

works = case Just 1 of { Just x | x  0 - x }

loops = let Just x | x  0 = Just 1 in x

 works returns 1, loops loops.  If x is unused on the rhs, the
 non-termination disappears.

works' = let Just x | x  0 = Just 1 in 42

 Is this intended by the Haskell semantics or is this a bug?  I would
 have assumed that non-recursive let and single-branch case are
 interchangeable, but apparently, not...

 Cheers,
 Andreas

 --
 Andreas AbelDu bist der geliebte Mensch.

 Theoretical Computer Science, University of Munich
 Oettingenstr. 67, D-80538 Munich, GERMANY

 andreas.a...@ifi.lmu.de
 http://www2.tcs.ifi.lmu.de/~abel/

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




 --
 Andreas AbelDu bist der geliebte Mensch.

 Theoretical Computer Science, University of Munich
 Oettingenstr. 67, D-80538 Munich, GERMANY

 andreas.a...@ifi.lmu.de
 http://www2.tcs.ifi.lmu.de/~abel/

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



-- 
Felipe.

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


Re: [Haskell-cafe] GHC bug? Let with guards loops

2013-07-09 Thread Dan Doel
With pattern guards, it's difficult to say whether it is never 'useful' to
have things like the following work:

C x | C' y z - f x = ...

But I'd also shy away from changing the behavior because it causes a lot of
consistency issues. In

let
  f vs1 | gs1 = es1
  h vs2 | gs2 = es2
  ...

we have that f and h are in scope in both gs1 and gs2. Does it make sense
to call f in gs1? It's easy to loop if you do. So should f not be in scope
in gs1, but h is, and vice versa for gs2? But they're both in scope for es1
and es2?

And if we leave the above alone, then what about the case where there are
no vs? Is that different? Or is it only left-hand patterns that get this
treatment?

Also, it might have some weird consequences for moving code around. Like:

let Just x | x  0 = Just 1

let Just x | y  0 = Just 1
y = x

let Just x | b = Just 1
  where b = x  0

let Just x | b = Just 1
b = x  0

These all behave the same way now. Which ones should change?

If Haskell had a non-recursive let, that'd probably be a different story.
But it doesn't.



On Tue, Jul 9, 2013 at 1:12 PM, Andreas Abel andreas.a...@ifi.lmu.dewrote:

 Thanks, Dan and Roman, for the explanation.  So I have to delete the
 explanation non-recursive let = single-branch case from my brain.

 I thought the guards in a let are assertations, but in fact it is more
 like an if.  Ok.

 But then I do not see why the pattern variables are in scope in the guards
 in

   let p | g = e

 The variables in p are only bound to their values (given by e) if the
 guard g evaluates to True.  But how can g evaluate if it has yet unbound
 variables?  How can ever a pattern variable of p be *needed* to compute the
 value of the guard?  My conjecture is that it cannot, so it does not make
 sense to consider variables of g bound by p.  Maybe you can cook up some
 counterexample.

 I think the pattern variables of p should not be in scope in g, and
 shadowing free variables of g by pattern variables of p should be forbidden.

 Cheers,
 Andreas

 On 09.07.2013 17:05, Dan Doel wrote: The definition

 
   Just x | x  0 = Just 1
 
  is recursive. It conditionally defines Just x as Just 1 when x  0 (and
  as bottom otherwise). So it must know the result before it can test the
  guard, but it cannot know the result until the guard is tested. Consider
  an augmented definition:
 
   Just x | x  0  = Just 1
  | x = 0 = Just 0
 
  What is x?

 On 09.07.2013 17:49, Roman Cheplyaka wrote:

 As Dan said, this behaviour is correct.

 The confusing thing here is that in case expressions guards are attached
 to the patterns (i.e. to the lhs), while in let expressions they are
 attached to the rhs.

 So, despite the common Just x | x  0 part, your examples mean rather
 different things.

 Here's the translation of 'loops' according to the Report:

loops =
  let Just x =
case () of
  () | x  0 - Just 1
  in x

 Here it's obvious that 'x' is used in the rhs of its own definition.

 Roman

 * Andreas Abel andreas.a...@ifi.lmu.de [2013-07-09 16:42:00+0200]

 Hi, is this a known bug or feature of GHC (7.4.1, 7.6.3)?:

 I got a looping behavior in one of my programs and could not explain
 why.  When I rewrote an irrefutable let with guards to use a case
 instead, the loop disappeared.  Cut-down:

works = case Just 1 of { Just x | x  0 - x }

loops = let Just x | x  0 = Just 1 in x

 works returns 1, loops loops.  If x is unused on the rhs, the
 non-termination disappears.

works' = let Just x | x  0 = Just 1 in 42

 Is this intended by the Haskell semantics or is this a bug?  I would
 have assumed that non-recursive let and single-branch case are
 interchangeable, but apparently, not...

 Cheers,
 Andreas

 --
 Andreas AbelDu bist der geliebte Mensch.

 Theoretical Computer Science, University of Munich
 Oettingenstr. 67, D-80538 Munich, GERMANY

 andreas.a...@ifi.lmu.de
 http://www2.tcs.ifi.lmu.de/~**abel/ http://www2.tcs.ifi.lmu.de/~abel/

 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe




 --
 Andreas AbelDu bist der geliebte Mensch.

 Theoretical Computer Science, University of Munich
 Oettingenstr. 67, D-80538 Munich, GERMANY

 andreas.a...@ifi.lmu.de
 http://www2.tcs.ifi.lmu.de/~**abel/ http://www2.tcs.ifi.lmu.de/~abel/

 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://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] GHC bug? Let with guards loops

2013-07-09 Thread Andreas Abel

Hi Felipe,  thanks for the centavos.

So you mean that in

  let p | g = e where bs
  in ...

the bindings bs should be in scope in g (and of course the variables of 
p are in scope in bs).  Mmh, the bindings in bs that do not uses the 
pattern variables could be useful in g, but the other bindings will 
still lead to non-termination.  Maybe such an analysis is too 
sophisticated.  My lesson is to use case instead of let.  Only that the 
let syntax is nicer and indentation-friendlier than case, so it would be 
preferable.


The greater evil is that Haskell does not have a non-recursive let. 
This is source of many non-termination bugs, including this one here. 
let should be non-recursive by default, and for recursion we could have 
the good old let rec.


Cheers,
Andreas

On 09.07.2013 19:23, Felipe Almeida Lessa wrote:

Well, you could use p's type for something.

   let x | foo (undefined `asTypeOf` x) = 3
   foo _ = True
   in x

Arguably not very useful.  It seems to me that the most compelling
rationale is being consistent with the cases where, instead of being a
data type, p is a function.  Even so most of the time you won't be
recursing on the guard.  But, since you could use something from the
where clause on the guard, and we certainly won't be restricting
recursing on the where clause, it also seems compelling to allow
recursion on the guard.

My 2 centavos, =)


On Tue, Jul 9, 2013 at 2:12 PM, Andreas Abel andreas.a...@ifi.lmu.de wrote:

Thanks, Dan and Roman, for the explanation.  So I have to delete the
explanation non-recursive let = single-branch case from my brain.

I thought the guards in a let are assertations, but in fact it is more like
an if.  Ok.

But then I do not see why the pattern variables are in scope in the guards
in

   let p | g = e

The variables in p are only bound to their values (given by e) if the guard
g evaluates to True.  But how can g evaluate if it has yet unbound
variables?  How can ever a pattern variable of p be *needed* to compute the
value of the guard?  My conjecture is that it cannot, so it does not make
sense to consider variables of g bound by p.  Maybe you can cook up some
counterexample.

I think the pattern variables of p should not be in scope in g, and
shadowing free variables of g by pattern variables of p should be forbidden.

Cheers,
Andreas

On 09.07.2013 17:05, Dan Doel wrote: The definition



  Just x | x  0 = Just 1

is recursive. It conditionally defines Just x as Just 1 when x  0 (and
as bottom otherwise). So it must know the result before it can test the
guard, but it cannot know the result until the guard is tested. Consider
an augmented definition:

  Just x | x  0  = Just 1
 | x = 0 = Just 0

What is x?


On 09.07.2013 17:49, Roman Cheplyaka wrote:


As Dan said, this behaviour is correct.

The confusing thing here is that in case expressions guards are attached
to the patterns (i.e. to the lhs), while in let expressions they are
attached to the rhs.

So, despite the common Just x | x  0 part, your examples mean rather
different things.

Here's the translation of 'loops' according to the Report:

loops =
  let Just x =
case () of
  () | x  0 - Just 1
  in x

Here it's obvious that 'x' is used in the rhs of its own definition.

Roman

* Andreas Abel andreas.a...@ifi.lmu.de [2013-07-09 16:42:00+0200]


Hi, is this a known bug or feature of GHC (7.4.1, 7.6.3)?:

I got a looping behavior in one of my programs and could not explain
why.  When I rewrote an irrefutable let with guards to use a case
instead, the loop disappeared.  Cut-down:

works = case Just 1 of { Just x | x  0 - x }

loops = let Just x | x  0 = Just 1 in x

works returns 1, loops loops.  If x is unused on the rhs, the
non-termination disappears.

works' = let Just x | x  0 = Just 1 in 42

Is this intended by the Haskell semantics or is this a bug?  I would
have assumed that non-recursive let and single-branch case are
interchangeable, but apparently, not...




--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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


Re: [Haskell-cafe] GHC bug? Let with guards loops

2013-07-09 Thread Andreas Abel

On 09.07.2013 19:56, Dan Doel wrote:

With pattern guards, it's difficult to say whether it is never 'useful'
to have things like the following work:

 C x | C' y z - f x = ...

But I'd also shy away from changing the behavior because it causes a lot
of consistency issues. In

 let
   f vs1 | gs1 = es1
   h vs2 | gs2 = es2
   ...

we have that f and h are in scope in both gs1 and gs2. Does it make
sense to call f in gs1? It's easy to loop if you do. So should f not be
in scope in gs1, but h is, and vice versa for gs2? But they're both in
scope for es1 and es2?


If f and h are really mutually recursive, then they should not be in 
scope in gs1 and gs2.


If the first thing you do in the body of f is calling f (which happens 
if f appears in gs1), then you are bound to loop.  But of course, if vs 
are not just variables but patterns, then the first thing you do is 
matching, so using f in gs1 could be fine.


I am getting on muddy grounds here, better retreat.  I was thinking only 
of non-recursive let.

In the report


http://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-440003.12

it says that

  let p = e1  in  e0=   case e1 of ~p - e0
where no variable in p appears free in e1

but this applies only for patterns p without guards, and I would have 
expected to be true also for patterns with guards.



And if we leave the above alone, then what about the case where there
are no vs? Is that different? Or is it only left-hand patterns that
get this treatment?


Yes, it is only about the things defined by the let binding (in this 
case, f and g).  The variables in vs1 are bound by calling f, but by f's 
body.



Also, it might have some weird consequences for moving code around. Like:

 let Just x | x  0 = Just 1


Non-recursive.


 let Just x | y  0 = Just 1
 y = x


Recursive.


 let Just x | b = Just 1
   where b = x  0


Recursive?


 let Just x | b = Just 1
 b = x  0


Recursive. (Like 2.)


These all behave the same way now. Which ones should change?


Only the first one?  Hard to tell.


If Haskell had a non-recursive let, that'd probably be a different
story. But it doesn't.


Definitely agree.


On Tue, Jul 9, 2013 at 1:12 PM, Andreas Abel andreas.a...@ifi.lmu.de
mailto:andreas.a...@ifi.lmu.de wrote:

Thanks, Dan and Roman, for the explanation.  So I have to delete the
explanation non-recursive let = single-branch case from my brain.

I thought the guards in a let are assertations, but in fact it is
more like an if.  Ok.

But then I do not see why the pattern variables are in scope in the
guards in

   let p | g = e

The variables in p are only bound to their values (given by e) if
the guard g evaluates to True.  But how can g evaluate if it has yet
unbound variables?  How can ever a pattern variable of p be *needed*
to compute the value of the guard?  My conjecture is that it cannot,
so it does not make sense to consider variables of g bound by p.
  Maybe you can cook up some counterexample.

I think the pattern variables of p should not be in scope in g, and
shadowing free variables of g by pattern variables of p should be
forbidden.

Cheers,
Andreas

On 09.07.2013 17:05, Dan Doel wrote: The definition

 
   Just x | x  0 = Just 1
 
  is recursive. It conditionally defines Just x as Just 1 when x 
0 (and
  as bottom otherwise). So it must know the result before it can
test the
  guard, but it cannot know the result until the guard is tested.
Consider
  an augmented definition:
 
   Just x | x  0  = Just 1
  | x = 0 = Just 0
 
  What is x?

On 09.07.2013 17:49, Roman Cheplyaka wrote:

As Dan said, this behaviour is correct.

The confusing thing here is that in case expressions guards are
attached
to the patterns (i.e. to the lhs), while in let expressions they are
attached to the rhs.

So, despite the common Just x | x  0 part, your examples mean
rather
different things.

Here's the translation of 'loops' according to the Report:

loops =
  let Just x =
case () of
  () | x  0 - Just 1
  in x

Here it's obvious that 'x' is used in the rhs of its own definition.

Roman

* Andreas Abel andreas.a...@ifi.lmu.de
mailto:andreas.a...@ifi.lmu.de [2013-07-09 16:42:00+0200]

Hi, is this a known bug or feature of GHC (7.4.1, 7.6.3)?:

I got a looping behavior in one of my programs and could not
explain
why.  When I rewrote an irrefutable let with guards to use a
case
instead, the loop disappeared.  Cut-down:

works = case Just 1 of { Just x | x  0 - x }

loops = let Just x | x  0

[Haskell-cafe] bug in Data.ByteString.Lazy or in me?

2013-07-03 Thread John MacFarlane
On a 64-bit Windows 8 server EC2 instance, with Haskell Platform
freshly installed from the package installer,

GHCI :m + Data.ByteString.Lazy
GHCI Data.ByteString.Lazy.hGetContents stdin

gives me an immediate error hGetBufSome: resource exhausted (Not enough
space), while

GHCI :m + Data.ByteString
GHCI Data.ByteString.hGetContents stdin

waits for user input, as expected.

On 32-bit Windows, both work as expected.

Can anyone explain this?  Is this a bug in bytestring?

John


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


Re: [Haskell-cafe] a bug of 32bit ghc on mac ?

2013-05-02 Thread Sray
so confused...
I have asked one of my friends to compile this code. And he also got an fail

It seems this bug only occurs on a 32-bit version ghc

update:
my friends said he changes the decode line into a ugly way:
 let x = decode $(C.pack. C.unpack) au :: Maybe AuctionInfo
then he got an ok

but i did so, also fail...


Subject: Re: [Haskell-cafe] a bug of 32bit ghc on mac ?
From: hutch-li...@recursive.ca
Date: Wed, 1 May 2013 05:43:46 -0400
CC: haskell-cafe@haskell.org
To: s...@live.com

I compiled and ran it a few hundred times in a script with no failures. I've 
got the same version of GHC on OS X 10.8.3.
BTW, it's not just Yesod that has that bug you mentioned in the 64-bit version.
Cheers,Bob

On 2013-04-30, at 11:37 PM, Sray s...@live.com wrote:








hi all

it seems i have met some bug on a  MAC 32bit GHC version 7.4.2 

to make long stroy short,  my code is about parse a json file using aeson
here is my code
http://pastebin.com/0VcVhdvX

and here is test data
http://pastebin.com/PvtSvst5

and test steps
save the code , and name it a.hs (or what you want)
save the test data ,name it a.json (do not change its name)
$ ghc a.hs -o a
$ ./a


what i get from the output is fail
and when i run the command below for a few times
$ runghc a.hs
i even got some ok and some fail mixed together 


but i copy the code and compile it on my linux, everything goes fine, the 
output is OK
i have run uninstall-hs and install a 64bit ghc, also goes fine

i delete one line randomly chosen from my test data , got an ok
roll back ,delete another line, also an ok...

I just want to make sure is this my bug or a bug of ghc

p.s. the reason using 32bit ghc is yesod, which has met another bug on 64bit 
mac ghc :(

thanks
sray


  
___
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] a bug of 32bit ghc on mac ?

2013-05-01 Thread Bob Hutchison
I compiled and ran it a few hundred times in a script with no failures. I've 
got the same version of GHC on OS X 10.8.3.

BTW, it's not just Yesod that has that bug you mentioned in the 64-bit version.

Cheers,
Bob


On 2013-04-30, at 11:37 PM, Sray s...@live.com wrote:

 hi all
 
 it seems i have met some bug on a MAC 32bit GHC version 7.4.2 
 
 to make long stroy short,  my code is about parse a json file using aeson
 here is my code
 http://pastebin.com/0VcVhdvX
 
 and here is test data
 http://pastebin.com/PvtSvst5
 
 and test steps
 save the code , and name it a.hs (or what you want)
 save the test data ,name it a.json (do not change its name)
 $ ghc a.hs -o a
 $ ./a
 
 
 what i get from the output is fail
 and when i run the command below for a few times
 $ runghc a.hs
 i even got some ok and some fail mixed together 
 
 
 but i copy the code and compile it on my linux, everything goes fine, the 
 output is OK
 i have run uninstall-hs and install a 64bit ghc, also goes fine
 
 i delete one line randomly chosen from my test data , got an ok
 roll back ,delete another line, also an ok...
 
 I just want to make sure is this my bug or a bug of ghc
 
 p.s. the reason using 32bit ghc is yesod, which has met another bug on 64bit 
 mac ghc :(
 
 thanks
 sray
 ___
 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] a bug of 32bit ghc on mac ?

2013-04-30 Thread Sray






hi all

it seems i have met some bug on a  MAC 32bit GHC version 7.4.2 

to make long stroy short,  my code is about parse a json file using aeson
here is my code
http://pastebin.com/0VcVhdvX

and here is test data
http://pastebin.com/PvtSvst5

and test steps
save the code , and name it a.hs (or what you want)
save the test data ,name it a.json (do not change its name)
$ ghc a.hs -o a
$ ./a


what i get from the output is fail
and when i run the command below for a few times
$ runghc a.hs
i even got some ok and some fail mixed together 


but i copy the code and compile it on my linux, everything goes fine, the 
output is OK
i have run uninstall-hs and install a 64bit ghc, also goes fine

i delete one line randomly chosen from my test data , got an ok
roll back ,delete another line, also an ok...

I just want to make sure is this my bug or a bug of ghc

p.s. the reason using 32bit ghc is yesod, which has met another bug on 64bit 
mac ghc :(

thanks
sray


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


[Haskell-cafe] Bug in Network package

2013-04-10 Thread Florian Hofmann
I might be mistaken, but is there a bug in the Show instance of PortNum?


λ PortNum 1
256
λ PortNum 2
512
λ PortNum 3
768

λ let (PortNum x) = PortNum 10
λ x
10

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


Re: [Haskell-cafe] Bug in Network package

2013-04-10 Thread Thomas DuBuisson
Replying to all.  Sorry for the duplicate, Florian.

The fact that the constructor `PortNum` is exported has been argued to be a
bug in past discussions.  PortNumber is stored big endian, which leads to
behaviors that people don't expect.  I suggest you lean on the fact that
PortNumber is an instance of the Num class:

ghci
...
 478 :: PortNumber
478

Cheers,
Thomas


On Wed, Apr 10, 2013 at 12:26 AM, Florian Hofmann 
fhofm...@techfak.uni-bielefeld.de wrote:

 I might be mistaken, but is there a bug in the Show instance of PortNum?


 λ PortNum 1
 256
 λ PortNum 2
 512
 λ PortNum 3
 768

 λ let (PortNum x) = PortNum 10
 λ x
 10

 Tested with network-2.4.1.2

 ___
 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] Bug in Network package

2013-04-10 Thread Brandon Allbery
On Wed, Apr 10, 2013 at 3:26 AM, Florian Hofmann 
fhofm...@techfak.uni-bielefeld.de wrote:

 I might be mistaken, but is there a bug in the Show instance of PortNum?


Not a bug, an annoying misdesign (IMO). A PortNum is actually in network
byte order. If you extract it, you get the original port; if you simply
show it, you see it byteswapped on little-endian platforms.

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Bug in Network package

2013-04-10 Thread Florian Hofmann
Ah ok ... thanks for the clarification


2013/4/10 Brandon Allbery allber...@gmail.com

 On Wed, Apr 10, 2013 at 3:26 AM, Florian Hofmann 
 fhofm...@techfak.uni-bielefeld.de wrote:

 I might be mistaken, but is there a bug in the Show instance of PortNum?


 Not a bug, an annoying misdesign (IMO). A PortNum is actually in network
 byte order. If you extract it, you get the original port; if you simply
 show it, you see it byteswapped on little-endian platforms.

 --
 brandon s allbery kf8nh   sine nomine
 associates
 allber...@gmail.com
 ballb...@sinenomine.net
 unix, openafs, kerberos, infrastructure, xmonad
 http://sinenomine.net

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


Re: [Haskell-cafe] Bug in Network package

2013-04-10 Thread Jeffrey Shaw
This is a case where a line of documentation could save a lot of people a
lot of trouble. Anyone have a clone of network handy that they could make a
pull request from?

Jeff


On Wed, Apr 10, 2013 at 4:31 PM, Florian Hofmann 
fhofm...@techfak.uni-bielefeld.de wrote:

 Ah ok ... thanks for the clarification


 2013/4/10 Brandon Allbery allber...@gmail.com

 On Wed, Apr 10, 2013 at 3:26 AM, Florian Hofmann 
 fhofm...@techfak.uni-bielefeld.de wrote:

 I might be mistaken, but is there a bug in the Show instance of PortNum?


 Not a bug, an annoying misdesign (IMO). A PortNum is actually in network
 byte order. If you extract it, you get the original port; if you simply
 show it, you see it byteswapped on little-endian platforms.

 --
 brandon s allbery kf8nh   sine nomine
 associates
 allber...@gmail.com
 ballb...@sinenomine.net
 unix, openafs, kerberos, infrastructure, xmonad
 http://sinenomine.net



 ___
 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] Bug in Network package

2013-04-10 Thread kudah
There's actually a comment near the definition of PortNumber
http://hackage.haskell.org/packages/archive/network/latest/doc/html/src/Network-Socket-Types.html#PortNumber
-- newtyped to prevent accidental use of sane-looking
-- port numbers that haven't actually been converted to
-- network-byte-order first.
Why the hell isn't it exported to haddocks is beyond me.

On Wed, 10 Apr 2013 16:51:23 -0400 Jeffrey Shaw shawj...@gmail.com
wrote:

 This is a case where a line of documentation could save a lot of
 people a lot of trouble. Anyone have a clone of network handy that
 they could make a pull request from?
 
 Jeff
 
 
 On Wed, Apr 10, 2013 at 4:31 PM, Florian Hofmann 
 fhofm...@techfak.uni-bielefeld.de wrote:
 
  Ah ok ... thanks for the clarification
 
 
  2013/4/10 Brandon Allbery allber...@gmail.com
 
  On Wed, Apr 10, 2013 at 3:26 AM, Florian Hofmann 
  fhofm...@techfak.uni-bielefeld.de wrote:
 
  I might be mistaken, but is there a bug in the Show instance of
  PortNum?
 
 
  Not a bug, an annoying misdesign (IMO). A PortNum is actually in
  network byte order. If you extract it, you get the original port;
  if you simply show it, you see it byteswapped on little-endian
  platforms.
 
  --
  brandon s allbery kf8nh   sine nomine
  associates
  allber...@gmail.com
  ballb...@sinenomine.net
  unix, openafs, kerberos, infrastructure, xmonad
  http://sinenomine.net
 
 
 
  ___
  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] Cabal bug? repeat --reinstall

2013-01-10 Thread Niklas Hambüchen
Where do we report this?

On 05/01/13 02:36, Albert Y. C. Lai wrote:
 On 13-01-04 04:36 PM, Niklas Hambüchen wrote:
 I get the following:

 $ cabal install --only-dependencies --reinstall

 Resolving dependencies...
 All the requested packages are already installed:
 Use --reinstall if you want to reinstall anyway.


 Can somebody confirm that they see the same?
 
 I confirm.
 
 
 ___
 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] Cabal bug? repeat --reinstall

2013-01-10 Thread Niklas Hambüchen
Ahah on Github. Filed as https://github.com/haskell/cabal/issues/1175.

On Fri 11 Jan 2013 01:21:11 CET, Niklas Hambüchen wrote:
 Where do we report this?

 On 05/01/13 02:36, Albert Y. C. Lai wrote:
 On 13-01-04 04:36 PM, Niklas Hambüchen wrote:
 I get the following:

 $ cabal install --only-dependencies --reinstall

 Resolving dependencies...
 All the requested packages are already installed:
 Use --reinstall if you want to reinstall anyway.


 Can somebody confirm that they see the same?

 I confirm.


 ___
 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Cabal bug? repeat --reinstall

2013-01-04 Thread Niklas Hambüchen
I get the following:

$ cabal install --only-dependencies --reinstall

Resolving dependencies...
All the requested packages are already installed:
Use --reinstall if you want to reinstall anyway.


Can somebody confirm that they see the same?

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


Re: [Haskell-cafe] Cabal bug? repeat --reinstall

2013-01-04 Thread Albert Y. C. Lai

On 13-01-04 04:36 PM, Niklas Hambüchen wrote:

I get the following:

$ cabal install --only-dependencies --reinstall

Resolving dependencies...
All the requested packages are already installed:
Use --reinstall if you want to reinstall anyway.


Can somebody confirm that they see the same?


I confirm.


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


[GHC] #7549: Deriving Bug?

2013-01-02 Thread GHC
#7549: Deriving Bug?
-+--
Reporter:  davorak   |  Owner:  
Type:  bug   | Status:  new 
Priority:  normal|  Component:  Compiler
 Version:  7.4.2 |   Keywords:  
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
 Failure:  None/Unknown  |  Blockedby:  
Blocking:|Related:  
-+--
 ghci -XDeriveDataTypeable
  import Data.Typeable
  data S = S deriving (typeable)
 ghc: panic! (the 'impossible' happened)
 (GHC version 7.4.2 for x86_64-unknown-linux):
   nameModule typeable{tv av8}

 Please report ...

 data S = S deriving typeable causes a parse error
 and
 The following work just fine:

 data S = S deriving Typeable
 data S = S deriving (Typeable)

 data S = S deriving (show) causes a similar error the only change being:

   nameModule show{tv av8}

 The same problem exists outside of ghci when trying to compile with GHC.

 The ascii tree for the dependancies of the ghc install produced with

 nix-store -q --tree $(which ghc)

 /nix/store/gzb4pca6nnb16lw2mbmr68kx2vwx8q56-ghc-7.4.2-wrapper[[BR]]
 +---/nix/store/043zrsanirjh8nbc5vqpjn93hhrf107f-bash-4.2-p24[[BR]]
 |   +---/nix/store/cj7a81wsm1ijwwpkks3725661h3263p5-glibc-2.13[[BR]]
 |   |   +---/nix/store/jfcs9xnfbmiwqs224sb0qqsybbfl3sab-linux-
 headers-2.6.35.14[[BR]]
 |   |   |   +---/nix/store/jfcs9xnfbmiwqs224sb0qqsybbfl3sab-linux-
 headers-2.6.35.14 [...][[BR]]
 |   |   +---/nix/store/cj7a81wsm1ijwwpkks3725661h3263p5-glibc-2.13
 [...][[BR]]
 |   +---/nix/store/043zrsanirjh8nbc5vqpjn93hhrf107f-bash-4.2-p24
 [...][[BR]]
 +---/nix/store/858ww5lrjxca5asa79vwq5rm6m1h3q6k-ghc-7.4.2[[BR]]
 |   +---/nix/store/cj7a81wsm1ijwwpkks3725661h3263p5-glibc-2.13 [...][[BR]]
 |   +---/nix/store/043zrsanirjh8nbc5vqpjn93hhrf107f-bash-4.2-p24
 [...][[BR]]
 |   +---/nix/store/1iigiim5855m8j7pmwf5xrnpf705s4dh-binutils-2.21.1a[[BR]]
 |   |   +---/nix/store/cj7a81wsm1ijwwpkks3725661h3263p5-glibc-2.13
 [...][[BR]]
 |   |   +---/nix/store/i3mqzy76lf51v5zqxjxyvf11j25iwycd-zlib-1.2.7[[BR]]
 |   |   |   +---/nix/store/cj7a81wsm1ijwwpkks3725661h3263p5-glibc-2.13
 [...][[BR]]
 |   |   |   +---/nix/store/i3mqzy76lf51v5zqxjxyvf11j25iwycd-zlib-1.2.7
 [...][[BR]]
 |   |   +---/nix/store/1iigiim5855m8j7pmwf5xrnpf705s4dh-binutils-2.21.1a
 [...][[BR]]
 |   +---/nix/store/a9jvlnrva7vr1szbg6shpw6nr5xz898p-gmp-5.0.5[[BR]]
 |   |   +---/nix/store/cj7a81wsm1ijwwpkks3725661h3263p5-glibc-2.13
 [...][[BR]]
 |   |   +---/nix/store/4gv9gby4bn1y0rlw3k0d5lyqy0yfkrc6-gcc-4.6.3[[BR]]
 |   |   |   +---/nix/store/jfcs9xnfbmiwqs224sb0qqsybbfl3sab-linux-
 headers-2.6.35.14 [...][[BR]]
 |   |   |   +---/nix/store/cj7a81wsm1ijwwpkks3725661h3263p5-glibc-2.13
 [...][[BR]]
 |   |   |   +---/nix/store/i3mqzy76lf51v5zqxjxyvf11j25iwycd-zlib-1.2.7
 [...][[BR]]
 |   |   |   +---/nix/store/4gv9gby4bn1y0rlw3k0d5lyqy0yfkrc6-gcc-4.6.3
 [...][[BR]]
 |   |   +---/nix/store/a9jvlnrva7vr1szbg6shpw6nr5xz898p-gmp-5.0.5
 [...][[BR]]
 |   +---/nix/store/ahg5mlj2mlp7yfl3x875pq95ar763vgj-ncurses-5.9[[BR]]
 |   |   +---/nix/store/cj7a81wsm1ijwwpkks3725661h3263p5-glibc-2.13
 [...][[BR]]
 |   |   +---/nix/store/043zrsanirjh8nbc5vqpjn93hhrf107f-bash-4.2-p24
 [...][[BR]]
 |   |   +---/nix/store/ahg5mlj2mlp7yfl3x875pq95ar763vgj-ncurses-5.9
 [...][[BR]]
 |   +---/nix/store/v4m3gahx1iz53v51rdinh0lcmipn1p4j-perl-5.14.2[[BR]]
 |   |   +---/nix/store/cj7a81wsm1ijwwpkks3725661h3263p5-glibc-2.13
 [...][[BR]]
 |   |   +---/nix/store/4gv9gby4bn1y0rlw3k0d5lyqy0yfkrc6-gcc-4.6.3
 [...][[BR]]
 |   |
 +---/nix/store/vpp6h8l3mzjdn5paziz31vk52pg73635-coreutils-8.15[[BR]]
 |   |   |   +---/nix/store/cj7a81wsm1ijwwpkks3725661h3263p5-glibc-2.13
 [...][[BR]]
 |   |   |   +---/nix/store/qh3l8f8369kvbhnkbwwnpaxayvnvi55v-
 acl-2.2.51[[BR]]
 |   |   |   |   +---/nix/store/cj7a81wsm1ijwwpkks3725661h3263p5-glibc-2.13
 [...][[BR]]
 |   |   |   |   +---/nix/store/jaabnv7dgxzvyhg0nxzk7xqs2qxp5rcy-
 attr-2.4.46[[BR]]
 |   |   |   |   |
 +---/nix/store/cj7a81wsm1ijwwpkks3725661h3263p5-glibc-2.13 [...][[BR]]
 |   |   |   |   |   +---/nix/store/jaabnv7dgxzvyhg0nxzk7xqs2qxp5rcy-
 attr-2.4.46 [...][[BR]]
 |   |   |   |   +---/nix/store/qh3l8f8369kvbhnkbwwnpaxayvnvi55v-acl-2.2.51
 [...][[BR]]
 |   |   |   +---/nix/store/vpp6h8l3mzjdn5paziz31vk52pg73635-coreutils-8.15
 [...][[BR]]
 |   |   +---/nix/store/v4m3gahx1iz53v51rdinh0lcmipn1p4j-perl-5.14.2
 [...][[BR]]
 |   +---/nix/store/xl3kqxs68gzs4h309wjyd32im9n6cnyr-gcc-
 wrapper-4.6.3[[BR]]
 |   |   +---/nix/store/cj7a81wsm1ijwwpkks3725661h3263p5-glibc-2.13
 [...][[BR]]
 |   |   +---/nix/store/043zrsanirjh8nbc5vqpjn93hhrf107f-bash-4.2-p24
 [...][[BR]]
 |   |   +---/nix/store/1iigiim5855m8j7pmwf5xrnpf705s4dh-binutils-2.21.1a

Re: [GHC] #7549: Deriving Bug?

2013-01-02 Thread GHC
#7549: Deriving Bug?
-+--
Reporter:  davorak   |Owner:  
Type:  bug   |   Status:  closed  
Priority:  normal|Component:  Compiler
 Version:  7.4.2 |   Resolution:  duplicate   
Keywords:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
   Blockedby:| Blocking:  
 Related:|  
-+--
Changes (by monoidal):

  * status:  new = closed
  * resolution:  = duplicate


Comment:

 Thanks for the report, the bug is already fixed in GHC 7.6 - bug #5961.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7549#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #7550: incorrect bang patterns rejected with report a ghc bug

2013-01-02 Thread GHC
#7550: incorrect bang patterns rejected with report a ghc bug
--+-
Reporter:  aavogt |  Owner: 
 
Type:  bug| Status:  new
 
Priority:  normal |  Component:  Compiler   
 
 Version:  7.6.1  |   Keywords: 
 
  Os:  Unknown/Multiple   |   Architecture:  
Unknown/Multiple
 Failure:  Incorrect warning at compile-time  |  Blockedby: 
 
Blocking: |Related: 
 
--+-
 {{{
 {-# LANGUAGE BangPatterns #-}
 data E a = E { e :: ! [] a }
 {- The current error given is not graceful:

 ghc: panic! (the 'impossible' happened)
   (GHC version 7.6.1 for x86_64-unknown-linux):
 tc_hs_type: bang

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

 -}

 -- maybe there could be some suggestion that E should have been written
 data D a = D { d :: ! ([] a) }
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7550
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7550: incorrect bang patterns rejected with report a ghc bug

2013-01-02 Thread GHC
#7550: incorrect bang patterns rejected with report a ghc bug
-+--
Reporter:  aavogt|Owner:
   
Type:  bug   |   Status:  closed
   
Priority:  normal|Component:  Compiler  
   
 Version:  7.6.1 |   Resolution:  duplicate 
   
Keywords:|   Os:  Unknown/Multiple  
   
Architecture:  Unknown/Multiple  |  Failure:  Incorrect warning at 
compile-time
   Blockedby:| Blocking:
   
 Related:|  
-+--
Changes (by monoidal):

  * status:  new = closed
  * resolution:  = duplicate


Comment:

 Thanks for the report. The bug is already fixed in HEAD, see #7210.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7550#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: Is there a workaround for this bug?

2013-01-01 Thread Dominic Steinitz
Thanks - I'll probably wait for the next release.

On 1 Jan 2013, at 19:48, Simon Peyton-Jones simo...@microsoft.com wrote:

 I think the patch did get into 7.6.2 (which is about to be released) though.
 
 I don't think there's a workaround, except by not using External Core, or not 
 using Integer literals (use Ints?).  Sorry.
 
 Simon
 
 |  -Original Message-
 |  From: glasgow-haskell-users-boun...@haskell.org 
 [mailto:glasgow-haskell-users-
 |  boun...@haskell.org] On Behalf Of Dominic Steinitz
 |  Sent: 26 December 2012 18:14
 |  To: glasgow-haskell-users@haskell.org
 |  Subject: Is there a workaround for this bug?
 |  
 |  AFAICT this bug fix http://hackage.haskell.org/trac/ghc/ticket/7239 did 
 not make
 |  it into 7.6.1. Also I am happily working on the Haskell Platform with 
 7.4.1 and I'd
 |  rather avoid upgrading if possible.
 |  
 |  Is there a workaround? I've attached my code below along with the error 
 message
 |  (which is the same as in the above bug report). I'm rather hoping I won't 
 have to
 |  build HEAD.
 |  
 |  Thanks, Dominic.
 |  
 |  bash-3.2$ ghc -fext-core --make Test.hs
 |  [1 of 1] Compiling Main ( Test.hs, Test.o )
 |  ghc: panic! (the 'impossible' happened)
 |   (GHC version 7.4.1 for x86_64-apple-darwin):
 | MkExternalCore died: make_lit
 |  
 |  {-# LANGUAGE FlexibleContexts #-}
 |  
 |  {-# OPTIONS_GHC -Wall -fno-warn-name-shadowing -fno-warn-type-defaults #-}
 |  
 |  import Data.Array.Repa as Repa
 |  import Data.Array.Repa.Eval
 |  import Control.Monad
 |  
 |  r, sigma, k, t, xMax, deltaX, deltaT :: Double
 |  m, n :: Int
 |  r = 0.05
 |  sigma = 0.2
 |  k = 50.0
 |  t = 3.0
 |  m = 80
 |  xMax = 150
 |  deltaX = xMax / (fromIntegral m)
 |  n = 800
 |  deltaT = t / (fromIntegral n)
 |  
 |  data PointedArrayU a = PointedArrayU Int (Array U DIM1 a)
 |   deriving Show
 |  
 |  f :: PointedArrayU Double - Double
 |  f (PointedArrayU j _x) | j == 0 = 0.0
 |  f (PointedArrayU j _x) | j == m = xMax - k
 |  f (PointedArrayU j  x)  = a * x! (Z :. j-1) +
 |   b * x! (Z :. j) +
 |   c * x! (Z :. j+1)
 |   where
 | a = deltaT * (sigma^2 * (fromIntegral j)^2 - r * (fromIntegral j)) / 2
 | b = 1 - deltaT * (r  + sigma^2 * (fromIntegral j)^2)
 | c = deltaT * (sigma^2 * (fromIntegral j)^2 + r * (fromIntegral j)) / 2
 |  
 |  priceAtT :: PointedArrayU Double
 |  priceAtT = PointedArrayU 0 (fromListUnboxed (Z :. m+1)
 |[ max 0 (deltaX * (fromIntegral j) - k) | j - 
 [0..m] ])
 |  
 |  coBindU :: (Source U a, Source U b, Target U b, Monad m) =
 |PointedArrayU a - (PointedArrayU a - b) - m (PointedArrayU  b)
 |  coBindU (PointedArrayU i a) f = computeP newArr = return . PointedArrayU 
 i
 |   where
 |   newArr = traverse a id g
 | where
 |   g _get (Z :. j) = f $ PointedArrayU j a
 |  
 |  testN :: Int - IO (PointedArrayU Double)
 |  testN n =  h priceAtT
 |where
 |h = foldr (=) return
 |(take n $ Prelude.zipWith flip (repeat coBindU) (repeat f))
 |  
 |  main :: IO ()
 |  main = do r - testN n
 |   putStrLn $ show r
 |  
 |  
 |  ___
 |  Glasgow-haskell-users mailing list
 |  Glasgow-haskell-users@haskell.org
 |  http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Is there a workaround for this bug?

2013-01-01 Thread Roman Cheplyaka
Hi Dom,

I can confirm that your example compiles (with minimal adjustments)
under GHC 7.6.2 RC1. You can get it here:

http://www.haskell.org/ghc/dist/7.6.2-rc1/

Roman

* Dominic Steinitz domi...@steinitz.org [2013-01-01 20:30:10+]
 Thanks - I'll probably wait for the next release.
 
 On 1 Jan 2013, at 19:48, Simon Peyton-Jones simo...@microsoft.com wrote:
 
  I think the patch did get into 7.6.2 (which is about to be released) though.
  
  I don't think there's a workaround, except by not using External Core, or 
  not using Integer literals (use Ints?).  Sorry.
  
  Simon
  
  |  -Original Message-
  |  From: glasgow-haskell-users-boun...@haskell.org 
  [mailto:glasgow-haskell-users-
  |  boun...@haskell.org] On Behalf Of Dominic Steinitz
  |  Sent: 26 December 2012 18:14
  |  To: glasgow-haskell-users@haskell.org
  |  Subject: Is there a workaround for this bug?
  |  
  |  AFAICT this bug fix http://hackage.haskell.org/trac/ghc/ticket/7239 did 
  not make
  |  it into 7.6.1. Also I am happily working on the Haskell Platform with 
  7.4.1 and I'd
  |  rather avoid upgrading if possible.
  |  
  |  Is there a workaround? I've attached my code below along with the error 
  message
  |  (which is the same as in the above bug report). I'm rather hoping I 
  won't have to
  |  build HEAD.
  |  
  |  Thanks, Dominic.
  |  
  |  bash-3.2$ ghc -fext-core --make Test.hs
  |  [1 of 1] Compiling Main ( Test.hs, Test.o )
  |  ghc: panic! (the 'impossible' happened)
  |   (GHC version 7.4.1 for x86_64-apple-darwin):
  |   MkExternalCore died: make_lit
  |  
  |  {-# LANGUAGE FlexibleContexts #-}
  |  
  |  {-# OPTIONS_GHC -Wall -fno-warn-name-shadowing -fno-warn-type-defaults 
  #-}
  |  
  |  import Data.Array.Repa as Repa
  |  import Data.Array.Repa.Eval
  |  import Control.Monad
  |  
  |  r, sigma, k, t, xMax, deltaX, deltaT :: Double
  |  m, n :: Int
  |  r = 0.05
  |  sigma = 0.2
  |  k = 50.0
  |  t = 3.0
  |  m = 80
  |  xMax = 150
  |  deltaX = xMax / (fromIntegral m)
  |  n = 800
  |  deltaT = t / (fromIntegral n)
  |  
  |  data PointedArrayU a = PointedArrayU Int (Array U DIM1 a)
  |   deriving Show
  |  
  |  f :: PointedArrayU Double - Double
  |  f (PointedArrayU j _x) | j == 0 = 0.0
  |  f (PointedArrayU j _x) | j == m = xMax - k
  |  f (PointedArrayU j  x)  = a * x! (Z :. j-1) +
  |   b * x! (Z :. j) +
  |   c * x! (Z :. j+1)
  |   where
  | a = deltaT * (sigma^2 * (fromIntegral j)^2 - r * (fromIntegral j)) / 2
  | b = 1 - deltaT * (r  + sigma^2 * (fromIntegral j)^2)
  | c = deltaT * (sigma^2 * (fromIntegral j)^2 + r * (fromIntegral j)) / 2
  |  
  |  priceAtT :: PointedArrayU Double
  |  priceAtT = PointedArrayU 0 (fromListUnboxed (Z :. m+1)
  |[ max 0 (deltaX * (fromIntegral j) - k) | j - 
  [0..m] ])
  |  
  |  coBindU :: (Source U a, Source U b, Target U b, Monad m) =
  |PointedArrayU a - (PointedArrayU a - b) - m (PointedArrayU  
  b)
  |  coBindU (PointedArrayU i a) f = computeP newArr = return . 
  PointedArrayU i
  |   where
  |   newArr = traverse a id g
  | where
  |   g _get (Z :. j) = f $ PointedArrayU j a
  |  
  |  testN :: Int - IO (PointedArrayU Double)
  |  testN n =  h priceAtT
  |where
  |h = foldr (=) return
  |(take n $ Prelude.zipWith flip (repeat coBindU) (repeat f))
  |  
  |  main :: IO ()
  |  main = do r - testN n
  |   putStrLn $ show r
  |  
  |  
  |  ___
  |  Glasgow-haskell-users mailing list
  |  Glasgow-haskell-users@haskell.org
  |  http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 
 
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [GHC] #7192: Bug in -fregs-graph with -fnew-codegen

2012-12-28 Thread GHC
#7192: Bug in -fregs-graph with -fnew-codegen
-+--
Reporter:  simonmar  |   Owner:  benl
Type:  bug   |  Status:  new 
Priority:  highest   |   Milestone:  7.8.1   
   Component:  Compiler  | Version:  7.7 
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  4258
 Related:|  
-+--
Changes (by PHO):

 * cc: pho@… (added)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7192#comment:11
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Is there a workaround for this bug?

2012-12-26 Thread Dominic Steinitz
AFAICT this bug fix http://hackage.haskell.org/trac/ghc/ticket/7239 did not 
make it into 7.6.1. Also I am happily working on the Haskell Platform with 
7.4.1 and I'd rather avoid upgrading if possible.

Is there a workaround? I've attached my code below along with the error message 
(which is the same as in the above bug report). I'm rather hoping I won't have 
to build HEAD.

Thanks, Dominic.

bash-3.2$ ghc -fext-core --make Test.hs
[1 of 1] Compiling Main ( Test.hs, Test.o )
ghc: panic! (the 'impossible' happened)
 (GHC version 7.4.1 for x86_64-apple-darwin):
MkExternalCore died: make_lit

{-# LANGUAGE FlexibleContexts #-}

{-# OPTIONS_GHC -Wall -fno-warn-name-shadowing -fno-warn-type-defaults #-}

import Data.Array.Repa as Repa
import Data.Array.Repa.Eval
import Control.Monad

r, sigma, k, t, xMax, deltaX, deltaT :: Double
m, n :: Int
r = 0.05
sigma = 0.2
k = 50.0
t = 3.0
m = 80
xMax = 150
deltaX = xMax / (fromIntegral m)
n = 800
deltaT = t / (fromIntegral n)

data PointedArrayU a = PointedArrayU Int (Array U DIM1 a)
 deriving Show

f :: PointedArrayU Double - Double
f (PointedArrayU j _x) | j == 0 = 0.0
f (PointedArrayU j _x) | j == m = xMax - k
f (PointedArrayU j  x)  = a * x! (Z :. j-1) +
 b * x! (Z :. j) +
 c * x! (Z :. j+1)
 where
   a = deltaT * (sigma^2 * (fromIntegral j)^2 - r * (fromIntegral j)) / 2
   b = 1 - deltaT * (r  + sigma^2 * (fromIntegral j)^2)
   c = deltaT * (sigma^2 * (fromIntegral j)^2 + r * (fromIntegral j)) / 2

priceAtT :: PointedArrayU Double
priceAtT = PointedArrayU 0 (fromListUnboxed (Z :. m+1) 
  [ max 0 (deltaX * (fromIntegral j) - k) | j - [0..m] 
])

coBindU :: (Source U a, Source U b, Target U b, Monad m) =
  PointedArrayU a - (PointedArrayU a - b) - m (PointedArrayU  b)
coBindU (PointedArrayU i a) f = computeP newArr = return . PointedArrayU i
 where
 newArr = traverse a id g
   where
 g _get (Z :. j) = f $ PointedArrayU j a

testN :: Int - IO (PointedArrayU Double)
testN n =  h priceAtT
  where
  h = foldr (=) return
  (take n $ Prelude.zipWith flip (repeat coBindU) (repeat f))

main :: IO ()
main = do r - testN n
 putStrLn $ show r


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [GHC] #7503: Bug with PolyKinds, type synonyms GADTs

2012-12-20 Thread GHC
#7503: Bug with PolyKinds, type synonyms  GADTs
+---
Reporter:  Ashley Yakeley   |   Owner:  
 
Type:  bug  |  Status:  new 
 
Priority:  normal   |   Milestone:  
 
   Component:  Compiler (Type checker)  | Version:  7.6.1   
 
Keywords:   |  Os:  Linux   
 
Architecture:  x86_64 (amd64)   | Failure:  GHC rejects valid 
program
  Difficulty:  Unknown  |Testcase:  
 
   Blockedby:   |Blocking:  
 
 Related:   |  
+---
Changes (by simonpj):

  * difficulty:  = Unknown


Comment:

 Hmm.  As stated, it fails both with `AW` and `AW'` in the commented line.
 But this simpler one fails:
 {{{
 data Wrap a --  Wrap :: forall k. k - *

 data A a = MkA a (AW a)

 type AW  a = A (Wrap a)
 type AW2 a = A (Wrap a)

 class C (a :: k) where
 aw :: AW a -- workaround: AW2
 }}}
 With `AW` in the last line we get
 {{{
 T7503.hs:15:14:
 The first argument of `AW' should have kind `*',
   but `a' has kind `k1'
 In the type `AW a'
 In the class declaration for `C'
 }}}
 Replacing with the identical (!) `AW2` makes it go through.  Here is what
 is happening:
  * Type synonym `AW` and data type `A` are mutually recursive.
  * So they are kind-checked together, with `AW` being monomorphic.
  * `AW` is applied to `a::*` in the data type declaration of `A`, so `AW`
 ends up with kind `*-*`.
  * But that is insufficiently polymorphic for its use in the class
 declaration.
  * On the other hand `AW2` is not mutually recursive with `A`, so it is
 kind-checked after `A` is done, and gets the polymorphic kind `AW2 ::
 forall k. k - *`.

 Very similar things happen in the world of terms.  We solve them by
 [http://www.haskell.org/ghc/docs/latest/html/users_guide/other-type-
 extensions.html#typing-binds breaking the mutual recursion at a type
 signature], and in principle we could do the same here. After all, `A` is
 given a full kind signature.

 Still, it's not entirely trivial to implement.  And we don't have a
 general mechanism for giving kind signatures; for example, how would you
 give a kind signature for a type synonym?

 Worth thinking about. But perhpas not urgent.  Yell if it is hurting you.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7503#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7503: Bug with PolyKinds, type synonyms GADTs

2012-12-19 Thread GHC
#7503: Bug with PolyKinds, type synonyms  GADTs
--+-
Reporter:  Ashley Yakeley |  Owner: 
Type:  bug| Status:  new
Priority:  normal |  Component:  Compiler (Type checker)
 Version:  7.6.1  |   Keywords: 
  Os:  Linux  |   Architecture:  x86_64 (amd64) 
 Failure:  GHC rejects valid program  |  Blockedby: 
Blocking: |Related: 
--+-

Comment(by simonpj@…):

 commit 3394d49af13697626145aca6d80b65ae8661418c
 {{{
 Author: Simon Peyton Jones simo...@microsoft.com
 Date:   Wed Dec 19 17:37:27 2012 +

 Pass the correct inst_tys argument to dataConCannotMatch, in
 mkRecSelBinds

 This fixes Trac #7503.

  compiler/typecheck/TcTyClsDecls.lhs |   16 ++--
  1 files changed, 10 insertions(+), 6 deletions(-)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7503#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [Haskell-cafe] A weird bug of regex-pcre

2012-12-18 Thread José Romildo Malaquias
On Tue, Dec 18, 2012 at 02:28:26PM +0800, Magicloud Magiclouds wrote:
 Attachment is the test text file.
 And I tested my regexp as this:
 
 Prelude :m + Text.Regex.PCRE
 Prelude Text.Regex.PCRE z - readFile test.html
 Prelude Text.Regex.PCRE let (b, m ,a, ss) = z =~ a
 href=\(.*?)\.*?img class=\article-image\ :: (String, String, String,
 [String])
 Prelude Text.Regex.PCRE b
 ...
 n of the Triumvirate/td\r\ntd class=\small\David Rapoza/td\r\n
td class=\small\\r\n  iReturn to Ravnica/i\r\n/td\r\n
td class=\small\10/31/2012/td\r\n  /trtr\r\n  td
 class=\small\
 Prelude Text.Regex.PCRE m
 a href=\/magic/magazine/article.aspx?x=mtg/daily/activity/1088\img
 class=\article-image\ 
 
 From the value of b and m, it was weird that the matching was moved forward
 by 1 char ( the ss (sub matching) was even worse, 2 chars ). Rematch to a
 and so on gave correct results. It was only the first matching that was
 broken.
 Tested with regex-posix (with modified regexp), everything is OK.

I have a similar issue with non-ascii strings. It seems that the
internal representation used by Haskell and pcre are different and one
of them is counting bytes and the other is counting code points. So they
diverge when a multi-byte representation (like utf8) is used.

It has been reported previously. See these threads:

http://www.haskell.org/pipermail/haskell-cafe/2012-August/thread.html#102959
http://www.haskell.org/pipermail/haskell-cafe/2012-August/thread.html#103029

I am still waiting for a new release of regex-pcre that fixes this
issue.

Romildo

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


Re: [Haskell-cafe] A weird bug of regex-pcre

2012-12-18 Thread Rico Moorman
I had similar issues a while ago. It had to do with UTF-8 encoding as far
as I can recall.

I wanted to wrap a multiline string (code listings) within some pandoc
generated HTML of a hakyll page with a container div. The text to wrap
would be determined using a PCRE regex.

Here the (probably inefficient) implementation:

module Transformations where

import Hakyll
import qualified Text.Regex.PCRE as RE
import qualified Data.ByteString.UTF8 as BSU
import qualified Data.ByteString as BS

-- Wraps numbered code listings within the page body with a div
-- in order to be able to apply some more specific styling.
wrapNumberedCodelistings (Page meta body) =
Page meta newBody
where
newBody = regexReplace' regex wrap body
regex = table\\s+class=\sourceCode[^]+.*?/table-
wrap x = div class=\sourceCodeWrap\ ++ x ++ /div


-- Replace the whole string matched by the given
-- regex using the given replacement function (hopefully UTF8-aware)
regexReplace' :: String - (String - String) - String - String
regexReplace' pattern replace text = BSU.toString $ go textUTF8
where
patternUTF8 = BSU.fromString pattern
textUTF8 = BSU.fromString text
replaceUTF8 x = BSU.fromString $ replace $ BSU.toString x
regex = RE.makeRegexOpts compOpts RE.defaultExecOpt $
BSU.fromString pattern
compOpts = RE.compMultiline + RE.compDotAll + RE.compUTF8 +
RE.compNoUTF8Check
go part = case RE.matchM regex part of
Just (before, match, after) -
BS.concat [before, replaceUTF8 match, go after]
_ - part


The discussion back then was
http://www.haskell.org/pipermail/beginners/2012-June/010064.html

Hope this helps.

Best regards,

Rico Moorman


P.S. Sorry for the double email Magicloud ... didn't hit reply all at first

On Tue, Dec 18, 2012 at 10:43 AM, José Romildo Malaquias 
j.romi...@gmail.com wrote:

 On Tue, Dec 18, 2012 at 02:28:26PM +0800, Magicloud Magiclouds wrote:
  Attachment is the test text file.
  And I tested my regexp as this:
 
  Prelude :m + Text.Regex.PCRE
  Prelude Text.Regex.PCRE z - readFile test.html
  Prelude Text.Regex.PCRE let (b, m ,a, ss) = z =~ a
  href=\(.*?)\.*?img class=\article-image\ :: (String, String,
 String,
  [String])
  Prelude Text.Regex.PCRE b
  ...
  n of the Triumvirate/td\r\ntd class=\small\David
 Rapoza/td\r\n
 td class=\small\\r\n  iReturn to Ravnica/i\r\n
  /td\r\n
 td class=\small\10/31/2012/td\r\n  /trtr\r\n  td
  class=\small\
  Prelude Text.Regex.PCRE m
  a href=\/magic/magazine/article.aspx?x=mtg/daily/activity/1088\img
  class=\article-image\ 
 
  From the value of b and m, it was weird that the matching was moved
 forward
  by 1 char ( the ss (sub matching) was even worse, 2 chars ). Rematch to a
  and so on gave correct results. It was only the first matching that was
  broken.
  Tested with regex-posix (with modified regexp), everything is OK.

 I have a similar issue with non-ascii strings. It seems that the
 internal representation used by Haskell and pcre are different and one
 of them is counting bytes and the other is counting code points. So they
 diverge when a multi-byte representation (like utf8) is used.

 It has been reported previously. See these threads:


 http://www.haskell.org/pipermail/haskell-cafe/2012-August/thread.html#102959

 http://www.haskell.org/pipermail/haskell-cafe/2012-August/thread.html#103029

 I am still waiting for a new release of regex-pcre that fixes this
 issue.

 Romildo

 ___
 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] A weird bug of regex-pcre

2012-12-18 Thread Rico Moorman

 regex = table\\s+class=\sourceCode[^]+.*?/table-


And mind the sneaky single - ... it doe not belong there ;-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A weird bug of regex-pcre

2012-12-18 Thread Magicloud Magiclouds
I see. A known bug. Thank you all.


On Tue, Dec 18, 2012 at 10:11 PM, Rico Moorman rico.moor...@gmail.comwrote:

 regex = table\\s+class=\sourceCode[^]+.*?/table-


 And mind the sneaky single - ... it doe not belong there ;-)






-- 
竹密岂妨流水过
山高哪阻野云飞

And for G+, please use magiclouds#gmail.com.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[GHC] #7503: Bug with PolyKinds, type synonyms GADTs

2012-12-16 Thread GHC
#7503: Bug with PolyKinds, type synonyms  GADTs
--+-
Reporter:  Ashley Yakeley |  Owner: 
Type:  bug| Status:  new
Priority:  normal |  Component:  Compiler (Type checker)
 Version:  7.6.1  |   Keywords: 
  Os:  Linux  |   Architecture:  x86_64 (amd64) 
 Failure:  GHC rejects valid program  |  Blockedby: 
Blocking: |Related: 
--+-
 GHC incorrectly rejects this program:
 {{{
 {-# LANGUAGE ExistentialQuantification, DataKinds, PolyKinds,
 KindSignatures, GADTs #-}
 module TestConstraintKinds where
 import GHC.Exts hiding (Any)

 data WrappedType = forall a. WrapType a

 data A :: WrappedType - * where
 MkA :: forall (a :: *). AW a - A (WrapType a)

 type AW  (a :: k) = A (WrapType a)
 type AW' (a :: k) = A (WrapType a)

 class C (a :: k) where
 aw :: AW a -- workaround: AW'

 instance C [] where
 aw = aw
 }}}

 GHC accepts the program when AW is replaced with AW' on that line.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7503
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #7504: hackage vector package yields ghc bug on raspberry pi

2012-12-16 Thread GHC
#7504: hackage vector package yields ghc bug on raspberry pi
-+--
Reporter:  plaeremans|  Owner: 
Type:  bug   | Status:  new
Priority:  normal|  Component:  Compiler   
 Version:  7.4.1 |   Keywords:  raspberry pi debian
  Os:  Linux |   Architecture:  arm
 Failure:  None/Unknown  |  Blockedby: 
Blocking:|Related: 
-+--
 See output below,


 {{{
 pieter@raspberrypi ~ $ cabal install vector
 Resolving dependencies...
 Configuring vector-0.10.0.1...
 Building vector-0.10.0.1...
 Preprocessing library vector-0.10.0.1...
 [ 1 of 19] Compiling Data.Vector.Storable.Internal (
 Data/Vector/Storable/Internal.hs,
 dist/build/Data/Vector/Storable/Internal.o )
 [ 2 of 19] Compiling Data.Vector.Fusion.Util ( Data/Vector/Fusion/Util.hs,
 dist/build/Data/Vector/Fusion/Util.o )
 [ 3 of 19] Compiling Data.Vector.Fusion.Stream.Size (
 Data/Vector/Fusion/Stream/Size.hs,
 dist/build/Data/Vector/Fusion/Stream/Size.o )

 Data/Vector/Fusion/Stream/Size.hs:25:10:
 Warning: No explicit method nor default method for `*'
 In the instance declaration for `Num Size'

 Data/Vector/Fusion/Stream/Size.hs:25:10:
 Warning: No explicit method nor default method for `abs'
 In the instance declaration for `Num Size'

 Data/Vector/Fusion/Stream/Size.hs:25:10:
 Warning: No explicit method nor default method for `signum'
 In the instance declaration for `Num Size'
 [ 4 of 19] Compiling Data.Vector.Internal.Check (
 Data/Vector/Internal/Check.hs, dist/build/Data/Vector/Internal/Check.o )
 [ 5 of 19] Compiling Data.Vector.Fusion.Stream.Monadic (
 Data/Vector/Fusion/Stream/Monadic.hs,
 dist/build/Data/Vector/Fusion/Stream/Monadic.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.4.1 for arm-unknown-linux):
 Cant do annotations without GHCi
 {Data/Vector/Fusion/Stream/Monadic.hs:104:19-33}
 base:GHC.Exts.ForceSpecConstr{d ra42}

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7504
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7471: Documentation bug: hs_init is incorrectly called in the example

2012-12-07 Thread GHC
#7471: Documentation bug: hs_init is incorrectly called in the example
-+--
Reporter:  dsign |   Owner:  simonmar 
Type:  bug   |  Status:  new  
Priority:  normal|   Milestone:  7.6.2
   Component:  Documentation | Version:   
Keywords:|  Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple  | Failure:  Documentation bug
  Difficulty:  Unknown   |Testcase:   
   Blockedby:|Blocking:   
 Related:|  
-+--
Changes (by simonmar):

  * owner:  = simonmar
  * difficulty:  = Unknown
  * milestone:  = 7.6.2


Comment:

 Thanks, I'll fix that.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7471#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7471: Documentation bug: hs_init is incorrectly called in the example

2012-12-07 Thread GHC
#7471: Documentation bug: hs_init is incorrectly called in the example
-+--
Reporter:  dsign |   Owner:  simonmar 
Type:  bug   |  Status:  new  
Priority:  normal|   Milestone:  7.6.2
   Component:  Documentation | Version:   
Keywords:|  Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple  | Failure:  Documentation bug
  Difficulty:  Unknown   |Testcase:   
   Blockedby:|Blocking:   
 Related:|  
-+--

Comment(by marlowsd@…):

 commit 250f02687eb6dc56394f1c6e9c4cc0aaa34b
 {{{
 Author: Simon Marlow marlo...@gmail.com
 Date:   Fri Dec 7 10:35:40 2012 +

 fix code in library initialisation example (#7471)

  docs/users_guide/ffi-chap.xml |   28 
  1 files changed, 16 insertions(+), 12 deletions(-)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7471#comment:2
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7471: Documentation bug: hs_init is incorrectly called in the example

2012-12-07 Thread GHC
#7471: Documentation bug: hs_init is incorrectly called in the example
-+--
Reporter:  dsign |   Owner:  simonmar 
Type:  bug   |  Status:  merge
Priority:  normal|   Milestone:  7.6.2
   Component:  Documentation | Version:   
Keywords:|  Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple  | Failure:  Documentation bug
  Difficulty:  Unknown   |Testcase:   
   Blockedby:|Blocking:   
 Related:|  
-+--
Changes (by simonmar):

  * status:  new = merge


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7471#comment:3
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7471: Documentation bug: hs_init is incorrectly called in the example

2012-12-07 Thread GHC
#7471: Documentation bug: hs_init is incorrectly called in the example
+---
  Reporter:  dsign  |  Owner:  simonmar
  Type:  bug| Status:  closed  
  Priority:  normal |  Milestone:  7.6.2   
 Component:  Documentation  |Version:  
Resolution:  fixed  |   Keywords:  
Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple
   Failure:  Documentation bug  | Difficulty:  Unknown 
  Testcase: |  Blockedby:  
  Blocking: |Related:  
+---
Changes (by igloo):

  * status:  merge = closed
  * resolution:  = fixed


Comment:

 Merged as 723570dab0384e295ced98089703060fce52e616

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7471#comment:4
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7342: Memory violation bug in System.Posix.Env.putEnv

2012-12-02 Thread GHC
#7342: Memory violation bug in System.Posix.Env.putEnv
--+-
  Reporter:  SimonHengel  |  Owner:
  Type:  bug  | Status:  closed
  Priority:  normal   |  Milestone:
 Component:  libraries/unix   |Version:  7.4.2 
Resolution:  fixed|   Keywords:
Os:  Linux|   Architecture:  x86_64 (amd64)
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown   
  Testcase:   |  Blockedby:
  Blocking:   |Related:
--+-
Changes (by igloo):

  * status:  patch = closed
  * difficulty:  = Unknown
  * resolution:  = fixed


Comment:

 Thanks for the patch! Applied to 7.6 as
 b95a003b20436863ef2f5fc01e6cd77f5bef94a0.

 Fixed in HEAD by:
 {{{
 commit b6b5fcbfd39a69b914f6af931856ef5af63393fc
 Author: Ian Lynagh i...@well-typed.com
 Date:   Sat Dec 1 22:28:50 2012 +

 Add newFilePath to System.Posix.Internals

 Needed for #7342
 }}}

 {{{
 commit 76dad7afeaef33576940b64a7b3be91d05434df5
 Author: Ian Lynagh i...@well-typed.com
 Date:   Sat Dec 1 22:31:48 2012 +

 Fix putenv; trac #7342

 We were freeing the string, but the string becomes part of the
 environment.
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7342#comment:5
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #7471: Documentation bug: hs_init is incorrectly called in the example

2012-12-02 Thread GHC
#7471: Documentation bug: hs_init is incorrectly called in the example
--+-
Reporter:  dsign  |  Owner:  
Type:  bug| Status:  new 
Priority:  normal |  Component:  Documentation   
 Version: |   Keywords:  
  Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple
 Failure:  Documentation bug  |  Blockedby:  
Blocking: |Related:  
--+-
 In the page

 http://www.haskell.org/ghc/docs/7.4.1/html/users_guide/ffi-ghc.html#ffi-
 library

 one of the examples in Using your own main() has some issues.

 See here http://stackoverflow.com/questions/13671429/is-this-typecast-
 correct/13671457#comment18765468_13671457  for more details.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7471
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7318: CONLIKE pragma documentation bug

2012-11-29 Thread GHC
#7318: CONLIKE pragma documentation bug
+---
  Reporter:  acowley|  Owner:  igloo   
  Type:  bug| Status:  closed  
  Priority:  normal |  Milestone:  7.6.2   
 Component:  Documentation  |Version:  7.6.1   
Resolution:  fixed  |   Keywords:  
Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple
   Failure:  Documentation bug  | Difficulty:  Unknown 
  Testcase: |  Blockedby:  
  Blocking: |Related:  
+---
Changes (by igloo):

  * status:  merge = closed
  * resolution:  = fixed


Comment:

 Merged as 003eb67f3380cd764d1bd6f94413eb0f062626b3

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7318#comment:5
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7342: Bug in System.Posix.Env.putEnv

2012-11-17 Thread GHC
#7342: Bug in System.Posix.Env.putEnv
-+--
 Reporter:  SimonHengel  |  Owner:
 Type:  bug  | Status:  patch 
 Priority:  normal   |  Component:  libraries/unix
  Version:  7.4.2|   Keywords:
   Os:  Linux|   Architecture:  x86_64 (amd64)
  Failure:  Incorrect result at runtime  |   Testcase:
Blockedby:   |   Blocking:
  Related:   |  
-+--
Changes (by SimonHengel):

  * status:  new = patch


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7342#comment:3
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7342: Memory violation bug in System.Posix.Env.putEnv (was: Bug in System.Posix.Env.putEnv)

2012-11-17 Thread GHC
#7342: Memory violation bug in System.Posix.Env.putEnv
-+--
 Reporter:  SimonHengel  |  Owner:
 Type:  bug  | Status:  patch 
 Priority:  normal   |  Component:  libraries/unix
  Version:  7.4.2|   Keywords:
   Os:  Linux|   Architecture:  x86_64 (amd64)
  Failure:  Incorrect result at runtime  |   Testcase:
Blockedby:   |   Blocking:
  Related:   |  
-+--

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7342#comment:4
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7192: Bug in -fregs-graph with -fnew-codegen

2012-11-13 Thread GHC
#7192: Bug in -fregs-graph with -fnew-codegen
-+--
Reporter:  simonmar  |   Owner:  benl
Type:  bug   |  Status:  new 
Priority:  highest   |   Milestone:  7.8.1   
   Component:  Compiler  | Version:  7.7 
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  4258
 Related:|  
-+--

Comment(by simonmar):

 Aha! You're absolutely right, it's a bug, sorry about that.  I'm
 validating a fix right now.  I don't seem to be able to reproduce the
 original problem, but I've definitely fixed the missing `R1` dependency.

 I still think we need to look at the graph-colouring allocator though,
 because I think it is interacting badly with the code generated by the new
 code generator.  The code I've seen doesn't look great.  I'm leaving it
 turned off for the time being, and I'll make a separate ticket.

 If you could verify that you don't see the wrong answers any more after my
 patch, that would be great.  Patch coming shortly...

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7192#comment:9
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7192: Bug in -fregs-graph with -fnew-codegen

2012-11-13 Thread GHC
#7192: Bug in -fregs-graph with -fnew-codegen
-+--
Reporter:  simonmar  |   Owner:  benl
Type:  bug   |  Status:  new 
Priority:  highest   |   Milestone:  7.8.1   
   Component:  Compiler  | Version:  7.7 
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  4258
 Related:|  
-+--

Comment(by marlowsd@…):

 commit 4270d7e7485b124dd153399dfe3f571253dc0d1d
 {{{
 Author: Simon Marlow marlo...@gmail.com
 Date:   Tue Nov 13 11:43:09 2012 +

 Fix the Slow calling convention (#7192)

 The Slow calling convention passes the closure in R1, but we were
 ignoring this and hoping it would work, which it often did.  However,
 this bug seems to have been the cause of #7192, because the
 graph-colouring allocator is more sensitive to having correct liveness
 information on jumps.

  compiler/cmm/CmmCallConv.hs  |6 +++---
  compiler/cmm/CmmParse.y  |2 +-
  compiler/cmm/MkGraph.hs  |   32 
  compiler/codeGen/StgCmmBind.hs   |   21 +++--
  compiler/codeGen/StgCmmExpr.hs   |4 ++--
  compiler/codeGen/StgCmmHeap.hs   |   12 
  compiler/codeGen/StgCmmLayout.hs |2 +-
  7 files changed, 30 insertions(+), 49 deletions(-)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7192#comment:10
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7192: Bug in -fregs-graph with -fnew-codegen

2012-11-12 Thread GHC
#7192: Bug in -fregs-graph with -fnew-codegen
-+--
Reporter:  simonmar  |   Owner:  benl
Type:  bug   |  Status:  new 
Priority:  highest   |   Milestone:  7.8.1   
   Component:  Compiler  | Version:  7.7 
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  4258
 Related:|  
-+--

Comment(by benl):

 On x86-32 compiling with the NCG with and without -fregs-graph causes a
 stack overflow in the compiled program, but with -fllvm it works fine.
 Maybe the register liveness determinator is broken, because this is used
 by both the linear and graph coloring allocators.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7192#comment:4
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7192: Bug in -fregs-graph with -fnew-codegen

2012-11-12 Thread GHC
#7192: Bug in -fregs-graph with -fnew-codegen
-+--
Reporter:  simonmar  |   Owner:  benl
Type:  bug   |  Status:  new 
Priority:  highest   |   Milestone:  7.8.1   
   Component:  Compiler  | Version:  7.7 
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  4258
 Related:|  
-+--

Comment(by simonmar):

 @benl: are you saying the `dph-diophantine-opt` test is broken in master
 at the moment?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7192#comment:5
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7192: Bug in -fregs-graph with -fnew-codegen

2012-11-12 Thread GHC
#7192: Bug in -fregs-graph with -fnew-codegen
-+--
Reporter:  simonmar  |   Owner:  benl
Type:  bug   |  Status:  new 
Priority:  highest   |   Milestone:  7.8.1   
   Component:  Compiler  | Version:  7.7 
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  4258
 Related:|  
-+--

Comment(by benl):

 @simonmar: yes. It looks like the NCG (or something) is broken
 independently from the graph allocator.

 When compiling with -fllvm I get the right answer:

 {{{
 desire:diophantine benl$ pwd
 /Users/benl/devel/ghc/ghc-head-devel/testsuite/tests/dph/diophantine

 desire:diophantine benl$ /Users/benl/devel/ghc/ghc-head-devel/inplace/bin
 /ghc-stage2 --version
 The Glorious Glasgow Haskell Compilation System, version 7.7.20121112

 desire:diophantine benl$ /Users/benl/devel/ghc/ghc-head-devel/inplace/bin
 /ghc-stage2 \
   -fforce-recomp -dcore-lint -dcmm-lint \
   --make -o dph-diophantine-copy-fast Main \
   -O -fno-enable-rewrite-rules -package dph-lifted-copy -fllvm

 desire:diophantine benl$ ./dph-diophantine-copy-fast
 (1260,[2,2,1,1,0])
 (1260,[2,2,1,1,0])
 (1260,fromListPArray [2,2,1,1,0])
 }}}

 But with with NCG `-fno-regs-graph` it gives a different answer:
 {{{
 desire:diophantine benl$ /Users/benl/devel/ghc/ghc-head-devel/inplace/bin
 /ghc-stage2 \
   -fforce-recomp -dcore-lint -dcmm-lint \
   --make -o dph-diophantine-copy-fast Main \
   -O -fno-enable-rewrite-rules -package dph-lifted-copy -fno-regs-graph

 desire:diophantine benl$ ./dph-diophantine-copy-fast
 dph-diophantine-copy-fast: Prelude.minimum: empty list
 }}}

 Compiling in different ways by typing `make` in that same directory
 sometimes causes a stack overflow instead of `Prelude.minimum: empty list`

 I looked through the output assembly code but didn't find code code
 sequence in your initial report. My approach was to compile with `-ddump-
 cmmz-sp -ddump-to-file` then grep

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7192#comment:6
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7192: Bug in -fregs-graph with -fnew-codegen

2012-11-12 Thread GHC
#7192: Bug in -fregs-graph with -fnew-codegen
-+--
Reporter:  simonmar  |   Owner:  benl
Type:  bug   |  Status:  new 
Priority:  highest   |   Milestone:  7.8.1   
   Component:  Compiler  | Version:  7.7 
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  4258
 Related:|  
-+--

Comment(by benl):

 ... (continued from previous)... the cmm code for the sequence you had.
 For this I compiled the Haskell code with `-Odph` to get array fusion and
 `-fregs-graph` to turn the graph allocator back on.

 {{{
 desire:diophantine benl$ /Users/benl/devel/ghc/ghc-head-devel/inplace/bin
 /ghc-stage2 \
   -fforce-recomp -dcore-lint -dcmm-lint --make -o dph-diophantine-copy \
   Main -Odph -fregs-graph -package dph-lifted-copy \
   -ddump-cmmz-sp -ddump-asm -ddump-to-file

 desire:diophantine benl$ ./dph-diophantine-copy
 Stack space overflow: current size 8388608 bytes.
 Use `+RTS -Ksize -RTS' to increase it.

 desire:diophantine benl$ grep -B 8 -A 16 if (Sp - 96  SpLim) \
   DiophantineVect.dump-cmmz-sp  dump-entry.cmm
 }}}

 From this I get about 12 blocks of cmm code that look like the one in your
 report. I checked the corresponding asm code and didn't see any register
 allocation problems. A few of the proc entry blocks assign to `%rbx`, but
 the original value this register had on entry to the proc is restored
 before issuing `jmp *-8(%r13)`, which I assume invokes the GC.

 However, I do notice that some of the calls to `stg_gc_fun` in the cmm
 code have `R1` arguments, and some don't.

 {{{
 c1cr6:
   _s12rI::P64 = R6;
   _s12rF::I64 = R5;
   _s12rU::I64 = R4;
   _s12rA::I64 = R3;
   _s12rD::I64 = R2;
   _s12rZ::P64 = R1;
   if (Sp - 96  SpLim) goto c1crZ; else goto c1cs2;
   ...

 c1crZ:
   R1 = _s12rZ::P64;
   I64[Sp - 40] = _s12rD::I64;
   I64[Sp - 32] = _s12rA::I64;
   I64[Sp - 24] = _s12rU::I64;
   I64[Sp - 16] = _s12rF::I64;
   P64[Sp - 8] = _s12rI::P64;
   Sp = Sp - 40;
   call (stg_gc_fun)() args: 48, res: 0, upd: 8;  *** no R1
 argument here
 }}}

 But then:
 {{{
 offset
   c1eWQ:
   _s17H9::P64 = R1;
   if (Sp - 96  SpLim) goto c1eXm; else goto c1eXl;
   ...
   c1eXm:
   R1 = _s17H9::P64;
   call (stg_gc_fun)(R1) args: 8, res: 0, upd: 8;  *** got an R1
 here
 }}}

 If `R1` needs to valid at *every* call to stg_gc_fun, then you need to
 pass it as an argument or the register liveness determinator will mark it
 as dead -- and no good will come from that.

 {{{
 c1crZ:
 movq %vI_s12rZ,%rbx
 # born:%r1
 # r_dying: %vI_s12rZ
 # w_dying: %r1  R1 dies here

 movq %vI_s12rD,-40(%rbp)
 # r_dying: %vI_s12rD

 movq %vI_s12rA,-32(%rbp)
 # r_dying: %vI_s12rA

 movq %vI_s12rU,-24(%rbp)
 # r_dying: %vI_s12rU

 movq %vI_s12rF,-16(%rbp)
 # r_dying: %vI_s12rF

 movq %vI_s12rI,-8(%rbp)
 # r_dying: %vI_s12rI

 addq $-40,%rbp

 jmp *-8(%r13)
 }}}

 If the `stg_gc_fun()` thing is correct then can you tell me how to find
 the assembly sequence in your initial report? I can hack on it this week.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7192#comment:7
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7192: Bug in -fregs-graph with -fnew-codegen

2012-11-12 Thread GHC
#7192: Bug in -fregs-graph with -fnew-codegen
-+--
Reporter:  simonmar  |   Owner:  benl
Type:  bug   |  Status:  new 
Priority:  highest   |   Milestone:  7.8.1   
   Component:  Compiler  | Version:  7.7 
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  4258
 Related:|  
-+--

Comment(by benl):

 Yeah, if the liveness determinator can't see R1 being read in the block
 that calls stg_gc_fun, then it the allocator isn't obliged to preserve
 it's value across the jump. I think your original cmm code is malformed.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7192#comment:8
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7369: Simplifier bug(?)

2012-11-01 Thread GHC
#7369: Simplifier bug(?)
---+
  Reporter:  sweirich  |  Owner:  
  Type:  bug   | Status:  closed  
  Priority:  normal|  Milestone:  
 Component:  Compiler  |Version:  7.6.1   
Resolution:  duplicate |   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  Other | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by sweirich):

 Ah, not a dup of #1495 (which related but uses newtypes and is reported
 fixed),  but it is a duplicate of #5400 (which uses GADTs).

 Also related to #3872.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7369#comment:2
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7369: Simplifier bug(?)

2012-11-01 Thread GHC
#7369: Simplifier bug(?)
---+
  Reporter:  sweirich  |  Owner:  
  Type:  bug   | Status:  closed  
  Priority:  normal|  Milestone:  
 Component:  Compiler  |Version:  7.6.1   
Resolution:  duplicate |   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  Other | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by sweirich):

 Replying to [comment:2 sweirich]:
  Ah, not a dup of #1495 (which related but uses newtypes and is reported
 fixed),  but it is a duplicate of #5400 (which uses GADTs).
 
  Also related to #3872.

 Oops, I meant is a duplicate of #3872 and (perhaps) related to #5400.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7369#comment:3
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7369: Simplifier bug(?)

2012-11-01 Thread GHC
#7369: Simplifier bug(?)
---+
  Reporter:  sweirich  |  Owner:  
  Type:  bug   | Status:  closed  
  Priority:  normal|  Milestone:  
 Component:  Compiler  |Version:  7.6.1   
Resolution:  duplicate |   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  Other | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by simonpj):

 Also #5448, #5722, #7057

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7369#comment:4
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #7369: Simplifier bug(?)

2012-10-26 Thread GHC
#7369: Simplifier bug(?)
--+-
 Reporter:  sweirich  |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Component:  Compiler
  Version:  7.6.1 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  Other |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
 Not sure if it is really a bug.  I was playing around with the following
 infinite loop in GHC 7.6:

 {{{

 {-# LANGUAGE GADTs, KindSignatures #-}

 data False

 data I (c :: * - *)

 data R (c :: *) where
   R :: (a (I a) - False) - R (I a)

 delta :: R (I R) - False
 delta = \ (R f) - f (R f)

 omega :: False
 omega = delta (R delta)

 main :: IO ()
 main = seq omega (return ())

 }}}

 And I got the following result.  It's supposed to be an infinite loop,
 though, so maybe it is ok. GHC 7.4 just hangs on this example.

 {{{
 spaceman:haskell sweirich$ ghc inj4.hs
 [1 of 1] Compiling Main ( inj4.hs, inj4.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.6.1 for i386-apple-darwin):
 Simplifier ticks exhausted
 When trying UnfoldingDone main:Main.$WR{v reV} [gid[DataConWrapper]]
 To increase the limit, use -fsimpl-tick-factor=N (default 100)
 If you need to do this, let GHC HQ know, and what factor you needed
 To see detailed counts use -ddump-simpl-stats
 Total ticks: 5160

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7369
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7369: Simplifier bug(?)

2012-10-26 Thread GHC
#7369: Simplifier bug(?)
---+
  Reporter:  sweirich  |  Owner:  
  Type:  bug   | Status:  closed  
  Priority:  normal|  Milestone:  
 Component:  Compiler  |Version:  7.6.1   
Resolution:  duplicate |   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  Other | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+
Changes (by simonpj):

  * status:  new = closed
  * difficulty:  = Unknown
  * resolution:  = duplicate


Comment:

 I think this is a dup of GHC's russel-paradox bug: #1495.  Re-open if you
 disagree.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7369#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7318: CONLIKE pragma documentation bug

2012-10-25 Thread GHC
#7318: CONLIKE pragma documentation bug
-+--
Reporter:  acowley   |   Owner:  igloo
Type:  bug   |  Status:  new  
Priority:  normal|   Milestone:  7.6.2
   Component:  Documentation | Version:  7.6.1
Keywords:|  Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple  | Failure:  Documentation bug
  Difficulty:  Unknown   |Testcase:   
   Blockedby:|Blocking:   
 Related:|  
-+--

Comment(by ian@…):

 commit e0c77c9f0729c105dddc5ce3fc79e117951719ba
 {{{
 Author: Ian Lynagh i...@well-typed.com
 Date:   Thu Oct 25 20:54:41 2012 +0100

 Fix doc typo; fixes #7318

  docs/users_guide/glasgow_exts.xml |2 +-
  1 files changed, 1 insertions(+), 1 deletions(-)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7318#comment:3
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7318: CONLIKE pragma documentation bug

2012-10-25 Thread GHC
#7318: CONLIKE pragma documentation bug
-+--
Reporter:  acowley   |   Owner:  igloo
Type:  bug   |  Status:  merge
Priority:  normal|   Milestone:  7.6.2
   Component:  Documentation | Version:  7.6.1
Keywords:|  Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple  | Failure:  Documentation bug
  Difficulty:  Unknown   |Testcase:   
   Blockedby:|Blocking:   
 Related:|  
-+--
Changes (by igloo):

  * status:  new = merge


Comment:

 Thanks for the report; fixed.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7318#comment:4
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #7342: Bug in System.Posix.Env.putEnv

2012-10-17 Thread GHC
#7342: Bug in System.Posix.Env.putEnv
-+--
 Reporter:  SimonHengel  |  Owner:
 Type:  bug  | Status:  new   
 Priority:  normal   |  Component:  libraries/unix
  Version:  7.4.2|   Keywords:
   Os:  Linux|   Architecture:  x86_64 (amd64)
  Failure:  Incorrect result at runtime  |   Testcase:
Blockedby:   |   Blocking:
  Related:   |  
-+--
 {{{putEnv}}} frees the marshaled string after calling {{{c_putenv}}}.
 This leads to unpredictable behavior, as the string becomes part of the
 environment and should not be freed.

 See [http://pubs.opengroup.org/onlinepubs/007908799/xsh/putenv.html
 SUSv2]:

  ... the string pointed to by string shall become part of the
  environment ...

 The issue is reproducible with the following QC property:

 {{{
 import   Test.QuickCheck
 import   Test.QuickCheck.Property
 import   System.Posix.Env
 import   Data.IORef
 import qualified Data.Map as Map
 import   Control.Applicative

 isValidKey :: String - Bool
 isValidKey   k = '\NUL' `notElem` k  '=' `notElem` k  (not . null) k

 isValidValue :: String - Bool
 isValidValue v = '\NUL' `notElem` v  (not . null) v

 main :: IO ()
 main = do
   env' - getEnvironment = newIORef . Map.fromList
   quickCheck $ \k v - isValidKey k == isValidValue v ==
 morallyDubiousIOProperty $ do
 putEnv (k ++ = ++ v)
 modifyIORef env' (Map.insert k v)
 (==) $ readIORef env' * (Map.fromList $ getEnvironment)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7342
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7342: Bug in System.Posix.Env.putEnv

2012-10-17 Thread GHC
#7342: Bug in System.Posix.Env.putEnv
-+--
 Reporter:  SimonHengel  |  Owner:
 Type:  bug  | Status:  new   
 Priority:  normal   |  Component:  libraries/unix
  Version:  7.4.2|   Keywords:
   Os:  Linux|   Architecture:  x86_64 (amd64)
  Failure:  Incorrect result at runtime  |   Testcase:
Blockedby:   |   Blocking:
  Related:   |  
-+--

Comment(by SimonHengel):

 Changing {{{putEnv}}} to

 {{{
 putEnv keyvalue = newCString keyvalue = throwErrnoIfMinus1_ putenv .
 c_putenv
 }}}

 fixes the issue.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7342#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7342: Bug in System.Posix.Env.putEnv

2012-10-17 Thread GHC
#7342: Bug in System.Posix.Env.putEnv
-+--
 Reporter:  SimonHengel  |  Owner:
 Type:  bug  | Status:  new   
 Priority:  normal   |  Component:  libraries/unix
  Version:  7.4.2|   Keywords:
   Os:  Linux|   Architecture:  x86_64 (amd64)
  Failure:  Incorrect result at runtime  |   Testcase:
Blockedby:   |   Blocking:
  Related:   |  
-+--

Comment(by SimonHengel):

 While looking at the code, I discovered an other minor issue.  I opened a
 separate ticket for that (#7343).

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7342#comment:2
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7318: CONLIKE pragma documentation bug

2012-10-14 Thread GHC
#7318: CONLIKE pragma documentation bug
-+--
Reporter:  acowley   |   Owner:  igloo
Type:  bug   |  Status:  new  
Priority:  normal|   Milestone:  7.6.2
   Component:  Documentation | Version:  7.6.1
Keywords:|  Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple  | Failure:  Documentation bug
  Difficulty:  Unknown   |Testcase:   
   Blockedby:|Blocking:   
 Related:|  
-+--
Changes (by igloo):

  * milestone:  = 7.6.2


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7318#comment:2
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7318: CONLIKE pragma documentation bug

2012-10-12 Thread GHC
#7318: CONLIKE pragma documentation bug
-+--
Reporter:  acowley   |   Owner:  igloo
Type:  bug   |  Status:  new  
Priority:  normal|   Milestone:   
   Component:  Documentation | Version:  7.6.1
Keywords:|  Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple  | Failure:  Documentation bug
  Difficulty:  Unknown   |Testcase:   
   Blockedby:|Blocking:   
 Related:|  
-+--
Changes (by simonpj):

  * owner:  = igloo
  * difficulty:  = Unknown


Comment:

 Thanks!

 Ian: can you fix this please?  Thanks.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7318#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #7318: CONLIKE pragma documentation bug

2012-10-10 Thread GHC
#7318: CONLIKE pragma documentation bug
---+
 Reporter:  acowley|  Owner:  
 Type:  bug| Status:  new 
 Priority:  normal |  Component:  Documentation   
  Version:  7.6.1  |   Keywords:  
   Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple
  Failure:  Documentation bug  |   Testcase:  
Blockedby: |   Blocking:  
  Related: |  
---+
 The documentation [http://www.haskell.org/ghc/docs/7.6.1/html/users_guide
 /rewrite-rules.html example],
 {{{
 {-# INLINE[1] CONLIKE f #-}
 f x = blah
 }}}
 results in a parse error in 7.6.1, but is accepted if the pragma is
 instead written as
 {{{
 {-# INLINE CONLIKE [1] #-}
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7318
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: copyArray# bug

2012-10-09 Thread Roman Leshchinskiy
Johan Tibell wrote:
 Hi,

 I did quite a bit of work to make sure copyArray# and friends get
 unrolled if the number of elements to copy is a constant. Does this
 still work with the extra branch?

I would expect it to but I don't know. Does the testsuite check for this?

Roman




___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: copyArray# bug

2012-10-09 Thread Herbert Valerio Riedel
Roman Leshchinskiy r...@cse.unsw.edu.au writes:


[...]

 If I'm right then I would suggest not to use copyArray# and
 copyMutableArray# for GHC  7.8.

I've grepped today's

 http://hackage.haskell.org/cgi-bin/hackage-scripts/archive.tar

for occurences of those two primitives, and this resulted in the
following matches:

--8---cut here---start-8---
./unordered-containers-0.2.2.1/Data/HashMap/Array.hs:case copyArray# 
(unArray src) sidx# (unMArray dst) didx# n# s# of
./unordered-containers-0.2.2.1/Data/HashMap/Array.hs:case copyMutableArray# 
(unMArray src) sidx# (unMArray dst) didx# n# s# of
./persistent-vector-0.1.0.1/src/Data/Vector/Persistent/Array.hs:case 
copyArray# (unArray src) sidx# (unMArray dst) didx# n# s# of
./persistent-vector-0.1.0.1/src/Data/Vector/Persistent/Array.hs:case 
copyMutableArray# (unMArray src) sidx# (unMArray dst) didx# n# s# of
./primitive-0.5/Data/Primitive/Array.hs:  = primitive_ (copyArray# src# soff# 
dst# doff# len#)
./primitive-0.5/Data/Primitive/Array.hs:  = primitive_ (copyMutableArray# src# 
soff# dst# doff# len#)
./trifecta-0.53/src/Text/Trifecta/Util/Array.hs:  ST $ \ s# - case copyArray# 
(unArray src) sidx# (unMArray dst) didx# n# s# of
./trifecta-0.53/src/Text/Trifecta/Util/Array.hs:  ST $ \ s# - case 
copyMutableArray# (unMArray src) sidx# (unMArray dst) didx# n# s# of
--8---cut here---end---8---

...so, are you saying, that those packages above are dangerous to use
with GHC=7.6.1?

cheers,
  hvr

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


  1   2   3   4   5   6   7   8   9   10   >