[Haskell-cafe] more generic class instances?
Nickolay Kudasov
nickolay.kudasov at gmail.com
Sat Nov 2 07:14:25 UTC 2013
Hi Christopher,
What you want is to make b (and a) depend on f. This can be done in several
ways.
With functional dependencies:
class (Integral a, Num b) => PartialSum a b f | f -> a b where
partialSum :: f -> a -> b
instance (Integral a, Num b) => PartialSum a b (a -> b) where
partialSum f n = foldl (\u v -> u + f v) 0 [1..n]
With type families:
class PartialSum f where
type End f
type Res f
partialSum' :: f -> End f -> Res f
instance (Integral a, Num b) => PartialSum (a -> b) where
type End (a -> b) = a
type Res (a -> b) = b
partialSum f n = foldl (\u v -> u + f v) 0 [1..n]
I can’t see though what you’re trying to achieve. Could you provide some
more use cases for that class?
Best,
Nick
2013/11/2 Christopher Howard <christopher.howard at frigidcode.com>
> Hi. I am playing around with basic Haskell overloading. What I'm
> interested in is how to do specialization in Haskell -- i.e., functions
> that work generically on all (or many) types but work more efficiently on
> certain types. So, I am trying to make a class of functions which can be
> fed into a partial sum calculator. Maybe something like so:
>
> class PartialSum f where
> -- params: term function, end index
> partialSum :: Integral b => f -> b -> a
>
> The most generic instance would be any function that takes an integer and
> returns a number. The specialized instances would things like, say, a
> wrapped function which is guaranteed to be linear (through safe
> constructors or something). But I'm having trouble figuring out how even to
> make the generic version. I'm thinking something like this:
>
> instance PartialSum (a -> b) where
> partialSum f n = foldl (\u v -> u + f v) 0 [1..n]
>
> But the compiler complains it can't prove that the input to the "f"
> function is the same type as the "n" parameter. That makes sense, but I'm
> not sure how to fix that.
> ______________________________**_________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/**mailman/listinfo/haskell-cafe<http://www.haskell.org/mailman/listinfo/haskell-cafe>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20131102/d7fd4cb4/attachment.html>
More information about the Haskell-Cafe
mailing list