Re: match_co: needs more cases

2013-11-07 Thread Evan Laforge
On Thu, Nov 7, 2013 at 4:20 PM, Carter Schonwald
 wrote:
> specialize only fires on functions that have type class constraints / are
> part of a type class.  Furthermore, the function needs to be marked
> INLINEABLE or INLINE for specialization to work (unless the specialize
> pragma was written in the defining module)

Right, and I added it because I wanted to get rid of both the
Vector.Generic typeclass, and the Unboxed typeclass, and it worked.  I
guess that's why I added INLINEABLEs too, I probably read about it in
the documentation and then forgot.  But if crockeea is right and it's
no longer happening, that would be unfortunate.

I wonder if you could write a kind of query language for core, to ask
things like "are the arguments to this function unboxed?" or "how many
list constructors are called here" (e.g. to check for fusion).

> not sure if that helps,

It does, thanks!
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: match_co: needs more cases

2013-11-07 Thread Carter Schonwald
specialize only fires on functions that have type class constraints / are
part of a type class.  Furthermore, the function needs to be marked
INLINEABLE or INLINE for specialization to work (unless the specialize
pragma was written in the defining module)

not sure if that helps,

cheers
-Carter


On Thu, Nov 7, 2013 at 7:17 PM, Evan Laforge  wrote:

> On Thu, Nov 7, 2013 at 11:11 AM, crockeea  wrote:
> > I got this error with a small example, so I thought I'd post it for you.
> I
> > could only get it to work when split over two files.
>
> Mine is similar, sorry I've been lazy about getting a small
> reproduction, I assumed it wasn't too important.
>
> I have a generic library that uses Data.Vector.Generic, along with a
> bunch of SPECIALIZE and INLINEABLE for a particular monomorphic
> Unboxed use.  I don't know about the INLINEABLE, but the SPECIALIZE
> does wonders for performance, otherwise it doesn't notice that the
> operation can be unboxed.
>
> So it's a bit worrisome to me if the SPECIALIZEs aren't firing.  I did
> profiling before and they made my vector operations fall off of the
> expensive list, but that was before upgrading ghc and getting the new
> error msgs.
>
> Would it be useful for me to boil down my example too, or is this one
> enough to work on?  Mine is simpler in that it specializes to a
> monomorphic Storable.Vector Double.
> ___
> 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


Re: match_co: needs more cases

2013-11-07 Thread Evan Laforge
On Thu, Nov 7, 2013 at 11:11 AM, crockeea  wrote:
> I got this error with a small example, so I thought I'd post it for you. I
> could only get it to work when split over two files.

Mine is similar, sorry I've been lazy about getting a small
reproduction, I assumed it wasn't too important.

I have a generic library that uses Data.Vector.Generic, along with a
bunch of SPECIALIZE and INLINEABLE for a particular monomorphic
Unboxed use.  I don't know about the INLINEABLE, but the SPECIALIZE
does wonders for performance, otherwise it doesn't notice that the
operation can be unboxed.

So it's a bit worrisome to me if the SPECIALIZEs aren't firing.  I did
profiling before and they made my vector operations fall off of the
expensive list, but that was before upgrading ghc and getting the new
error msgs.

Would it be useful for me to boil down my example too, or is this one
enough to work on?  Mine is simpler in that it specializes to a
monomorphic Storable.Vector Double.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: match_co: needs more cases

2013-11-07 Thread crockeea
I got this error with a small example, so I thought I'd post it for you. I
could only get it to work when split over two files.


Main.hs:
import qualified Data.Vector.Unboxed as U
import Helper

main = do
let iters = 100
dim = 221184
y = U.replicate dim 0 :: U.Vector (ZqW M)
let ans = iterate (f y) y !! iters
putStr $ (show $ U.foldl1' (+) ans)


Helper.hs
{-# LANGUAGE FlexibleContexts, StandaloneDeriving,
GeneralizedNewtypeDeriving, MultiParamTypeClasses #-}
module VectorTestHelper (ZqW,f,M) where

import qualified Data.Vector.Unboxed as U
import qualified Data.Vector.Generic as V
import Data.Vector.Generic.Mutable   as M

f :: (Num r, V.Vector v r) => v r -> v r -> v r
{-# SPECIALIZE f :: (Num (ZqW m Int)) => U.Vector (ZqW m Int) -> U.Vector
(ZqW m Int) -> U.Vector (ZqW m Int) #-}
f x y = V.zipWith (+) x y


newtype ZqW p i = T i deriving (U.Unbox, Show)
deriving instance (U.Unbox i) => V.Vector U.Vector (ZqW p i)
deriving instance (U.Unbox i) => MVector U.MVector (ZqW p i)

class Foo a b

data M
instance Foo M Int

instance (Foo p i, Integral i) => Num (ZqW p i) where
(T a) + (T b) = T $ (a+b)

fromInteger x = T $ fromInteger x


It's possible I'm abusing SPECIALIZE here, but I'm trying to get Unboxed
vector specialization, even though I have a phantom type. (In practice, the
phantom will represent a modulus and will be used in the Num instance).

When compiling with GHC 7.6.2 and -O2, I get a dozen or so "match_co: needs
more cases" warnings. Indeed, based on the runtime, it appears that
specialization is not happening. How to actually make this work is a whole
different question...



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/match-co-needs-more-cases-tp5730855p5739541.html
Sent from the Haskell - Glasgow-haskell-users mailing list archive at 
Nabble.com.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: match_co: needs more cases

2013-05-28 Thread Simon Peyton-Jones
It's harmless. But it's there to tell us that a RULE is not going to match 
because the LHS involves a coercion that is not Refl or a variable.   Matching 
on more complex coercions is likely to be fragile, since they can take a 
variety of forms.

So don't worry too much, but I'd be interested in a repro case

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of Evan Laforge
| Sent: 27 May 2013 18:56
| To: GHC users
| Subject: match_co: needs more cases
| 
| I made some strictifying changes and started getting this msg from ghc:
| 
| match_co: needs more cases
| vector-0.10.0.1:Data.Vector.Generic.Mutable.MVector{tc r46}
|   (Sym <(vector-0.10.0.1:Data.Vector.TFCo:R:MutableVector{tc r45})>)
|   
| 
| It's not just TimeVectorStorable.Sample (which is indeed stored in
| Data.Vectors), we also have some mysterious compiler-generated
| symbols:
| 
| match_co: needs more cases
| vector-0.10.0.1:Data.Vector.Generic.Mutable.MVector{tc rQA}
|   (Sym <(vector-0.10.0.1:Data.Vector.TFCo:R:MutableVector{tc rQz})>)
|   
| 
| I assume this is harmless, but I didn't see any other references to
| this error on the web or on the ghc trac so maybe it's new?
| 
| ___
| 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


match_co: needs more cases

2013-05-27 Thread Evan Laforge
I made some strictifying changes and started getting this msg from ghc:

match_co: needs more cases
vector-0.10.0.1:Data.Vector.Generic.Mutable.MVector{tc r46}
  (Sym <(vector-0.10.0.1:Data.Vector.TFCo:R:MutableVector{tc r45})>)
  

It's not just TimeVectorStorable.Sample (which is indeed stored in
Data.Vectors), we also have some mysterious compiler-generated
symbols:

match_co: needs more cases
vector-0.10.0.1:Data.Vector.Generic.Mutable.MVector{tc rQA}
  (Sym <(vector-0.10.0.1:Data.Vector.TFCo:R:MutableVector{tc rQz})>)
  

I assume this is harmless, but I didn't see any other references to
this error on the web or on the ghc trac so maybe it's new?

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