Re: Boxed foreign prim

2012-03-13 Thread Simon Marlow

On 12/03/2012 14:22, Edward Kmett wrote:

On Mon, Mar 12, 2012 at 6:45 AM, Simon Marlow marlo...@gmail.com
mailto:marlo...@gmail.com wrote:

But I can only pass unboxed types to foreign prim.

Is this an intrinsic limitation or just an artifact of the use cases
that have presented themselves to date?


It's an intrinsic limitation - the I# box is handled entirely at the
Haskell level, primitives only deal with primitive types.


Ah. I was reasoning by comparison to atomicModifyMutVar#, which deals
with unboxed polymorphic types, and even lies with a too general return
type. Though the result there is returned in an unboxed tuple, the
argument is passed unboxed.

Is that implemented specially?


I'm a little bit confused.

atomicModifyMutVar#
   :: MutVar# s a - (a - b) - State# s - (# State# s, c #)

Is the unboxed polymorphic type you're referring to the MutVar# s a? 
 Perhaps the confusion is around the term unboxed - we normally say 
that MutVar# is unlifted (no _|_), but it is not unboxed because its 
representation is a pointer to a heap object.



But anyway, I suspect your first definition of unsafeIndex will be
faster than the one using foreign import prim, because calling
out-of-line to do the indexing is slow.


Sure though, I suppose that balance of may shift as the side of the
short vector grows. (e.g. with Johan it'd probably be 16 items).

Also pseq is slow - use seq instead.


Of course. I was being paranoid at the time and trying to get it to work
at all. ;)

what you really want is built-in support for unsafeField#, which is
certainly do-able.  It's very similar to dataToTag# in the way that
the argument is required to be evaluated - this is the main
fragility, unfortunately GHC doesn't have a way to talk about things
that are unlifted (except for the primitive unlifted types).  But it
just about works if you make sure there's a seq in the right place.


I'd be happy even if I had to seq the argument myself before applying
it, as I was trying above.


The problem is, that can't be done reliably.  For dataToTag# the 
compiler automatically inserts the seq just before code generation if it 
can't prove that the argument is already evaluated, I think we would 
want to do the same thing for unsafeField#.


See CorePrep.saturateDataToTag in the GHC sources.

Cheers,
Simon

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


Re: Boxed foreign prim

2012-03-13 Thread Edward Kmett
On Tue, Mar 13, 2012 at 4:57 AM, Simon Marlow marlo...@gmail.com wrote:

 On 12/03/2012 14:22, Edward Kmett wrote:

 On Mon, Mar 12, 2012 at 6:45 AM, Simon Marlow marlo...@gmail.com
 mailto:marlo...@gmail.com wrote:
But I can only pass unboxed types to foreign prim.

Is this an intrinsic limitation or just an artifact of the use
 cases
that have presented themselves to date?

It's an intrinsic limitation - the I# box is handled entirely at the
Haskell level, primitives only deal with primitive types.

 Ah. I was reasoning by comparison to atomicModifyMutVar#, which deals
 with unboxed polymorphic types, and even lies with a too general return
 type. Though the result there is returned in an unboxed tuple, the
 argument is passed unboxed.

 Is that implemented specially?


 I'm a little bit confused.

 atomicModifyMutVar#
   :: MutVar# s a - (a - b) - State# s - (# State# s, c #)



 Is the unboxed polymorphic type you're referring to the MutVar# s a?
  Perhaps the confusion is around the term unboxed - we normally say that
 MutVar# is unlifted (no _|_), but it is not unboxed because its
 representation is a pointer to a heap object.


I was talking about the (a - b). I used it because the extraction of 'c'
rather than a proper pair was closest to my situation. A less confused
example might be newArray# which accepts a polymorphic 'a'.


 The problem is, that can't be done reliably.  For dataToTag# the compiler
 automatically inserts the seq just before code generation if it can't prove
 that the argument is already evaluated, I think we would want to do the
 same thing for unsafeField#.


Fair enough.

Thanks again.

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


Bug with unicode characters in file names

2012-03-13 Thread Volker Wysk
Hi

This is some file äöü.hs with three German umlauts in the file name:

   main = putStrLn äöü

Now I want to get the dependendency information. Therefore I call:

   ghc -M äöü.hs

The following gets added to the Makefile:

   # DO NOT DELETE: Beginning of Haskell dependencies
   äöü.o : äöü.hs
   # DO NOT DELETE: End of Haskell dependencies

