Re: Trouble committing

2014-12-14 Thread Herbert Valerio Riedel
On 2014-12-14 at 08:46:03 +0100, Erik de Castro Lopo wrote:

[...]

 $ git push origin master
 
 as explained on https://ghc.haskell.org/trac/ghc/wiki/Phabricator, but on
 the last command I get this error:
 
 fatal: remote error: access denied or repository not exported: /ghc.git
 
 Maybe I just no longer have commit access to ghc?

 Andi,

 Did you get a response to this? I seem to be in the same boat for D570.

What does the following command output in your case?

$ git remote show -n origin | grep URL
  Fetch URL: git://git.haskell.org/ghc.git
  Push  URL: ssh://g...@git.haskell.org/ghc.git
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: performance regressions

2014-12-14 Thread Herbert Valerio Riedel
Hello Richard,

Can you please push the fix asap to master? This performance failures
are causing distracting false alarms (in terms of validation failures)
on each pushed commit as well as submitted code-revisions.

Thanks,
  HVR
  
On 2014-12-13 at 16:55:40 +0100, Richard Eisenberg wrote:
 Fixed, hopefully!

 On Dec 13, 2014, at 10:03 AM, Richard Eisenberg e...@cis.upenn.edu wrote:

 I think I've fixed this. I've pushed the fix to wip/rae, and waiting for 
 validation results before pushing to master.
 
 My hunch below was right -- it was the change to matchFam, which
 essentially evaluated type-level functions more strictly. I've now
 made it lazier again. I'd like to better understand the tradeoff
 here, and to see if there's a principled sweet spot. But that will
 happen in a few days.
 
 Expect a push to master soon.
 
 Again, sorry for the bother.

___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: Trouble committing

2014-12-14 Thread Erik de Castro Lopo
Herbert Valerio Riedel wrote:

 What does the following command output in your case?
 
 $ git remote show -n origin | grep URL
   Fetch URL: git://git.haskell.org/ghc.git
   Push  URL: ssh://g...@git.haskell.org/ghc.git

Fixed it with some help from ezyang who suggested:

git remote set-url origin --push ssh://g...@git.haskell.org/ghc.git

Cheers,
Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: Trouble committing

2014-12-14 Thread Herbert Valerio Riedel
On 2014-12-14 at 11:25:35 +0100, Erik de Castro Lopo wrote:
 What does the following command output in your case?
 
 $ git remote show -n origin | grep URL
   Fetch URL: git://git.haskell.org/ghc.git
   Push  URL: ssh://g...@git.haskell.org/ghc.git

 Fixed it with some help from ezyang who suggested:

 git remote set-url origin --push ssh://g...@git.haskell.org/ghc.git

That works too, but the more general approach (so you don't have to
repeat the step above for other ghc.git repos and/or each submodule
separately) is described below:

  https://ghc.haskell.org/trac/ghc/wiki/WorkingConventions/Git#Pushaccess

Cheers,
  HVR
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: Program runs out of memory using GHC 7.6.3

2014-12-14 Thread Matthias Fischmann

sorry, you're right, my mistake.  makeCounts has no obvious complexity
issues.

my next guess: the default stack size (+RTS -Kn) for 7.6.3 is 8M,
the default for 7.8.3 is 80% of physical memory (see 7.8.1 release
notes).  i think this is the reason why the 7.8.3 executable does not
run out of stack, whlie the 7.6.3 one does.

