Re: [Haskell-cafe] ANN: psqueue-benchmarks - benchmarks of priority queue implementations

2013-03-29 Thread Scott Dillard
I do not know why it overflows. It's been a while, but isn't the answer
usually "too much laziness"? Maybe try changing the foldr in fromList to
foldr'? I would try it out quickly but do not have ghc installed on any
computers here.

I am happy start a repo for this library, but there is not much history to
import so anyone else may do it. I'm not sure how hackage upload
permissions work... I guess I just change the maintainer field in the
.cabal file from myself to someone else...? Any volunteers?




On Thu, Mar 28, 2013 at 11:16 PM, Kazu Yamamoto  wrote:

> Hi Niklas,
>
> > * PSQueue throws a stack space overflow if you try to put in 10
> > * Ints
>
> A slightly different implementation is used in GHC:
>
> https://github.com/ghc/packages-base/blob/master/GHC/Event/PSQ.hs
>
> Could you test it? If this code also has the same problem, I need to
> fix it.
>
> --Kazu
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Unboxed array of product type -> product type of unboxed arrays

2008-07-02 Thread Scott Dillard
On Wed, Jul 2, 2008 at 11:52 AM, Daniel Fischer <[EMAIL PROTECTED]>
wrote:

>
> Perhaps
>
> class (Ix i) => UArrClass i e where ...
>
> would work?
>
>
class Ix i => UArrClass i e where
  data UArr i e
  unsafeAt_ :: UArr i e -> Int -> e

instance
( IArray UArray e
, IArray UArray f
, Ix i
) => UArrClass i (e,f)
  where
newtype UArr i (e,f) = UArrPair (UArray i e) (UArray i f)
unsafeAt_ (UArrPair ea fa) i = (unsafeAt ea i , unsafeAt fa i)

instance
( IArray UArray e
, IArray UArray f
, UArrClass i (e,f)
, Ix i
) => IArray UArr (e,f)
  where
unsafeAt = unsafeAt_

test1 :: UArr Int (Int,Int) -> (Int,Int)
test1 a = unsafeAt a 5   --this is line 77


Array.hs:77:10:
Ambiguous type variable `i' in the constraint:
  `Ix i' arising from a use of `unsafeAt' at Array.hs:77:10-21
Probable fix: add a type signature that fixes these type variable(s)

I think the 'i' there is the one from the method context of IArray,

class IArray a e where
   unsafeAt :: Ix i => a i e -> Int -> e

But that 'i' does not escape to the class context, so I have no way to
address it. I think I need to leave it free, but I can't do that with my
associated type.

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


[Haskell-cafe] Unboxed array of product type -> product type of unboxed arrays

2008-07-02 Thread Scott Dillard
Hi,

I'm trying to extended the standard unboxed array types and array classes to
my own product types, for now let's just say (,). So if the proper MArray
and IArray instances exist for e and f, then I can make an instance for
(e,f). The actual type of that array, something like (UArray i e, UArray i
f), would be given by an associated type. This is how the uvector library
does it, but that library defines its own array primitives and classes. I'd
like to reuse the standard ones if possible.

The problem I keep running into is the kind of the array, * -> * -> *, or 'a
i e'. The crucial type there is e, which is used to dispatch the instance to
the proper associated type, so if e = (a,b) then the array type would be
(UArray i a, UArray I b), and if e is (a,b,c) then (UArray i a, UArray i b,
UArray i c). If IArray was instead expecting the array type to be 'a e i' I
could maybe do something like this:

class UArrClass e where
  data UArr e :: * -> *
instance (IArray UArray e, IArray UArray f) => UArrClass (e,f) where
  data UArr (e,f) i = UArrPair (UArray i e) (UArray i f)

But as it stands, I can't do that. The 'i' type parameter has to be bound as
a parameter of UArrClass. So instead I tried this.

class UArrClass i e where
  data UArr i e
  unsafeAt_ :: UArr i e -> Int -> e
  --mirror all IArray methods

instance
( IArray UArray e
, IArray UArray f
, Ix i  --needed for unsafeAt
) => UArrClass i (e,f)
  where
newtype UArr i (e,f) = UArrPair (UArray i e) (UArray i f)
unsafeAt_ (UArrPair ea fa) i = (unsafeAt ea i , unsafeAt fa i)

and then the instance for IArray could be defined as follows, just a mapping
from the methods of that class onto my own:

instance
( IArray UArray e
, IArray UArray f
, UArrClass i (e,f)
) => IArray UArr (e,f)
  where
unsafeAt = unsafeAt_

The problem I get now is from the 'Ix i' context of the IArray methods. The
'i' there is only mentioned in the context of the methods, not the class, so
I have no 'handle' onto that 'i' that I can use to explicitly unify it with
the 'i' mentioned in UArrClass. The compiler keeps complaining about rigid
type variables. It would be great if I could leave that type variable
unbound in my class, and only bind it in the methods, as IArray does, but as
far as I can tell, I can't. I need to bind 'i' in my class because it's the
first type-argument to the array type constructor, rather than the second. I
don't care about the 'i', its the 'e' I'm after, but all applications of the
associated type constructor need to be saturated.

Can anyone see a way to do this? I understand there's about a million other
ways to accomplish what I'm trying to do without IArray and MArray, but I'm
just wondering if I should abandon those classes altogether, and use my own
array classes, using something like uvector or unsafeIO/ForeignPtr. That
seems to be trend.

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