The umlauts get transformed from three UTF-8 encoded characters (six bytes) to 
six UTF-8 encoded characters (twelve bytes).


I'm sending this to glasgow-haskell-users instead of glasgow-haskell-bugs, 
because the latter does not seem to accept my messages. I receive nothing, 
neither the message in the mailing list, nor any error message.

Bye,
V.W.

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


packaged up polykinded types can't index type families?

2012-03-13 Thread Nicolas Frisby
I suspect I'm tripping on a gap in the PolyKinds support. I'm trying
to package up a type-level generic view. It uses PolyKinds — and
DataKinds, but I think it's the PolyKinds that matter. If I compile
everything locally in the same build, it works fine. If I isolate the
spine view declarations in their own package, I get type errors.

A quick search turned up this omnibus, which I'm guessing might fix my problem.

  
http://hackage.haskell.org/trac/ghc/changeset/3bf54e78cfd4b94756e3f21c00ae187f80c3341d

I was hoping someone might be able to identify if that's the case. I
can wait for 7.6.1 if I must, but I was wondering if there's a
workaround.

(If I avoid PolyKinds, it works. But I have to simulate PolyKinds for
a finite set of kinds, which is pretty obfuscating and not general. If
you're curious, checkout the type-spine package. This whole email
regards my trying to generalize and simplify that package with
PolyKinds.)

