Re: [GHC] #2110: Rules to eliminate casted id's

2012-09-25 Thread GHC
#2110: Rules to eliminate casted id's
-+--
Reporter:  igloo |   Owner:  
Type:  feature request   |  Status:  new 
Priority:  lowest|   Milestone:  7.6.2   
   Component:  Compiler  | Version:  6.8.2   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by simonpj):

 Your previous comment ("I find I disagree").  But I don't see a good
 solution at the moment:
  * I really do not want anything relying on `unsafeCorece`.  There is
 nothing ill-typed going on here, and it would be horrible to subert the
 type system to do something the (FC) type system can express perfectly
 well.
  * I really do not want to magically infer that a function is map-like.
 That seems terribly fragile to me (what about mutual recursion, types with
 multiple parameters, non-uniform recursion etc).   At most one could make
 a special case for lists.

 Generally the GHC story has been, lacking a good way forward, to wait
 until someone has a neat idea, rather than to implement a hack that we
 later regret.  That's where I am on this one at the moment.

 Simon

-- 
Ticket URL: 
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] #367: Infinite loops can hang Concurrent Haskell

2012-09-25 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by ezyang):

 OK, once I get my validate running (failing, due to a certain someone,
 wink), I will push the patch, plus this docu patch:

 {{{
 
   
 -falways-yield
 -falways-
 yield
   
   
   Tells GHC to always emit a pre-emption check on entry
 points to functions. This means that threads that run in tight
 non-allocating loops will get preempted in a timely fashion;
 otherwise, GHC may never manage to interrupt such a loop.  This
 imposes a very slight performance impact but inflates binary sizes
 by about 5%, so it is not enabled by default.  Note that if you
 would like to guarantee that threads can always be interrupted,
 you will need to compile all libraries with this flag.
   
 
 }}}

 What are we going to do with information about CPU hogging primitives?
 There are lots of unsafe primitives which can cause GHC to segfault or
 jump to arbitrary code, so mostly this information would have to be
 advisory for Safe Haskell implementors, who would know if one of these
 primitives were called it better be doing bounds checks, etc. We can't
 forcibly terminate the primops, since they're fat machine instructions and
 don't give up the capability?

-- 
Ticket URL: 
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] #917: -O introduces space leak

2012-09-25 Thread GHC
#917: -O introduces space leak
+---
Reporter:  claus.reinke@…   |   Owner:  
Type:  bug  |  Status:  new 
Priority:  lowest   |   Milestone:  _|_ 
   Component:  Compiler | Version:  6.5 
Keywords:   |  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple | Failure:  None/Unknown
  Difficulty:  Unknown  |Testcase:  
   Blockedby:   |Blocking:  
 Related:   |  
+---
Changes (by ezyang):

 * cc: ezyang@… (added)


-- 
Ticket URL: 
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] #917: -O introduces space leak

2012-09-25 Thread GHC
#917: -O introduces space leak
+---
Reporter:  claus.reinke@…   |   Owner:  
Type:  bug  |  Status:  new 
Priority:  lowest   |   Milestone:  _|_ 
   Component:  Compiler | Version:  6.5 
Keywords:   |  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple | Failure:  None/Unknown
  Difficulty:  Unknown  |Testcase:  
   Blockedby:   |Blocking:  
 Related:   |  
+---

Comment(by ezyang):

 While doing this automatically seems quite hard, would some generalized
 form of ``revertCAFs`` help folks out? The generalization would be on two
 axes: one is that it would apply to any closure on the heap, not just
 CAFs; and two is that you would be able to trigger the reversion from user
 code (some other thunk to force, which you can either throw away or poke
 with a ``seq``).

-- 
Ticket URL: 
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] #7271: Panic with strictness annotation

2012-09-25 Thread GHC
#7271: Panic with strictness annotation
+---
 Reporter:  acowley |  Owner:   
 Type:  bug | Status:  new  
 Priority:  normal  |  Component:  Compiler 
  Version:  7.6.1   |   Keywords:  strictness annotation
   Os:  Unknown/Multiple|   Architecture:  Unknown/Multiple 
  Failure:  Compile-time crash  |   Testcase:   
Blockedby:  |   Blocking:   
  Related:  |  
+---

Comment(by parcs):

 It's fixed in #7210 but it looks like it hasn't been merged with the 7.6
 branch.

-- 
Ticket URL: 
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] #7271: Panic with strictness annotation

2012-09-25 Thread GHC
#7271: Panic with strictness annotation
+---
 Reporter:  acowley |  Owner:   
 Type:  bug | Status:  new  
 Priority:  normal  |  Component:  Compiler 
  Version:  7.6.1   |   Keywords:  strictness annotation
   Os:  Unknown/Multiple|   Architecture:  Unknown/Multiple 
  Failure:  Compile-time crash  |   Testcase:   
Blockedby:  |   Blocking:   
  Related:  |  
+---
 This code

 {{{
 data Foo = Foo (!Int,!Int)
 }}}

 results in a ghc: panic~ (the 'impossible' happened) in 7.6.1 but not
 7.4.2.

-- 
Ticket URL: 
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] #7262: directory 1.2 fails to build with base < 4.6

2012-09-25 Thread GHC
#7262: directory 1.2 fails to build with base < 4.6
--+-
 Reporter:  sopvop|  Owner: 
 Type:  bug   | Status:  new
 Priority:  normal|  Component:  libraries/directory
  Version:  7.4.2 |   Keywords: 
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple   
  Failure:  None/Unknown  |   Testcase: 
Blockedby:|   Blocking: 
  Related:|  
--+-

Comment(by sopvop):

 Second patch allows directory to be build even on ghc-7.0.3.

-- 
Ticket URL: 
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] #7260: directory-1.1.0.2 fails to build on ghc 7.0.3

2012-09-25 Thread GHC
#7260: directory-1.1.0.2 fails to build on ghc 7.0.3
-+--
Reporter:  sopvop|Owner: 
Type:  bug   |   Status:  closed 
Priority:  normal|Component:  libraries/directory
 Version:  7.0.3 |   Resolution:  wontfix
Keywords:|   Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown   
Testcase:|Blockedby: 
Blocking:|  Related: 
-+--
Changes (by sopvop):

  * status:  new => closed
  * resolution:  => wontfix


Comment:

 Actually it can't be built on 7.0.3 at all, because fileSystemEncoding
 only existed in base 4.4.

 Closing because it's too much effort to fix it.
 But lots of checks in code should be cleaned even in latest 1.2 because it
 does not support anything below base 4.4 (ghc-7.2.1)

-- 
Ticket URL: 
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] #7270: Incorrect optimization with Data.ByteString.append

2012-09-25 Thread GHC
#7270: Incorrect optimization with Data.ByteString.append
--+-
  Reporter:  ocheron  |  Owner:  igloo   
  Type:  bug  | Status:  new 
  Priority:  highest  |  Milestone:  7.6.2   
 Component:  libraries (other)|Version:  7.6.1   
Resolution:   |   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by igloo):

  * owner:  => igloo


-- 
Ticket URL: 
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] #7270: Incorrect optimization with Data.ByteString.append

2012-09-25 Thread GHC
#7270: Incorrect optimization with Data.ByteString.append
--+-
  Reporter:  ocheron  |  Owner:  
  Type:  bug  | Status:  new 
  Priority:  highest  |  Milestone:  7.6.2   
 Component:  libraries (other)|Version:  7.6.1   
Resolution:   |   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by igloo):

  * owner:  duncan =>
  * status:  closed => new
  * resolution:  fixed =>


Comment:

 We should make sure this goes into the next GHC release.

-- 
Ticket URL: 
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] #7270: Incorrect optimization with Data.ByteString.append

2012-09-25 Thread GHC
#7270: Incorrect optimization with Data.ByteString.append
--+-
  Reporter:  ocheron  |  Owner:  duncan  
  Type:  bug  | Status:  closed  
  Priority:  highest  |  Milestone:  7.6.2   
 Component:  libraries (other)|Version:  7.6.1   
Resolution:  fixed|   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by duncan):

  * status:  new => closed
  * resolution:  => fixed


Comment:

 Committed to the upstream bytestring repo. So it'll be fixed in the next
 bytestring point release.

 {{{
 Tue Sep 25 16:21:14 BST 2012  Duncan Coutts 
   * Fix a few incorrect uses of inlinePerformIO
   The incorrect use of inlinePerformIO resulted in multiple calls to
   mallocByteString being shared, and hence two different strings sharing
   the same memory. See http://hackage.haskell.org/trac/ghc/ticket/7270

   Consider:
 foo x = s `seq` r
   where
 r = B.map succ x
 s = B.map succ r

   The B.map function used a pattern like:
 map f (PS fp s len) = inlinePerformIO $ ...
fp' <- mallocByteString len

   Now, in the foo function above, we have both r and s where the compiler
   can see that the 'len' is the same in both cases, and with
   inlinePerformIO exposing everything, the compiler is free to share the
   two calls to mallocByteString len.

   The answer is not to use inlinePerformIO if we are allocating, but to
 use
   unsafeDupablePerformIO instead. Another reminder that inlinePerformIO is
   really really unsafe, and that we should be using the ST monad instead.
 }}}

-- 
Ticket URL: 
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] #7270: Incorrect optimization with Data.ByteString.append

2012-09-25 Thread GHC
#7270: Incorrect optimization with Data.ByteString.append
--+-
Reporter:  ocheron|   Owner:  duncan 
Type:  bug|  Status:  new
Priority:  highest|   Milestone:  7.6.2  
   Component:  libraries (other)  | Version:  7.6.1  
Keywords: |  Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple   | Failure:  Incorrect result at runtime
  Difficulty:  Unknown|Testcase: 
   Blockedby: |Blocking: 
 Related: |  
--+-
Changes (by igloo):

  * owner:  igloo => duncan
  * priority:  normal => highest
  * milestone:  => 7.6.2


Comment:

 Thanks for the report. This is due to bytestring's misuse of its
 `inlinePerformIO`; Duncan knows what to do.

 Here's a small standalone program demonstrating the problem:
 {{{
 {-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples #-}

 module Main (main) where

 import GHC.Base
 import GHC.ForeignPtr
 import Foreign

 main :: IO ()
 main = do let !r = make 68
   !s = make 70
   dump r
   dump s

 dump :: ForeignPtr Word8 -> IO ()
 dump fp = do print fp
  withForeignPtr fp $ \p -> do x <- peek p
   print x

 make :: Word8 -> ForeignPtr Word8
 make w = inlinePerformIO $ do fp <- mallocPlainForeignPtrBytes 1
   withForeignPtr fp $ \p -> poke p w
   return fp

 inlinePerformIO :: IO a -> a
 inlinePerformIO (IO m) = case m realWorld# of (# _, r #) -> r
 }}}

 {{{
 $ ghc --make q -O
 $ ./q
 0x7f95b0706010
 68
 0x7f95b0706010
 68
 }}}

-- 
Ticket URL: 
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] #7229: Detecting if a process was killed by a signal is impossible

2012-09-25 Thread GHC
#7229: Detecting if a process was killed by a signal is impossible
--+-
Reporter:  benmachine |   Owner:  
Type:  bug|  Status:  new 
Priority:  high   |   Milestone:  7.6.2   
   Component:  libraries/process  | Version:  
Keywords: |  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple   | Failure:  None/Unknown
  Difficulty:  Unknown|Testcase:  
   Blockedby: |Blocking:  
 Related: |  
--+-

Comment(by benmachine):

 I'm happy with Simon's solution (one aspect that confuses me: if you're
 terminated by signal 3, you get `(3 << 8) + exit code`: what's exit code?)
 but I'd be happier still, I think, with an extra constructor that's unused
 on Windows. It just seems that in practice that's what people will write
 in their code anyway, using a suitable `ExitCode -> Either Signal Int`
 function (or, well, `Either Int Int`, to be portable against the case of
 `Signal` not existing)

-- 
Ticket URL: 
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] #7270: Incorrect optimization with Data.ByteString.append