anyway, if you want to continue this discussion on ghc-dev, you should
probably provide some evidence that it is a bug.  performance
improvements between releases are intentional.  (-:

thanks for the kattis link, btw!

cheers,
m.


On Sat, Dec 13, 2014 at 02:10:25PM -0700, David Spies wrote:
 Date: Sat, 13 Dec 2014 14:10:25 -0700
 From: David Spies dnsp...@gmail.com
 To: Matthias Fischmann m...@zerobuzz.net
 Cc: ghc-devs@haskell.org ghc-devs@haskell.org
 Subject: Re: Program runs out of memory using GHC 7.6.3

 I think there's some confusion about makeCounts's behavior.  makeCount
 never traverses the same thing twice.  Essentially, the worst-case size of
 the unevaluated thunks doesn't exceed the total size of the array of lists
 that was used to create them (and that array itself was created with
 accumArray which is strict).
 Nonetheless, I've tried adding strictness all over makeCounts and it
 reduces the memory usage a little bit, but it still fails a later input
 instance with OOM.  It's not a significant reduction like in GHC 7.8.3


 On Sat, Dec 13, 2014 at 3:06 AM, Matthias Fischmann m...@zerobuzz.net wrote:
 
 
  Hi David,
 
  I don't think this is a ghc issue.
 
  I suspect you have too many unevaluated function calls lying around
  (this would cause the runtime to run out of *stack* as opposed to
  *heap*).  Different versions of ghc perform different optimizations on
  your code, and 7.8 knows a way to fix it that 7.6 doesn't know.
 
  This is usually solved by adding strictness: Instead of letting the
  unevaluated function calls pile up, you force them (e.g. with `print`
  or `Control.DeepSeq.deepseq`).
 
  I would take a closer look at your makeCounts function: you call
  traverse the input list, and traverse the entire list (starting from
  each element) again in each round.  Either you should find a way to
  iterate only once and accumulate all the data you need, or you should
  start optimizing there.
 
  hope this helps,
  cheers,
  matthias
 
 
  On Sat, Dec 13, 2014 at 02:06:52AM -0700, David Spies wrote:
   Date: Sat, 13 Dec 2014 02:06:52 -0700
   From: David Spies dnsp...@gmail.com
   To: ghc-devs@haskell.org ghc-devs@haskell.org
   Subject: Program runs out of memory using GHC 7.6.3
  
   I have a program I submitted for a Kattis problem:
   https://open.kattis.com/problems/digicomp2
   But I got memory limit exceeded.  I downloaded the test data and ran the
   program on my own computer without problems.  Eventually I found out that
   when compiling with GHC 7.6.3 (the version Kattis uses) rather than
  7.8.3,
   this program runs out of memory.
   Can someone explain why it only works on the later compiler?  Is there a
   workaround so that I can submit to Kattis?
  
   Thanks,
   David
 
   module Main(main) where
  
   import   Control.Monad
   import   Data.Array
   import qualified Data.ByteString.Char8 as BS
   import   Data.Int
   import   Data.Maybe
  
   readAsInt :: BS.ByteString - Int
   readAsInt = fst . fromJust . BS.readInt
  
   readVert :: IO Vert
   readVert = do
 [s, sl, sr] - liftM BS.words BS.getLine
 return $ V (fromBS s) (readAsInt sl) (readAsInt sr)
  
   main::IO()
   main = do
 [n, m64] - liftM (map read . words) getLine :: IO [Int64]
 let m = fromIntegral m64 :: Int
 verts - replicateM m readVert
 let vside = map getSide verts
 let vpar = concat $ zipWith makeAssoc [1..] verts
 let parArr = accumArray (flip (:)) [] (1, m) vpar
 let counts = makeCounts n m $ elems parArr
 let res = zipWith doFlips counts vside
 putStrLn $ map toChar res
  
   doFlips :: Int64 - Side - Side
   doFlips n
 | odd n = flipSide
 | otherwise = id
  
   makeCounts :: Int64 - Int - [[(Int, Round)]] - [Int64]
   makeCounts n m l = tail $ elems res
 where
   res = listArray (0, m) $ 0 : n : map makeCount (tail l)
   makeCount :: [(Int, Round)] - Int64
   makeCount = sum . map countFor
   countFor :: (Int, Round) - Int64
   countFor (i, Up) = ((res ! i) + 1) `quot` 2
   countFor (i, Down) = (res ! i) `quot` 2
  
   fromBS :: BS.ByteString - Side
   fromBS = fromChar . BS.head
  
   fromChar :: Char - Side
   fromChar 'L' = L
   fromChar 'R' = R
   fromChar _ = error Bad char
  
   toChar :: Side - Char
   toChar L = 'L'
   toChar R = 'R'
  
   makeAssoc :: Int - Vert - [(Int, (Int, Round))]
   makeAssoc n (V L a b) = filtPos [(a, (n, Up)), (b, (n, Down))]
   makeAssoc n (V R a b) = filtPos [(a, (n, Down)), (b, (n, Up))]
  
   filtPos :: [(Int, a)] - [(Int, a)]
   filtPos = filter (( 0) . fst)
  
   data Vert = V !Side !Int !Int
  
   getSide :: Vert 

Re: Program runs out of memory using GHC 7.6.3

2014-12-14 Thread David Spies
Oh,
Now I feel really silly for not noticing that that number was 8 MB.  I saw
the 8 at the beginning all this time and just assumed it meant 8 GB.

I'm sorry,
In the future I'll post queries like this on the GHC-users mailing list.
I'm guessing Kattis doesn't bother to change the default stack size when
they run the program.  I'll email to let them know.

Thank you,
David


On Sun, Dec 14, 2014 at 4:03 AM, Matthias Fischmann m...@zerobuzz.net wrote:


 sorry, you're right, my mistake.  makeCounts has no obvious complexity
 issues.

 my next guess: the default stack size (+RTS -Kn) for 7.6.3 is 8M,
 the default for 7.8.3 is 80% of physical memory (see 7.8.1 release
 notes).  i think this is the reason why the 7.8.3 executable does not
 run out of stack, whlie the 7.6.3 one does.

 anyway, if you want to continue this discussion on ghc-dev, you should
 probably provide some evidence that it is a bug.  performance
 improvements between releases are intentional.  (-:

 thanks for the kattis link, btw!

 cheers,
 m.


 On Sat, Dec 13, 2014 at 02:10:25PM -0700, David Spies wrote:
  Date: Sat, 13 Dec 2014 14:10:25 -0700
  From: David Spies dnsp...@gmail.com
  To: Matthias Fischmann m...@zerobuzz.net
  Cc: ghc-devs@haskell.org ghc-devs@haskell.org
  Subject: Re: Program runs out of memory using GHC 7.6.3
 
  I think there's some confusion about makeCounts's behavior.  makeCount
  never traverses the same thing twice.  Essentially, the worst-case size
 of
  the unevaluated thunks doesn't exceed the total size of the array of
 lists
  that was used to create them (and that array itself was created with
  accumArray which is strict).
  Nonetheless, I've tried adding strictness all over makeCounts and it
  reduces the memory usage a little bit, but it still fails a later input
  instance with OOM.  It's not a significant reduction like in GHC 7.8.3
 
 
  On Sat, Dec 13, 2014 at 3:06 AM, Matthias Fischmann m...@zerobuzz.net
 wrote:
  
  
   Hi David,
  
   I don't think this is a ghc issue.
  
   I suspect you have too many unevaluated function calls lying around
   (this would cause the runtime to run out of *stack* as opposed to
   *heap*).  Different versions of ghc perform different optimizations on
   your code, and 7.8 knows a way to fix it that 7.6 doesn't know.
  
   This is usually solved by adding strictness: Instead of letting the
   unevaluated function calls pile up, you force them (e.g. with `print`
   or `Control.DeepSeq.deepseq`).
  
   I would take a closer look at your makeCounts function: you call
   traverse the input list, and traverse the entire list (starting from
   each element) again in each round.  Either you should find a way to
   iterate only once and accumulate all the data you need, or you should
   start optimizing there.
  
   hope this helps,
   cheers,
   matthias
  
  
   On Sat, Dec 13, 2014 at 02:06:52AM -0700, David Spies wrote:
Date: Sat, 13 Dec 2014 02:06:52 -0700
From: David Spies dnsp...@gmail.com
To: ghc-devs@haskell.org ghc-devs@haskell.org
Subject: Program runs out of memory using GHC 7.6.3
   
I have a program I submitted for a Kattis problem:
https://open.kattis.com/problems/digicomp2
But I got memory limit exceeded.  I downloaded the test data and ran
 the
program on my own computer without problems.  Eventually I found out
 that
when compiling with GHC 7.6.3 (the version Kattis uses) rather than
   7.8.3,
this program runs out of memory.
Can someone explain why it only works on the later compiler?  Is
 there a
workaround so that I can submit to Kattis?
   
Thanks,
David
  
module Main(main) where
   
import   Control.Monad
import   Data.Array
import qualified Data.ByteString.Char8 as BS
import   Data.Int
import   Data.Maybe
   
readAsInt :: BS.ByteString - Int
readAsInt = fst . fromJust . BS.readInt
   
readVert :: IO Vert
readVert = do
  [s, sl, sr] - liftM BS.words BS.getLine
  return $ V (fromBS s) (readAsInt sl) (readAsInt sr)
   
main::IO()
main = do
  [n, m64] - liftM (map read . words) getLine :: IO [Int64]
  let m = fromIntegral m64 :: Int
  verts - replicateM m readVert
  let vside = map getSide verts
  let vpar = concat $ zipWith makeAssoc [1..] verts
  let parArr = accumArray (flip (:)) [] (1, m) vpar
  let counts = makeCounts n m $ elems parArr
  let res = zipWith doFlips counts vside
  putStrLn $ map toChar res
   
doFlips :: Int64 - Side - Side
doFlips n
  | odd n = flipSide
  | otherwise = id
   
makeCounts :: Int64 - Int - [[(Int, Round)]] - [Int64]
makeCounts n m l = tail $ elems res
  where
res = listArray (0, m) $ 0 : n : map makeCount (tail l)
makeCount :: [(Int, Round)] - Int64
makeCount = sum . map countFor
countFor :: (Int, Round) - Int64
countFor (i, Up) = ((res ! i) + 1) `quot` 2
countFor 

Re: more parser conflicts?

2014-12-14 Thread Sergei Trofimovich
On Sat, 13 Dec 2014 15:19:34 +
Sergei Trofimovich sly...@gmail.com wrote:

 On Wed, 03 Dec 2014 11:59:42 +
 Simon Marlow marlo...@gmail.com wrote:
 
   In unrelated work, I saw this scroll across when happy'ing the parser:
  
   shift/reduce conflicts:  60
   reduce/reduce conflicts: 16
  
   These numbers seem quite a bit higher than what I last remember (which
   is something like 48 and 1, not 60 and 16). Does anyone know why?
 
 4 of reduce/reduce conflicts are result of exact rule copy:
 https://phabricator.haskell.org/D569
 
  reduce/reduce conflicts are bad, especially so since they're 
  undocumented.  We don't know whether this introduced parser bugs or not. 
Mike - could you look at this please?  It was your commit that 
  introduced the new conflicts.
 
 Agreed.
 
 11 more reduce/reduce (of left 12) came from single scary rule
 added in
  commit bc2289e13d9586be087bd8136943dc35a0130c88
 ghc generates more user-friendly error messages
 
 exp10 :: { LHsExpr RdrName }
 ...
  | 'let' binds {% parseErrorSDoc (combineLocs $1 $2) $ text
  parse error in let binding: missing required 
 'in'
 }
 
 The other rules add shift/reduce conflicts as follows:
 
 -- parsing error messages go below here
 {- s/r:1 r/r:0 -}
 | '\\' apat apats opt_asig '-' {% parseErrorSDoc (combineLocs $1 $5) $ 
 text
parse error in 
 lambda: no expression after '-'
 {- s/r:1 r/r:0 -}
 | '\\'   {% parseErrorSDoc (getLoc 
 $1) $ text
parse error: naked 
 lambda expression '\'
 }
 {- s/r:1 r/r:0 -}
 | 'let' binds 'in'   {% parseErrorSDoc 
 (combineLocs $1 $2) $ text
parse error in let 
 binding: missing expression after 'in'
 }
 {- s/r:0 r/r:11 -}
  | 'let' binds{% parseErrorSDoc 
 (combineLocs $1 $2) $ text
 parse error in let 
 binding: missing required 'in'
  }
 {- s/r:0 r/r:0 -}
 | 'let'  {% parseErrorSDoc 
 (getLoc $1) $ text
parse error: naked 
 let binding
}
 {- s/r:1 r/r:0 -}
 | 'if' exp optSemi 'then' exp optSemi 'else' {% hintIf (combineLocs 
 $1 $5) else clause empty }
 {- s/r:2 r/r:0 -}
 | 'if' exp optSemi 'then' exp optSemi{% hintIf (combineLocs 
 $1 $5) missing required else clause }
 {- s/r:1 r/r:0 -}
 | 'if' exp optSemi 'then'{% hintIf (combineLocs 
 $1 $2) then clause empty }
 {- s/r:2 r/r:0 -}
 | 'if' exp optSemi   {% hintIf (combineLocs 
 $1 $2) missing required then and else clauses
 {- s/r:2 r/r:0 -}
 | 'if'   {% hintIf (getLoc $1) 
 naked if statement }
 {- s/r:0 r/r:0 -}
 | 'case' exp 'of'{% parseErrorSDoc 
 (combineLocs $1 $2) $ text
 parse error in case 
 statement: missing list after '-'
   }
 {- s/r:1 r/r:0 -}
 | 'case' exp {% parseErrorSDoc 
 (combineLocs $1 $2) $ text
parse error in case 
 statement: missing required 'of'
  }
 {- s/r:1 r/r:0 -}
 | 'case' {% parseErrorSDoc 
 (getLoc $1) $ text
 parse error: naked 
 case statement
   }
 
 Shift/reduces look harmless (like MultiWayIf ambiguity)
 as they seem to resolve as shift correctly.

Proposed fix as:
https://phabricator.haskell.org/D571

Simon, is using happy's error token the proper way of fixing
these error reporting rules?

Thanks!

-- 

  Sergei


signature.asc
Description: PGP signature
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: performance regressions

2014-12-14 Thread Joachim Breitner
Hi,

Am Samstag, den 13.12.2014, 10:55 -0500 schrieb Richard Eisenberg:
 Fixed, hopefully!

Mitigated, but still a regression:

http://ghcspeed-nomeata.rhcloud.com/timeline/?exe=2base=2%2B68ben=tests%2Falloc%2FT9872aenv=1revs=50equid=on#

Is that now a level that we’ll have to live with, or is it still
unexpectedly high?

Greetings,
Joachim

-- 
Joachim “nomeata” Breitner
  m...@joachim-breitner.de • http://www.joachim-breitner.de/
  Jabber: nome...@joachim-breitner.de  • GPG-Key: 0xF0FBF51F
  Debian Developer: nome...@debian.org



signature.asc
Description: This is a digitally signed message part
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: performance regressions

2014-12-14 Thread Richard Eisenberg
I pushed my supposed fix yesterday morning, as I emailed out the Fixed, 
hopefully note.

Of course, I now see that it wasn't a full fix.

This is all most assuredly my fault. However, I also feel that elements of the 
infrastructure failed me somewhat, making this error easier for me to commit:
- Travis has not picked up on these errors.
- Harbormaster has seemed unreliable, finding spurious compile-time errors 
sometimes, and sometimes just failing to test code that it sees. For example, 
when I pushed Diff 1901 to D546, Harbormaster never even attempted. Also, when 
I pushed my fix, commit 3ec9391711, Harbormaster also skipped, as viewable 
here: https://phabricator.haskell.org/diffusion/GHC/

So, after pushing yesterday morning, I didn't get any email from Harbormaster 
saying that it failed, so I thought my fix was indeed a fix. Because my local 
build was a devel2 build (and that I had only about 20 minutes to work), I was 
unable to test locally -- all I could tell is that my fix lowered the numbers 
(as verified by ghcspeed).

Having a weekend full of plans, there wasn't really any opportunity for me to 
do the work necessary to figure out what's going on. It will be first on my 
docket tomorrow.

I suppose one lesson here is that I shouldn't push anything at all non-trivial 
on a Friday afternoon. But I also hope we can either improve the infrastructure 
(of course, it's *much* better than it was months ago!) or have realistic 
expectations of what we can expect from the infrastructure (e.g., trust 
Harbormaster/Travis when seeking feedback, but always validate locally before 
actually pushing to master).

More tomorrow,
Richard

On Dec 14, 2014, at 3:47 PM, Joachim Breitner m...@joachim-breitner.de wrote:

 Hi,
 
 Am Samstag, den 13.12.2014, 10:55 -0500 schrieb Richard Eisenberg:
 Fixed, hopefully!
 
 Mitigated, but still a regression:
 
 http://ghcspeed-nomeata.rhcloud.com/timeline/?exe=2base=2%2B68ben=tests%2Falloc%2FT9872aenv=1revs=50equid=on#
 
 Is that now a level that we’ll have to live with, or is it still
 unexpectedly high?
 
 Greetings,
 Joachim
 
 -- 
 Joachim “nomeata” Breitner
  m...@joachim-breitner.de • http://www.joachim-breitner.de/
  Jabber: nome...@joachim-breitner.de  • GPG-Key: 0xF0FBF51F
  Debian Developer: nome...@debian.org
 

___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs