RE: [commit: ghc] master: Fix Trac #7681. (7b098b6)

2013-02-12 Thread Simon Peyton-Jones
Thanks for fixing.

You removed lookupType_mod from TrieMap.  It was defined and exported but not 
called. How did validate spot that?   I'm sure there are quite a few such 
functions in GHC.

Simon

| -Original Message-
| From: ghc-commits-boun...@haskell.org [mailto:ghc-commits-
| boun...@haskell.org] On Behalf Of Richard Eisenberg
| Sent: 12 February 2013 04:10
| To: ghc-comm...@haskell.org
| Subject: [commit: ghc] master: Fix Trac #7681. (7b098b6)
| 
| Repository : ssh://darcs.haskell.org//srv/darcs/ghc
| 
| On branch  : master
| 
| http://hackage.haskell.org/trac/ghc/changeset/7b098b6009727a012cb1f3ff0c
| a51698d302cae1
| 
| ---
| 
| commit 7b098b6009727a012cb1f3ff0ca51698d302cae1
| Author: Richard Eisenberg e...@cis.upenn.edu
| Date:   Mon Feb 11 23:07:25 2013 -0500
| 
| Fix Trac #7681.
| 
| Removed checks for empty lists for case expressions and lambda-case.
| If -XEmptyCase is not enabled, compilation still fails
| (appropriately)
| in the renamer.
| 
| Had to remove dead code from TrieMap to pass the validator.
| 
| ---
| 
|  compiler/coreSyn/TrieMap.lhs |   38 +--
| ---
|  compiler/deSugar/DsMeta.hs   |6 --
|  compiler/hsSyn/Convert.lhs   |8 ++--
|  libraries/random |2 +-
|  4 files changed, 8 insertions(+), 46 deletions(-)
| 
| diff --git a/compiler/coreSyn/TrieMap.lhs b/compiler/coreSyn/TrieMap.lhs
| index 148464b..c013b5d 100644
| --- a/compiler/coreSyn/TrieMap.lhs
| +++ b/compiler/coreSyn/TrieMap.lhs
| @@ -14,7 +14,7 @@
|  {-# LANGUAGE TypeFamilies #-}
|  module TrieMap(
| CoreMap, emptyCoreMap, extendCoreMap, lookupCoreMap, foldCoreMap,
| -   TypeMap, foldTypeMap, lookupTypeMap_mod,
| +   TypeMap, foldTypeMap, -- lookupTypeMap_mod,
| CoercionMap,
| MaybeMap,
| ListMap,
| @@ -32,8 +32,6 @@ import UniqFM
|  import Unique( Unique )
|  import FastString(FastString)
| 
| -import Unify ( niFixTvSubst )
| -
|  import qualified Data.Mapas Map
|  import qualified Data.IntMap as IntMap
|  import VarEnv
| @@ -632,40 +630,6 @@ lkT env ty m
|  go (ForAllTy tv ty)  = tm_forall . lkT (extendCME env tv) ty =
| lkBndr env tv
| 
| 
| -lkT_mod :: CmEnv
| -- TyVarEnv Type -- TvSubstEnv
| -- Type
| -- TypeMap b - Maybe b
| -lkT_mod env s ty m
| -  | EmptyTM - m = Nothing
| -  | Just ty' - coreView ty
| -  = lkT_mod env s ty' m
| -  | [] - candidates
| -  = go env s ty m
| -  | otherwise
| -  = Just $ snd (head candidates) -- Yikes!
| -  where
| - -- Hopefully intersects is much smaller than traversing the whole
| vm_fvar
| -intersects = eltsUFM $
| - intersectUFM_C (,) s (vm_fvar $ tm_var m)
| -candidates = [ (u,ct) | (u,ct) - intersects
| -  , Type.substTy (niFixTvSubst s) u `eqType` ty
| ]
| -
| -go env _s (TyVarTy v)  = tm_var. lkVar env v
| -go env s (AppTy t1 t2) = tm_app. lkT_mod env s t1 =
| lkT_mod env s t2
| -go env s (FunTy t1 t2) = tm_fun. lkT_mod env s t1 =
| lkT_mod env s t2
| -go env s (TyConApp tc tys) = tm_tc_app . lkNamed tc = lkList
| (lkT_mod env s) tys
| -go _env _s (LitTy l)   = tm_tylit  . lkTyLit l
| -go _env _s (ForAllTy _tv _ty) = const Nothing
| -
| -{- DV TODO: Add proper lookup for ForAll -}
| -
| -lookupTypeMap_mod :: TyVarEnv a -- A substitution to be applied to the
| /keys/ of type map
| -  - (a - Type)
| -  - Type
| -  - TypeMap b - Maybe b
| -lookupTypeMap_mod s f = lkT_mod emptyCME (mapVarEnv f s)
| -
|  -
|  xtT :: CmEnv - Type - XT a - TypeMap a - TypeMap a  xtT env ty f m
| diff --git a/compiler/deSugar/DsMeta.hs b/compiler/deSugar/DsMeta.hs
| index 9a9f89d..4f5ba2d 100644
| --- a/compiler/deSugar/DsMeta.hs
| +++ b/compiler/deSugar/DsMeta.hs
| @@ -920,7 +920,8 @@ repE (HsLit l) = do { a - repLiteral l;
| repLit a }
|  repE (HsLam (MG { mg_alts = [m] })) = repLambda m  repE (HsLamCase _
| (MG { mg_alts = ms }))
| = do { ms' - mapM repMatchTup ms
| -; repLamCase (nonEmptyCoreList ms') }
| +; core_ms - coreList matchQTyConName ms'
| +; repLamCase core_ms }
|  repE (HsApp x y)   = do {a - repLE x; b - repLE y; repApp a b}
| 
|  repE (OpApp e1 op _ e2) =
| @@ -938,7 +939,8 @@ repE (SectionR x y)   = do { a - repLE x; b -
| repLE y; repSectionR a b }
|  repE (HsCase e (MG { mg_alts = ms }))
|= do { arg - repLE e
| ; ms2 - mapM repMatchTup ms
| -   ; repCaseE arg (nonEmptyCoreList ms2) }
| +   ; core_ms2 - coreList matchQTyConName
| ms2
| +   ; repCaseE arg core_ms2 }
|  repE (HsIf _ x y z) = do
|   

RE: RFC: Singleton equality witnesses

2013-02-12 Thread Simon Peyton-Jones
- Currently, the internals of GHC assign types like 0 the kind 
GHC.TypeLits.Nat, so Nat and Symbol *must* remain in the GHC.TypeLits module. 
Unfortunately, the plumbing around GHC.TypeLits.Unsafe want Nat and Symbol to 
be defined in GHC.TypeLits.Internals. So, I created a TypeLits.hs-boot file to 
fix the problem. This is highly unsatisfactory, and if something like what I've 
done here sticks around, we should change the internals of GHC to use 
GHC.TypeLits.Internals.Nat, getting rid of the import cycle.

Let's NOT have an hs-boot file here.  Instead, change PrelNames to tell GHC 
where Nat and Symbol are defined.  It's ok for them to be in Internals.

I'm also unconvinced about the distinction between Internals and Unsafe.  
To me the former connotes the latter.  Import Internals if you know what you 
are doing; eg that might let you break important invariants.  Import a kosher 
module like TypeLits if you want the Joe Programmer interface.

Simon

From: ghc-devs-boun...@haskell.org [mailto:ghc-devs-boun...@haskell.org] On 
Behalf Of Richard Eisenberg
Sent: 12 February 2013 02:41
To: Iavor Diatchki
Cc: José Pedro Magalhães; ghc-devs
Subject: Re: RFC: Singleton equality witnesses

I've just pushed a commit to the type-reasoning branch with a strawman proposal 
of a reorganization of these definitions. Specifically, this commit breaks 
TypeLits into the following five files:

- GHC.TypeEq, which contains the definitions for (:~:), Void, Refuted, etc.
- GHC.Singletons, which contains the definitions about singletons in general, 
such as SingI and SingEquality
- GHC.TypeLits.Unsafe, which contains just unsafeSingNat and unsafeSingSymbol
- GHC.TypeLits.Internals, which is necessary to get GHC.TypeLits.Unsafe to have 
access to the right internals;
this module is not exported from the 'base' package
and
- GHC.TypeLits, which contains the definitions specific to type-level literals.

Some thoughts on this design:
- First off, why is TypeEq part of GHC?? Because we wish to write eqSingNat and 
eqSingSym in GHC.TypeLits, and that module rightly deserves to be part of GHC. 
I'm quite uncomfortable with this decision, and I even created a new git repo 
at 
github.com/goldfirere/type-reasoninghttp://github.com/goldfirere/type-reasoning
 to hold the definitions that eventually ended up in GHC.TypeEq. (The repo has 
nothing in it, now.) Perhaps the best resolution is to move eqSingNat and 
eqSingSym out of GHC.TypeLits and into an external package, but that seems 
silly in a different direction. (It is fully technically feasible, as those 
functions don't depend on any internals.) I would love some feedback here.
- Why is Singletons broken off? No strong reason here, but it seemed that the 
singletons-oriented definitions weren't solely related to type-level literals, 
so it seemed more natural this way.
- Making the Unsafe module was a little more principled, because those 
functions really are unsafe! They are quite useful, though, and should be 
available somewhere.
- Currently, the internals of GHC assign types like 0 the kind 
GHC.TypeLits.Nat, so Nat and Symbol *must* remain in the GHC.TypeLits module. 
Unfortunately, the plumbing around GHC.TypeLits.Unsafe want Nat and Symbol to 
be defined in GHC.TypeLits.Internals. So, I created a TypeLits.hs-boot file to 
fix the problem. This is highly unsatisfactory, and if something like what I've 
done here sticks around, we should change the internals of GHC to use 
GHC.TypeLits.Internals.Nat, getting rid of the import cycle.
- I've put in the decideSing function as discussed further up in this thread. 
Its implementation for Nat and Symbol must use unsafeCoerce, but that shouldn't 
be a surprise.

Unfortunately, the code doesn't compile now. This is because it needs SingI 
instances for, say, Sing 0. For a reason I have not explored, these instances 
are not available here, though they seem to be for code written outside of GHC. 
Iavor, any thoughts on this?

Please tear any of these ideas (or my whole commit) to shreds! It really is 
meant to be a strawman proposal, but committing these changes seemed the best 
way of communicating on possible set of design decisions.

Richard

PS: I'm pasting much of this email to the wiki page for posterity.

On Feb 7, 2013, at 10:45 AM, Iavor Diatchki 
iavor.diatc...@gmail.commailto:iavor.diatc...@gmail.com wrote:


Hello,

my preference would be to build this kind of functionality (and other related 
features) in libraries on top of GHC.TypeLits.  This modules was intended to 
contain only a minimal set of the constants that the compiler needs to know 
about, and it already may have too much in it.

On the concrete issue:  orphan instances could be avoided if the type lits 
instances are defined in the same module as the class.

-Iavor

On Thu, Feb 7, 2013 at 6:50 AM, Gabor Greif 
ggr...@gmail.commailto:ggr...@gmail.com wrote:
In its current state it is not tied to TypeLits, but when Richard adds
his magic it probably will 

RE: [commit: vector] master: Implement poly-kinded Typeable (8b27167)

2013-02-12 Thread Simon Peyton-Jones
Hang on... vector has an upstream repo; see 
http://hackage.haskell.org/trac/ghc/wiki/Repositories
and in particular the Upstream repo? bullet.
So we may need to do more than push to the mirror?

Simon

| -Original Message-
| From: ghc-commits-boun...@haskell.org [mailto:ghc-commits-
| boun...@haskell.org] On Behalf Of José Pedro Magalhães
| Sent: 12 February 2013 10:41
| To: ghc-comm...@haskell.org
| Subject: [commit: vector] master: Implement poly-kinded Typeable
| (8b27167)
| 
| Repository : ssh://darcs.haskell.org//srv/darcs/packages/vector
| 
| On branch  : master
| 
| http://hackage.haskell.org/trac/ghc/changeset/8b271670f79a3b50d7e15ca924
| 878212f042f259
| 
| ---
| 
| commit 8b271670f79a3b50d7e15ca924878212f042f259
| Author: Jose Pedro Magalhaes j...@cs.ox.ac.uk
| Date:   Thu Feb 7 14:00:33 2013 +
| 
| Implement poly-kinded Typeable
| 
| This patch makes the Data.Typeable.Typeable class work with
| arguments of any
| kind. In particular, this removes the Typeable1..7 class hierarchy,
| greatly
| simplyfing the whole Typeable story. Also added is the
| AutoDeriveTypeable
| language extension, which will automatically derive Typeable for all
| types and
| classes declared in that module. Since there is now no good reason
| to give
| handwritten instances of the Typeable class, those are ignored (for
| backwards
| compatibility), and a warning is emitted.
| 
| The old, kind-* Typeable class is now called OldTypeable, and lives
| in the
| Data.OldTypeable module. It is deprecated, and should be removed in
| some future
| version of GHC.
| 
| ---
| 
|  Data/Vector/Generic.hs  |9 +
|  Data/Vector/Unboxed/Base.hs |   14 +-
|  2 files changed, 22 insertions(+), 1 deletions(-)
| 
| diff --git a/Data/Vector/Generic.hs b/Data/Vector/Generic.hs index
| b8f2e81..f17ff23 100644
| --- a/Data/Vector/Generic.hs
| +++ b/Data/Vector/Generic.hs
| @@ -194,7 +194,12 @@ import Prelude hiding ( length, null,
|  showsPrec )
| 
|  import qualified Text.Read as Read
| +
| +#if __GLASGOW_HASKELL__ = 707
| +import Data.Typeable ( Typeable, gcast1 ) #else
|  import Data.Typeable ( Typeable1, gcast1 )
| +#endif
| 
|  #include vector.h
| 
| @@ -2020,7 +2025,11 @@ mkType :: String - DataType  {-# INLINE mkType
| #-}  mkType = mkNoRepType
| 
| +#if __GLASGOW_HASKELL__ = 707
| +dataCast :: (Vector v a, Data a, Typeable v, Typeable t) #else
|  dataCast :: (Vector v a, Data a, Typeable1 v, Typeable1 t)
| +#endif
|   = (forall d. Data  d = c (t d)) - Maybe  (c (v a))  {-#
| INLINE dataCast #-}  dataCast f = gcast1 f diff --git
| a/Data/Vector/Unboxed/Base.hs b/Data/Vector/Unboxed/Base.hs index
| 2d9822e..359b001 100644
| --- a/Data/Vector/Unboxed/Base.hs
| +++ b/Data/Vector/Unboxed/Base.hs
| @@ -1,4 +1,7 @@
|  {-# LANGUAGE MultiParamTypeClasses, TypeFamilies, FlexibleContexts #-}
| +#if __GLASGOW_HASKELL__ = 707
| +{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-} #endif
|  {-# OPTIONS_HADDOCK hide #-}
| 
|  -- |
| @@ -29,6 +32,9 @@ import Data.Word ( Word, Word8, Word16, Word32, Word64
| )  import Data.Int  ( Int8, Int16, Int32, Int64 )  import Data.Complex
| 
| +#if __GLASGOW_HASKELL__ = 707
| +import Data.Typeable ( Typeable )
| +#else
|  import Data.Typeable ( Typeable1(..), Typeable2(..), mkTyConApp,  #if
| MIN_VERSION_base(4,4,0)
| mkTyCon3
| @@ -36,6 +42,8 @@ import Data.Typeable ( Typeable1(..), Typeable2(..),
| mkTyConApp,
| mkTyCon
|  #endif
|   )
| +#endif
| +
|  import Data.Data ( Data(..) )
| 
|  #include vector.h
| @@ -53,7 +61,10 @@ class (G.Vector Vector a, M.MVector MVector a) =
| Unbox a
|  -- -
|  -- Data and Typeable
|  -- -
| -
| +#if __GLASGOW_HASKELL__ = 707
| +deriving instance Typeable Vector
| +deriving instance Typeable MVector
| +#else
|  #if MIN_VERSION_base(4,4,0)
|  vectorTyCon = mkTyCon3 vector
|  #else
| @@ -65,6 +76,7 @@ instance Typeable1 Vector where
| 
|  instance Typeable2 MVector where
|typeOf2 _ = mkTyConApp (vectorTyCon Data.Vector.Unboxed.Mutable
| MVector) []
| +#endif
| 
|  instance (Data a, Unbox a) = Data (Vector a) where
|gfoldl   = G.gfoldl
| 
| 
| 
| ___
| ghc-commits mailing list
| ghc-comm...@haskell.org
| http://www.haskell.org/mailman/listinfo/ghc-commits

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


Re: nofib regressions in HEAD since 7.6.2 release

2013-02-12 Thread Simon Marlow

On 12/02/13 03:17, Johan Tibell wrote:

Hi Nicolas!

I tried to reproduce the difference between 7.0.4 and 7.6.2 on the
exp3_8, wheel-sieve1, and primes and couldn't get the same percent
difference as you. We need to reconcile these differences somehow. Lets
start with more exact machine specs. I have a:


 Program   SizeAllocs   Runtime   Elapsed  TotalMem

  bernouilli  +3.3% +0.2%  0.12  0.13 +0.0%
  exp3_8  +1.1%+53.7%  0.14  0.14   +300.0%
 gen_regexps +18.7% +3.9%  0.00  0.00 +0.0%
   integrate  -0.1%+39.0%  0.21  0.23 +0.0%
   kahan  +1.7%+98.6% +9.9% +7.3% +0.0%
   paraffins  +1.3% -1.2%  0.06  0.08 +0.0%
  primes  +1.4%+64.7%  0.04  0.05+50.0%
  queens  +0.8% -0.5%  0.02  0.02 +0.0%
rfib  +1.7%+42.8%  0.02  0.02 +0.0%
 tak  +0.9%+12.0%  0.01  0.01 +0.0%
wheel-sieve1  +0.8%+66.6% -4.6% -5.8%-12.5%
wheel-sieve2  +0.9% +0.0%  0.12  0.13 +0.0%
x2n1 +10.3%+87.3%  0.00  0.01   +200.0%

 Min  -0.1% -1.2% -4.6% -5.8%-12.5%
 Max +18.7%+98.6% +9.9% +7.3%   +300.0%
  Geometric Mean  +3.2%+31.7% +2.4% +0.5%+23.6%


Some of these benchmarks essentially do no allocation in their inner 
loops (x2nl, rfib, tak), so differences there just indicate changes in 
the IO library or elsewhere, and aren't significant.


Is your 7.6.2 from our binary distributions, or did you build it yourself?

Cheers,
Simon


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


Re: Patch to time

2013-02-12 Thread José Pedro Magalhães
Hi Ashley,

Just to remind you of the patch to time I've previously sent you. Whenever
you can apply it,
we can remove the temporary fix patch on the GHC copy of the repo.


Thanks,
Pedro

On Wed, Nov 28, 2012 at 3:05 PM, José Pedro Magalhães j...@cs.uu.nl wrote:

 Hi Ashley,

 I'm attaching a patch to the time package to make it derive Typeable
 instances instead of defining them manually. GHC HEAD will soon ignore
 handwritten Typeable instances, so this replacement is necessary.


 Thanks,
 Pedro


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


Re: Missing change?

2013-02-12 Thread José Pedro Magalhães
Hi Simon,

I pushed to the wrong branch, but that should be fixed now. Does a
./sync-all pull solve it?


Cheers,
Pedro

On Tue, Feb 12, 2013 at 1:47 PM, Simon Peyton-Jones
simo...@microsoft.comwrote:

  Pedro: did you miss something?

 ** **

 This is breaking my build.

 ** **

 I have your last patch 12ba4321d34d646cf9040ad12810c4257d26ade9

 ** **

 Simon

 ** **

   url = http://darcs.haskell.org/libraries/time.git/

 ** **

 ** **

 libraries/time/Data/Time/Calendar/Days.hs:30:9:

 `typeOf' is not a (visible) method of class `Typeable'

 ** **

 libraries/time/Data/Time/Calendar/Days.hs:30:32:

 Not in scope: `mkTyCon'

 Perhaps you meant `mkTyCon3' (imported from Data.Data)

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


RE: Missing change?

2013-02-12 Thread Simon Peyton-Jones
NO... but I've just discovered that my 'time' link tree had some .hs files in 
it, NOT pointers to the source tree.  I have no clue why.

That turned out to be the problem.  Sorry for the noise

S

From: josepedromagalh...@gmail.com [mailto:josepedromagalh...@gmail.com] On 
Behalf Of José Pedro Magalhães
Sent: 12 February 2013 13:49
To: Simon Peyton-Jones
Cc: ghc-devs@haskell.org
Subject: Re: Missing change?

Hi Simon,

I pushed to the wrong branch, but that should be fixed now. Does a ./sync-all 
pull solve it?


Cheers,
Pedro
On Tue, Feb 12, 2013 at 1:47 PM, Simon Peyton-Jones 
simo...@microsoft.commailto:simo...@microsoft.com wrote:
Pedro: did you miss something?

This is breaking my build.

I have your last patch 12ba4321d34d646cf9040ad12810c4257d26ade9

Simon

  url = http://darcs.haskell.org/libraries/time.git/


libraries/time/Data/Time/Calendar/Days.hs:30:9:
`typeOf' is not a (visible) method of class `Typeable'

libraries/time/Data/Time/Calendar/Days.hs:30:32:
Not in scope: `mkTyCon'
Perhaps you meant `mkTyCon3' (imported from Data.Data)

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


Re: Patch to vector

2013-02-12 Thread shelarcy

Hi all,

I filed this to vector's trac.

  http://trac.haskell.org/vector/ticket/91


Thanks,

On Tue, 12 Feb 2013 22:12:02 +0900, José Pedro Magalhães j...@cs.uu.nl wrote:


Hi Roman,

Just to remind you of the patch to vector I've previously sent you.
Whenever you can apply it,
we can remove the temporary fix patch on the GHC copy of the repo.


Thanks,
Pedro

On Wed, Nov 28, 2012 at 3:03 PM, José Pedro Magalhães j...@cs.uu.nl wrote:


Hi Roman,

I'm attaching a patch to the vector package to make it derive Typeable
instances instead of defining them manually. GHC HEAD will soon ignore
handwritten Typeable instances, so this replacement is necessary.


Thanks,
Pedro


--
shelarcy shelarcyhotmail.co.jp
http://page.freett.com/shelarcy/

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


Re: [commit: ghc] master: Fix Trac #7681. (7b098b6)

2013-02-12 Thread Richard Eisenberg
I was working in a ghc tree that I thought was clean (i.e. was a checkout of 
HEAD), but evidently was not.

In my other work, I needed to update lookupType_mod, but wasn't sure how to. 
So, I looked for use sites. When I found none, I must have gone into this ghc 
tree, removed the exports, and checked to make sure everything compiled. There 
were no problems, and I guess I forgot to undo my test change. When fixing 
#7681, the exports were still missing, causing the warning and validate failure.

I'm happy to bring lookupType_mod back if it is expected to be needed somewhere.

Richard

On Feb 12, 2013, at 3:08 AM, Simon Peyton-Jones simo...@microsoft.com wrote:

 Thanks for fixing.
 
 You removed lookupType_mod from TrieMap.  It was defined and exported but not 
 called. How did validate spot that?   I'm sure there are quite a few such 
 functions in GHC.
 
 Simon
 
 | -Original Message-
 | From: ghc-commits-boun...@haskell.org [mailto:ghc-commits-
 | boun...@haskell.org] On Behalf Of Richard Eisenberg
 | Sent: 12 February 2013 04:10
 | To: ghc-comm...@haskell.org
 | Subject: [commit: ghc] master: Fix Trac #7681. (7b098b6)
 | 
 | Repository : ssh://darcs.haskell.org//srv/darcs/ghc
 | 
 | On branch  : master
 | 
 | http://hackage.haskell.org/trac/ghc/changeset/7b098b6009727a012cb1f3ff0c
 | a51698d302cae1
 | 
 | ---
 | 
 | commit 7b098b6009727a012cb1f3ff0ca51698d302cae1
 | Author: Richard Eisenberg e...@cis.upenn.edu
 | Date:   Mon Feb 11 23:07:25 2013 -0500
 | 
 | Fix Trac #7681.
 | 
 | Removed checks for empty lists for case expressions and lambda-case.
 | If -XEmptyCase is not enabled, compilation still fails
 | (appropriately)
 | in the renamer.
 | 
 | Had to remove dead code from TrieMap to pass the validator.
 | 
 | ---
 | 
 |  compiler/coreSyn/TrieMap.lhs |   38 +--
 | ---
 |  compiler/deSugar/DsMeta.hs   |6 --
 |  compiler/hsSyn/Convert.lhs   |8 ++--
 |  libraries/random |2 +-
 |  4 files changed, 8 insertions(+), 46 deletions(-)
 | 
 | diff --git a/compiler/coreSyn/TrieMap.lhs b/compiler/coreSyn/TrieMap.lhs
 | index 148464b..c013b5d 100644
 | --- a/compiler/coreSyn/TrieMap.lhs
 | +++ b/compiler/coreSyn/TrieMap.lhs
 | @@ -14,7 +14,7 @@
 |  {-# LANGUAGE TypeFamilies #-}
 |  module TrieMap(
 | CoreMap, emptyCoreMap, extendCoreMap, lookupCoreMap, foldCoreMap,
 | -   TypeMap, foldTypeMap, lookupTypeMap_mod,
 | +   TypeMap, foldTypeMap, -- lookupTypeMap_mod,
 | CoercionMap,
 | MaybeMap,
 | ListMap,
 | @@ -32,8 +32,6 @@ import UniqFM
 |  import Unique( Unique )
 |  import FastString(FastString)
 | 
 | -import Unify ( niFixTvSubst )
 | -
 |  import qualified Data.Mapas Map
 |  import qualified Data.IntMap as IntMap
 |  import VarEnv
 | @@ -632,40 +630,6 @@ lkT env ty m
 |  go (ForAllTy tv ty)  = tm_forall . lkT (extendCME env tv) ty =
 | lkBndr env tv
 | 
 | 
 | -lkT_mod :: CmEnv
 | -- TyVarEnv Type -- TvSubstEnv
 | -- Type
 | -- TypeMap b - Maybe b
 | -lkT_mod env s ty m
 | -  | EmptyTM - m = Nothing
 | -  | Just ty' - coreView ty
 | -  = lkT_mod env s ty' m
 | -  | [] - candidates
 | -  = go env s ty m
 | -  | otherwise
 | -  = Just $ snd (head candidates) -- Yikes!
 | -  where
 | - -- Hopefully intersects is much smaller than traversing the whole
 | vm_fvar
 | -intersects = eltsUFM $
 | - intersectUFM_C (,) s (vm_fvar $ tm_var m)
 | -candidates = [ (u,ct) | (u,ct) - intersects
 | -  , Type.substTy (niFixTvSubst s) u `eqType` ty
 | ]
 | -
 | -go env _s (TyVarTy v)  = tm_var. lkVar env v
 | -go env s (AppTy t1 t2) = tm_app. lkT_mod env s t1 =
 | lkT_mod env s t2
 | -go env s (FunTy t1 t2) = tm_fun. lkT_mod env s t1 =
 | lkT_mod env s t2
 | -go env s (TyConApp tc tys) = tm_tc_app . lkNamed tc = lkList
 | (lkT_mod env s) tys
 | -go _env _s (LitTy l)   = tm_tylit  . lkTyLit l
 | -go _env _s (ForAllTy _tv _ty) = const Nothing
 | -
 | -{- DV TODO: Add proper lookup for ForAll -}
 | -
 | -lookupTypeMap_mod :: TyVarEnv a -- A substitution to be applied to the
 | /keys/ of type map
 | -  - (a - Type)
 | -  - Type
 | -  - TypeMap b - Maybe b
 | -lookupTypeMap_mod s f = lkT_mod emptyCME (mapVarEnv f s)
 | -
 |  -
 |  xtT :: CmEnv - Type - XT a - TypeMap a - TypeMap a  xtT env ty f m
 | diff --git a/compiler/deSugar/DsMeta.hs b/compiler/deSugar/DsMeta.hs
 | index 9a9f89d..4f5ba2d 100644
 | --- a/compiler/deSugar/DsMeta.hs
 | +++ b/compiler/deSugar/DsMeta.hs
 | @@ -920,7 +920,8 @@ repE (HsLit l) = do { a - repLiteral l;
 | repLit a }
 |  repE (HsLam (MG { mg_alts = [m] })) = repLambda m  repE (HsLamCase _
 | (MG { mg_alts = ms }))
 | = do { ms' - mapM repMatchTup ms
 

RE: Changes to help GHCJS, GHC API multi-target cross compile

2013-02-12 Thread Simon Peyton-Jones
I've had a look.  As you say, the changes are modest.

For (2), I'd like to see a 

Note [Overriding the GHC.Prim interface]


with the field decl for sOverridePrimIface in DynFlags, with enough commentary
to explain what is going on.

In particular, this DynFlag field is never altered from the command line flags 
etc; it is only used via the GHC API.  This point needs to be made so that we 
don't remove it again as dead code!


Similarly (1): a Note with the CustomWay constructor

Then I'm happy for Ian to commit, if Ian is happy too.

Simon

| -Original Message-
| From: ghc-devs-boun...@haskell.org [mailto:ghc-devs-boun...@haskell.org]
| On Behalf Of Luite Stegeman
| Sent: 08 February 2013 18:53
| To: ghc-devs@haskell.org
| Subject: RFC: Changes to help GHCJS, GHC API multi-target cross compile
| 
| Hi all,
| 
| I'm looking for comments on two minor patches that would greatly help
| GHCJS [1]. The goal is to make a cabal-installable GHCJS compiler that
| uses the GHC API to generate both JavaScript (always 32 bit) and native
| code (to run Template Haskell). This way we can release updates
| frequently and have an easy installation procedure for users.
| 
| I have an experimental branch [2] that uses the patches below to make
| working compiler that can generate 32 bit JavaScript from a 64 bit host
| compiler, with working TH.
| 
| 1. Add a Way for custom build tags.
| Since we generate code for two architectures, we need to make sure that
| we don't mix the native and JavaScript .hi files. Setting the buildTag
| manually in DynFlags does not work, because it gets reset every time a
| file is preprocessed (due to OPTIONS pragma handling).
| This patch adds an extra Way that just adds something to the build tag,
| it could be extended to also add custom program options and extras.
| 
| 2. Make GHC.Prim interface overridable.
| Since JavaScript does not support 64 bit integers, we want to generate
| 32 bit code, even if our host platform is 64 bit. HEAD has
| wORD_SIZE_IN_BITS already configurable though DynFlags, but
| unfortunately the primop interface (GHC.Prim) is also platform
| dependent, some primops have a different type on a 64 bit system.
| 
| This patch makes it possible for a GHC API user to supply a custom
| interface for GHC.Prim. It's rather hacky, requires an extra hs-boot
| file and requires the user to mess with the NameCache to make it work
| correctly [3]. Probably a stopgap measure until GHC supports multitarget
| cross compilation out of the box. Is there a better way of doing this?
| 
| Luite
| 
| [1] https://github.com/ghcjs
| [2] https://github.com/ghcjs/ghcjs/tree/gen2-64
| [3]
| https://github.com/ghcjs/ghcjs/blob/1a84f82fa149b4e9510586c10864694efe78
| 20bf/src-bin/Compiler/Main.hs#L544

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


Re: GHC 7.8 release?

2013-02-12 Thread Sergei Trofimovich

 Thanks for sharing! My perspective is of course as a user. I don't think
 I've ever run into a case where the compiler broken a previous work e.g.
 C++ program. On the other hand I have to make a release of most of the
 libraries I maintain with every GHC release (to bump cabal version
 constraints to accept the new base version, if nothing else).

Just don't set upper version of base on the packages when you are not sure
they will break. Write tested ghc versions in comments instead.
You can't install separate base for a given ghc, so why bother?

According to PVP you need to use 'base  4.7' in version,
BUT IT IS INSANE

How do you expect users to test new ghc release (preview, name it
any way), if you require them to unpack every nonresolvable package
and update depends by hands?

It's very fun to check -HEAD version for fixed bugs in that respect.
Luckily many devs are not that insane and use arbitrary 'base  5' or
'base  10', which will break randomly at an arbitrary base-5 release.

-- 

  Sergei


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


Re: RFC: Singleton equality witnesses

2013-02-12 Thread Iavor Diatchki
Hi Richard,

Thanks for pushing on this!   The summary of my comments is this:  I think
that we should have 1 or 2 low-level (not necessarily safe) GHC modules
that contain all the bits that GHC needs to know about, and move all other
bits into a separate library, which is to be used by the actual users of
the system.  In this way, this library could evolve independently of GHC
releases.

Here are some more detailed comments:

On Mon, Feb 11, 2013 at 6:40 PM, Richard Eisenberg e...@cis.upenn.edu
 wrote:

 I've just pushed a commit to the type-reasoning branch with a strawman
 proposal of a reorganization of these definitions. Specifically, this
 commit breaks TypeLits into the following five files:

 - GHC.TypeEq, which contains the definitions for (:~:), Void, Refuted, etc.
 - GHC.Singletons, which contains the definitions about singletons in
 general, such as SingI and SingEquality
 - GHC.TypeLits.Unsafe, which contains just unsafeSingNat and
 unsafeSingSymbol
 - GHC.TypeLits.Internals, which is necessary to get GHC.TypeLits.Unsafe to
 have access to the right internals;
 this module is not exported from the 'base' package
 and
 - GHC.TypeLits, which contains the definitions specific to type-level
 literals.

 Like Simon, I think that there is no need to distinguish between
TypeList.Unsafe and TypeLits.Internals.

Some thoughts on this design:
 - First off, why is TypeEq part of GHC?? Because we wish to write
 eqSingNat and eqSingSym in GHC.TypeLits, and that module rightly deserves
 to be part of GHC. I'm quite uncomfortable with this decision, and I even
 created a new git repo at github.com/goldfirere/type-reasoning to hold
 the definitions that eventually ended up in GHC.TypeEq. (The repo has
 nothing in it, now.) Perhaps the best resolution is to move eqSingNat and
 eqSingSym out of GHC.TypeLits and into an external package, but that seems
 silly in a different direction. (It is fully technically feasible, as those
 functions don't depend on any internals.) I would love some feedback here.


We could move these out of GHC: they are just defined using (a safe use of)
`unsafeCoerce`.  They just need to know about the equality type (:~:), so I
think they should be defined wherever the equality type is defined.

Also, an unrelated piece of advice:  try to keep down the use of type
synonyms---they make libraries seem complex.  For example, most programmers
would understand the type 'a - Void', but when I see `Refuted a` I have to
go lookup its definition and check if there is something special about it.


 - Why is Singletons broken off? No strong reason here, but it seemed that
 the singletons-oriented definitions weren't solely related to type-level
 literals, so it seemed more natural this way.


I don't think this matters too much either way, but I would look for things
to remove from here and move to the programmer facing library.  For
example, why should `SingEquality` be there?  It is important for `SingI`
to be in GHC, because the instances for type-level literals are wired into
GHC: it expects the class to be in GHC.TypeLits (this is why moving the
class broke the instances, take a look in
`compiler/prelude/TysWiredIn.lhs`, indeed, `Nat` and `Symbol` are also
wired into GHC in the same module).


 - Making the Unsafe module was a little more principled, because those
 functions really are unsafe! They are quite useful, though, and should be
 available somewhere.


Yes, I think that we want to export these at least for the use by the
programmer facing library---it may choose not to re-export them.

-Iavor



On Tue, Feb 12, 2013 at 12:38 AM, Simon Peyton-Jones
simo...@microsoft.comwrote:

  - Currently, the internals of GHC assign types like 0 the kind
 GHC.TypeLits.Nat, so Nat and Symbol *must* remain in the GHC.TypeLits
 module. Unfortunately, the plumbing around GHC.TypeLits.Unsafe want Nat and
 Symbol to be defined in GHC.TypeLits.Internals. So, I created a
 TypeLits.hs-boot file to fix the problem. This is highly unsatisfactory,
 and if something like what I've done here sticks around, we should change
 the internals of GHC to use GHC.TypeLits.Internals.Nat, getting rid of the
 import cycle.

 ** **

 Let’s NOT have an hs-boot file here.  Instead, change PrelNames to tell
 GHC where Nat and Symbol are defined.  It’s ok for them to be in Internals.
 

 ** **

 I’m also unconvinced about the distinction between “Internals” and
 “Unsafe”.  To me the former connotes the latter.  Import Internals if you
 know what you are doing; eg that might let you break important invariants.
 Import a kosher module like TypeLits if you want the Joe Programmer
 interface.

 ** **

 Simon

 ** **



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


Re: Heads-up: new parallel I/O manager merged

2013-02-12 Thread 山本和彦
Hi all,

 I've merged the new parallel I/O manager that Andreas Voellmy and Kazu
 Yamamoto have been working on. The new parallel I/O manager scales much better
 than the current one*: the number of requests per second scales almost
 linearly up to 32 cores I believe. Perhaps Andreas could post the numbers.

Just after Johan's merge, I could build GHC on Mac. But after executing
./sync-all -r git://github.com/ghc --testsuite pull
today, I cannot build GHC on Mac:


ghc-stage1: could not execute: /usr/bin/gcc
make[1]: *** 
[libraries/template-haskell/dist-install/build/Language/Haskell/TH/Syntax.o] 
Error 1
make[1]: *** Waiting for unfinished jobs
make: *** [all] Error 2


I would like to know whether or not this failure is due to our
patches. Since building GHC with our patches were unstable on Mac, we
made a workaround. Andreas and I need to know that this workaround is
stable enough:


https://github.com/ghc/packages-base/commit/bcf8724642f3cec73587313878047c87fd61e18f

https://github.com/ghc/packages-base/commit/51a8b9bb878247675b6e003fa081f1a22b2ae420
http://hackage.haskell.org/trac/ghc/ticket/7651

Any information is welcome.

Building GHC on FreeBSD is fine.

--Kazu

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


Vector primops sizes

2013-02-12 Thread Michael Baikov
Recently merged vector primops support only 16 bytes operands - Int32
x 4, Double x 2 and so on. Current AVX instructions support 256 bit
operands and with simple cut'n'paste work it's possible to support at
least Double x 4 operands. I made those changes and GHC generates
(using llvm) proper AVX code using ymm registers. Also it might make
sense to support primops for vector types larger than any currently
supported primitive types - I have those changes in my branch as well
and llvm generates pretty good code as well - those changes might be
useful to provide access for llvm shufflevector instruction or writing
high performance processing of large vectors - with less potential
overhead.

Do we want to support larger vectors directly or ghc should be made
smart enough to fuse operations with vector primops performed in
parallel into larger vectors/registers for llvm? Do we want to provide
access to llvm shufflevector instruction?

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


Re: Vector primops sizes

2013-02-12 Thread Carter Schonwald
Yes please! having these  (for valid target arches/ CPU targets) would be
really really valuable for me.

On Feb 13, 2013 12:07 AM, Michael Baikov manpac...@gmail.com wrote:

 Recently merged vector primops support only 16 bytes operands - Int32
 x 4, Double x 2 and so on. Current AVX instructions support 256 bit
 operands and with simple cut'n'paste work it's possible to support at
 least Double x 4 operands. I made those changes and GHC generates
 (using llvm) proper AVX code using ymm registers. Also it might make
 sense to support primops for vector types larger than any currently
 supported primitive types - I have those changes in my branch as well
 and llvm generates pretty good code as well - those changes might be
 useful to provide access for llvm shufflevector instruction or writing
 high performance processing of large vectors - with less potential
 overhead.

 Do we want to support larger vectors directly or ghc should be made
 smart enough to fuse operations with vector primops performed in
 parallel into larger vectors/registers for llvm? Do we want to provide
 access to llvm shufflevector instruction?

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