In a distillation of my use case, we have two modules. The first is
the type-level spine view.

 {-# LANGUAGE TypeFamilies, PolyKinds, DataKinds, TypeOperators,
   UndecidableInstances, TemplateHaskell, EmptyDataDecls #-}
 module Spine where

 type family Spine a :: *

 data Atom n -- represents a totally unapplied type name
 data f :@ a -- |represents a type-level application

 -- this is an unsaturated instance, which might be a no-no, but
 -- at least isn't obviously causing the current problem
 type instance Spine (f a) = f :@ a

 -- all other instances are for unapplied types names:
 -  e.g.   type instance Spine N = Atom N
 spineType :: Name - Q [Dec]
 spineType n = let t = conT n in
   (:[]) `fmap` tySynInstD ''Spine [t] [t| Atom $t |]

The second module is a distilled use case.

 {-# LANGUAGE TypeFamilies, PolyKinds, DataKinds, TypeOperators, 
 TemplateHaskell #-}

 module Test where

 import Spine -- our first module above

 type family IsApp (a :: *) :: Bool
 type instance IsApp (Atom n) = False
 type instance IsApp (a :@ b) = True

 -- example types and use
 data A = A
 data F a = F a

 concat `fmap` mapM spineType [''A, ''F]

 isApp :: (True ~ IsApp (Spine a)) = a - ()
 isApp _ = ()

 test :: ()
 test = isApp (F A)

If Spine.hs and Test.hs are in the same directory and I load Test in
ghci, it type-checks fine. If I instead use cabal to install Spine as
its own package, the subsequent type-checking of Test.test fails with:

 Couldn't match type `IsApp ((:@) (* - *) * F A)' with `'True'

The :bro Spine command returns the same information regardless of how
Test imports Spine.

 *Test :bro Spine
 type family Spine k a :: *
 data Atom k n
 data (:@) k k f a
 spineType :: ...snip...

Why can IsApp (... :@ ...) reduce if Spine was locally compiled but
not if it's pulled from a package? Is there some crucial info that the
package interfaces can't yet express? Is there an open bug for this?

Thanks for your time,
Nick

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


RE: packaged up polykinded types can't index type families?

2012-03-13 Thread Simon Peyton-Jones
I'm afraid that PolyKinds is not an advertised feature of 7.4.1, and we won't 
fix bugs in it.  The flag exists because we were working on it before releasing 
7.4, but it was too far from completion to support.  We knew there were many 
bugs, but did not want to hold up 7.4 for them.  (Otherwise we'd never make a 
release!)  

Bug reports are very valuable though, so keep them coming.  Nicolas, happily 
your program works just fine with HEAD.  (If you don't want to compile from 
source, grab a binary snapshot.)

PolyKinds *will* be a feature in 7.6, and I believe that they are fully working 
right now.  So beat on HEAD!

Simon

|  -Original Message-
|  From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-
|  boun...@haskell.org] On Behalf Of Nicolas Frisby
|  Sent: 13 March 2012 19:18
|  To: glasgow-haskell-users
|  Subject: packaged up polykinded types can't index type families?
|  
|  I suspect I'm tripping on a gap in the PolyKinds support. I'm trying
|  to package up a type-level generic view. It uses PolyKinds - and
|  DataKinds, but I think it's the PolyKinds that matter. If I compile
|  everything locally in the same build, it works fine. If I isolate the
|  spine view declarations in their own package, I get type errors.
|  
|  A quick search turned up this omnibus, which I'm guessing might fix my 
problem.
|  
|  
|  http://hackage.haskell.org/trac/ghc/changeset/3bf54e78cfd4b94756e3f21c00ae1
|  87f80c3341d
|  
|  I was hoping someone might be able to identify if that's the case. I
|  can wait for 7.6.1 if I must, but I was wondering if there's a
|  workaround.
|  
|  (If I avoid PolyKinds, it works. But I have to simulate PolyKinds for
|  a finite set of kinds, which is pretty obfuscating and not general. If
|  you're curious, checkout the type-spine package. This whole email
|  regards my trying to generalize and simplify that package with
|  PolyKinds.)
|  
|  In a distillation of my use case, we have two modules. The first is
|  the type-level spine view.
|  
|   {-# LANGUAGE TypeFamilies, PolyKinds, DataKinds, TypeOperators,
| UndecidableInstances, TemplateHaskell, EmptyDataDecls #-}
|   module Spine where
|  
|   type family Spine a :: *
|  
|   data Atom n -- represents a totally unapplied type name
|   data f :@ a -- |represents a type-level application
|  
|   -- this is an unsaturated instance, which might be a no-no, but
|   -- at least isn't obviously causing the current problem
|   type instance Spine (f a) = f :@ a
|  
|   -- all other instances are for unapplied types names:
|   -  e.g.   type instance Spine N = Atom N
|   spineType :: Name - Q [Dec]
|   spineType n = let t = conT n in
| (:[]) `fmap` tySynInstD ''Spine [t] [t| Atom $t |]
|  
|  The second module is a distilled use case.
|  
|   {-# LANGUAGE TypeFamilies, PolyKinds, DataKinds, TypeOperators,
|  TemplateHaskell #-}
|  
|   module Test where
|  
|   import Spine -- our first module above
|  
|   type family IsApp (a :: *) :: Bool
|   type instance IsApp (Atom n) = False
|   type instance IsApp (a :@ b) = True
|  
|   -- example types and use
|   data A = A
|   data F a = F a
|  
|   concat `fmap` mapM spineType [''A, ''F]
|  
|   isApp :: (True ~ IsApp (Spine a)) = a - ()
|   isApp _ = ()
|  
|   test :: ()
|   test = isApp (F A)
|  
|  If Spine.hs and Test.hs are in the same directory and I load Test in
|  ghci, it type-checks fine. If I instead use cabal to install Spine as
|  its own package, the subsequent type-checking of Test.test fails with:
|  
|   Couldn't match type `IsApp ((:@) (* - *) * F A)' with `'True'
|  
|  The :bro Spine command returns the same information regardless of how
|  Test imports Spine.
|  
|   *Test :bro Spine
|   type family Spine k a :: *
|   data Atom k n
|   data (:@) k k f a
|   spineType :: ...snip...
|  
|  Why can IsApp (... :@ ...) reduce if Spine was locally compiled but
|  not if it's pulled from a package? Is there some crucial info that the
|  package interfaces can't yet express? Is there an open bug for this?
|  
|  Thanks for your time,
|  Nick
|  
|  ___
|  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


profiling and backtracing blues

2012-03-13 Thread Ranjit Jhala
Hi all, 

I'm trying to use the nifty backtracing mechanism in GHC 74.
AFAICT, this requires everything be built with profiling on), 
but as a consequence, I hit this:

You can't call hscCompileCoreExpr in a profiled compiler

Any hints on whether there are work-arounds?

Thanks!

Ranjit.



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


Re: Bug with unicode characters in file names

2012-03-13 Thread Brent Yorgey
On Tue, Mar 13, 2012 at 06:06:49PM +0100, Volker Wysk wrote:
 
 I'm sending this to glasgow-haskell-users instead of glasgow-haskell-bugs, 
 because the latter does not seem to accept my messages. I receive nothing, 
 neither the message in the mailing list, nor any error message.

As I understand it, the glasgow-haskell-bugs list is for receiving
information about bugs, not for reporting them.  Information on how to
report bugs can be found here:

http://hackage.haskell.org/trac/ghc/wiki/ReportABug

-Brent

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