2012-09-25 Thread GHC
#7270: Incorrect optimization with Data.ByteString.append
--+-
Reporter:  ocheron|   Owner:  igloo  
Type:  bug|  Status:  new
Priority:  normal |   Milestone: 
   Component:  libraries (other)  | Version:  7.6.1  
Keywords: |  Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple   | Failure:  Incorrect result at runtime
  Difficulty:  Unknown|Testcase: 
   Blockedby: |Blocking: 
 Related: |  
--+-
Changes (by igloo):

  * owner:  => igloo
  * difficulty:  => Unknown


-- 
Ticket URL: 
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] #7229: Detecting if a process was killed by a signal is impossible

2012-09-25 Thread GHC
#7229: Detecting if a process was killed by a signal is impossible
--+-
Reporter:  benmachine |   Owner:  
Type:  bug|  Status:  new 
Priority:  high   |   Milestone:  7.6.2   
   Component:  libraries/process  | Version:  
Keywords: |  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple   | Failure:  None/Unknown
  Difficulty:  Unknown|Testcase:  
   Blockedby: |Blocking:  
 Related: |  
--+-

Comment(by andersk):

 Waah… that’s going to confuse anyone who knows that the real encoding is
 `(exit code << 8) + signal` (which, say, Perl forces you to learn).  If
 that’s what we end up with, I guess that difference ought to be noted in
 the documentation.

 I’m not sure I see the problem with an extra constructor that’s unused on
 non-Unix, but other than that I don’t really have anything else to
 propose.

-- 
Ticket URL: 
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] #2110: Rules to eliminate casted id's

2012-09-25 Thread GHC
#2110: Rules to eliminate casted id's
-+--
Reporter:  igloo |   Owner:  
Type:  feature request   |  Status:  new 
Priority:  lowest|   Milestone:  7.6.2   
   Component:  Compiler  | Version:  6.8.2   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by nomeata):

 Thanks for bearing with my spam. I found another reason why a programmer
 might already expect this to work via RULES, and an indication to a
 possible implementation. Consider this code:

 {{{
 newtype X = X Int
 b :: [Int] -> [X]
 b = map X
 c :: [Int] -> [X]
 c = map unsafeCoerce#
 }}}

 Both functions generate almost identical core code, they even share the
 same „identitiy“ function:

 {{{
 Test.b1 :: GHC.Types.Int -> GHC.Types.Int
 [GblId,
  Arity=1,
  Caf=NoCafRefs,
  Str=DmdType S,
  Unf=Unf{Src=, TopLvl=True, Arity=1, Value=True,
  ConLike=True, Cheap=True, Expandable=True,
  Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=True)}]
 Test.b1 = \ (tpl_B1 :: GHC.Types.Int) -> tpl_B1

 Test.b :: [GHC.Types.Int] -> [Test.X]
 [GblId,
  Arity=1,
  Str=DmdType,
  Unf=Unf{Src=, TopLvl=True, Arity=0, Value=True,
  ConLike=True, Cheap=True, Expandable=True,
  Guidance=IF_ARGS [] 20 60}]
 Test.b =
   GHC.Base.map
 @ GHC.Types.Int
 @ Test.X
 (Test.b1
  `cast` ( -> Sym (Test.NTCo:X)
  :: (GHC.Types.Int -> GHC.Types.Int) ~# (GHC.Types.Int ->
 Test.X)))

 Test.c :: [GHC.Types.Int] -> [Test.X]
 [GblId,
  Arity=1,
  Str=DmdType,
  Unf=Unf{Src=, TopLvl=True, Arity=0, Value=True,
  ConLike=True, Cheap=True, Expandable=True,
  Guidance=IF_ARGS [] 20 60}]
 Test.c =
   GHC.Base.map
 @ GHC.Types.Int
 @ Test.X
 (Test.b1
  `cast` ( -> UnsafeCo GHC.Types.Int Test.X
  :: (GHC.Types.Int -> GHC.Types.Int) ~# (GHC.Types.Int ->
 Test.X)))
 }}}

 The only difference is how the coercion is being constructed. Now a the
 author of the list data type might have added this rule:

 {{{
 {-# RULES
 "map/coerce" map unsafeCoerce# = unsafeCoerce#
   #-}
 }}}

 Then assuming the rule fires on ```c``` (and I could swear that it did
 just an hour ago, but I cannot reproduce it now, it seems that now the
 inlining of ```unsafeCoerce#``` happens too soon), then would it not make
 sense to have it also fire on ```b```, giving us the desired result?

 I tried to create a quick hack that would unfold ```unsafeCoerce#``` on
 the LHS of a rule so that the "map/coerce" rule would fire on both the
 inlined ```c``` as well as on ```b```, but my GHC foo is not strong enough
 yet.

 Nevertheless I think letting unsafeCoerce# in a RULE match also functions
 known to be just specializations of it (namely newtype constructors and
 deconstructors) seems to be a reasonably clean way to achieve this,
 without exposing any Core details (casts, equality types) to the surface
 syntax.

-- 
Ticket URL: 
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] #367: Infinite loops can hang Concurrent Haskell

2012-09-25 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by ganesh):

 Why can you assume that calling an arbitrary closure is guaranteed to
 yield?

-- 
Ticket URL: 
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] #7262: directory 1.2 fails to build with base < 4.6

2012-09-25 Thread GHC
#7262: directory 1.2 fails to build with base < 4.6
--+-
 Reporter:  sopvop|  Owner: 
 Type:  bug   | Status:  new
 Priority:  normal|  Component:  libraries/directory
  Version:  7.4.2 |   Keywords: 
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple   
  Failure:  None/Unknown  |   Testcase: 
Blockedby:|   Blocking: 
  Related:|  
--+-
Changes (by bjp):

 * cc: bjp@… (added)


-- 
Ticket URL: 
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] #367: Infinite loops can hang Concurrent Haskell

2012-09-25 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by simonmar):

 I think we could incorporate the patch, but not turn on the flag by
 default.  If you want to work on it further and see if you can get the
 code size penalty down that would be great - my suggestion would be to do
 as I mentioned earlier and omit the yield check for functions which are
 guaranteed to yield within a finite time, because they only call other
 functions which have that property.  You can assume that calling an
 arbitrary closure or a primop is guaranteed to yield.  As a first step you
 can do the analysis within a module, the next step would be to extend it
 across module boundaries.

 We should check the primops to make sure that none of them hog the CPU for
 a long time.  I think `newArray#` has this problem, because it fills in
 the array in a loop, so for a large array it won't yield quickly.

-- 
Ticket URL: 
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] #7229: Detecting if a process was killed by a signal is impossible

2012-09-25 Thread GHC
#7229: Detecting if a process was killed by a signal is impossible
--+-
Reporter:  benmachine |   Owner:  
Type:  bug|  Status:  new 
Priority:  high   |   Milestone:  7.6.2   
   Component:  libraries/process  | Version:  
Keywords: |  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple   | Failure:  None/Unknown
  Difficulty:  Unknown|Testcase:  
   Blockedby: |Blocking:  
 Related: |  
--+-

Comment(by simonmar):

 Ok, points taken.  128+signal is not good, because that overlaps with exit
 codes.

 Unfortunately we can't add the right information to `ExitCode`, because it
 is a platform-independent type.  The correct type already exists: it is
 called `System.Posix.ProcessStatus`.

 {{{
 data ProcessStatus = Exited ExitCode
| Terminated Signal
| Stopped Signal
deriving (Eq, Ord, Show)
 }}}

 Unfortunately whoever wrote this forgot to add a `Bool` to indicate a core
 dump in the `Terminated` constructor.  We *could* fix that.

 Now, the right thing to do would be to create a new `process-unix` package
 containing

 {{{
 module System.Process.Posix where
 waitForProcess :: ProcessHandle -> IO ProcessStatus
 getProcessStatus :: ProcessHandle -> IO (Maybe ProcessStatus)
 }}}

 It can't be part of the `process` package because the API of a package
 cannot differ depending on the platform.  It could be part of the `unix`
 package, but then we have to move a chunk of code from the `process`
 package into the `unix` package, which is annoying.


 I propose as an intermediate solution that we just fix the `ExitCode`
 encoding: instead of 128+signal, use `(signal << 8) + exit code`, with a
 core dump setting the `0x8000` bit.

-- 
Ticket URL: 
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] #2110: Rules to eliminate casted id's

2012-09-25 Thread GHC
#2110: Rules to eliminate casted id's
-+--
Reporter:  igloo |   Owner:  
Type:  feature request   |  Status:  new 
Priority:  lowest|   Milestone:  7.6.2   
   Component:  Compiler  | Version:  6.8.2   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by nomeata):

 I find that I disagree. Consider a library that uses newtypes to hide the
 implementation:
 {{{
 newtype Nat = Nat { natToInteger :: Integer }

 safeNat x = if x >= 0 then Nat x else error "negative"
 ...more operations on nat...
 }}}

 now the user of the library has a value ```l :: [Nat]``` around, but wants
 to go back to Integers. The natural way of doing it is ```map natToInteger
 l```. And I find it reasonable to have the compiler (with the help of the
 library writer) to optimize that to a cast.

 The programmer cannot be the one to have to think about it, because he
 might not even know that Nat ist but a newtype. (Although it might be
 documented somewhere, so he might be expecting zero-overhead over Ints,
 and hence expecting the map to be free.)

 With my proposition, the burdon of writing the rule is not even with the
 library author, but the author of the data structure, in this case the
 list. I find it reasonable to expect him to worry about such things, it is
 no less tricky than using RULES for list fusion.


 If I read your suggestion in comment:23 correctly, you want to introduce a
 type cast operator to the Haskell syntax that checked whether the types
 really have the same representation? Might also be useful, but isn’t this
 risky? We would not want the user to be able to write
 {{{
 let x :: Map Int = 
 y = x |> Map (Down Int)
 }}}
 would we? How would that be prevented?

-- 
Ticket URL: 
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] #2110: Rules to eliminate casted id's

2012-09-25 Thread GHC
#2110: Rules to eliminate casted id's
-+--
Reporter:  igloo |   Owner:  
Type:  feature request   |  Status:  new 
Priority:  lowest|   Milestone:  7.6.2   
   Component:  Compiler  | Version:  6.8.2   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by simonpj):

 I'm sorry, but I can't follow your line of thought.

 In any case, I'm convinced that rewrite rules are not the way to solve
 this problem.  As a programmer I absolutely do not want to rely on some
 relatively-complicated optimisation machinery kicking in to avoid a
 complete traversal of my data structure, when all I'm doing is changing
 the type.  And I want to be able to change the type even if there isn't a
 map function.

 Really the only difficult thing is surface syntax.  Say I have
 {{{
 newtype Age = MkAge { unAge :: Int }
 }}}
 Then if I have
 {{{
e :: Tree (Either Int Int)
 }}}
 I'd like to be able to get these things eaily:
 {{{
e1 :: Tree (Either Age Int)
e2 :: Tree (Either Int Age)
e3 :: Tree (Either Age Age)
 }}}
 One possible syntax might be this:
 {{{
e1 = e |> Tree (Either MkAge Int)
e2 = e |> Tree (Either Int MkAge)
e3 = e |> Tree (Either MkAge MkAge)
 }}}
 Here I am using the data constructor `MkAge` in the middle of a type to
 say "make the change here!".  It's less convenient in the other direction
 {{{
e4 :: Tree (Either Int Age)
e4 = e3 |> Tree (Either unAge Age)
 }}}
 THere's a record selector `unAge` in the middle there.   Maybe we need a
 more explicit signal that we are dropping from the type world to the term
 world, something like
 {{{
   e4 = e3 |> Tree (Either |unAge| Age)
 }}}
 Simon

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

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