
Hi everyone, I'm working on a computational algebra program and I've run into a problem. In my program, I have types for instances of algebraic objects, e.g. ZModN for modular integers, and types for the objects themselves, e.g. ZModNTy for the ring of modular integers. Now, I want to subclass ZModNTy from something like class RingTy a b where order :: a -> Integer units :: a -> [b] where `a' represents algebraic object, and `b' the type of instances of that object. I want an instance instance RingTy ZModNTy ZModN where ... but then code that only uses order fails with errors like No instance for (RingTy ZModNTy b) arising from a use of `order' at Test2.hs:16:8-15 since there is no constraint on the second type variable. I think what I really want is class RingTy a where order :: a b -> Integer units :: a b -> [b] but this doesn't work either since ZModNTy is not parametric in its type like, say, `Polynomial a' is. Is this a common problem? Is there a standard way to handle it? Thank you for your attention, Cotton

On Wednesday 02 July 2008, Cotton Seed wrote:
Hi everyone,
I'm working on a computational algebra program and I've run into a problem. In my program, I have types for instances of algebraic objects, e.g. ZModN for modular integers, and types for the objects themselves, e.g. ZModNTy for the ring of modular integers.
Now, I want to subclass ZModNTy from something like
class RingTy a b where order :: a -> Integer units :: a -> [b]
where `a' represents algebraic object, and `b' the type of instances of that object. I want an instance
instance RingTy ZModNTy ZModN where ...
but then code that only uses order fails with errors like
No instance for (RingTy ZModNTy b) arising from a use of `order' at Test2.hs:16:8-15
since there is no constraint on the second type variable.
I think what I really want is
class RingTy a where order :: a b -> Integer units :: a b -> [b]
but this doesn't work either since ZModNTy is not parametric in its type like, say, `Polynomial a' is.
Is this a common problem? Is there a standard way to handle it?
Correct me if I'm wrong, but wouldn't the a uniquely determine the b? In that case, you'd probably want a functional dependency: class RingTy a b | a -> b where order :: a -> Integer units :: a -> [b] This solves the problem with order, because with multi-parameter type classes, all the variables should be determined for a use of a method. Since b is not involved with order, it could be anything, so it's rather ambiguous. The functional dependency solves this by uniquely determined b from a, so order is no longer ambiguous. Alternately, with the new type families, this can become: class RingTy a where type RingElem a :: * order :: a -> Integer units :: a -> [RingElem a] Or something along those lines. Hope that helps. -- Dan

Hi Dan,
Thanks! This is exactly what I was looking for.
Cotton
On Wed, Jul 2, 2008 at 9:57 PM, Dan Doel
On Wednesday 02 July 2008, Cotton Seed wrote:
Hi everyone,
I'm working on a computational algebra program and I've run into a problem. In my program, I have types for instances of algebraic objects, e.g. ZModN for modular integers, and types for the objects themselves, e.g. ZModNTy for the ring of modular integers.
Now, I want to subclass ZModNTy from something like
class RingTy a b where order :: a -> Integer units :: a -> [b]
where `a' represents algebraic object, and `b' the type of instances of that object. I want an instance
instance RingTy ZModNTy ZModN where ...
but then code that only uses order fails with errors like
No instance for (RingTy ZModNTy b) arising from a use of `order' at Test2.hs:16:8-15
since there is no constraint on the second type variable.
I think what I really want is
class RingTy a where order :: a b -> Integer units :: a b -> [b]
but this doesn't work either since ZModNTy is not parametric in its type like, say, `Polynomial a' is.
Is this a common problem? Is there a standard way to handle it?
Correct me if I'm wrong, but wouldn't the a uniquely determine the b? In that case, you'd probably want a functional dependency:
class RingTy a b | a -> b where order :: a -> Integer units :: a -> [b]
This solves the problem with order, because with multi-parameter type classes, all the variables should be determined for a use of a method. Since b is not involved with order, it could be anything, so it's rather ambiguous. The functional dependency solves this by uniquely determined b from a, so order is no longer ambiguous.
Alternately, with the new type families, this can become:
class RingTy a where type RingElem a :: * order :: a -> Integer units :: a -> [RingElem a]
Or something along those lines.
Hope that helps. -- Dan

On Wed, 2 Jul 2008, Cotton Seed wrote:
Hi everyone,
I'm working on a computational algebra program and I've run into a problem. In my program, I have types for instances of algebraic objects, e.g. ZModN for modular integers, and types for the objects themselves, e.g. ZModNTy for the ring of modular integers.
Maybe you are also interested in: http://darcs.haskell.org/numericprelude/src/Number/ResidueClass.hs http://darcs.haskell.org/numericprelude/src/Number/ResidueClass/

Hi Henning,
The numeric prelude was inspiration for a lot of my design. Part of
the reason I didn't use it was because one of my goals is to learn
Haskell better, and I wanted to grapple with these design decisions
myself.
I decided, like IsZeroTestable in the numeric prelude, to make
zero/one separate type classes. Thus, I have
class AbelianGroup a where
(+) :: a -> a -> a
negate :: a -> a
class HasZero a where
zero :: a
so ZModN is an instance of AbelianGroup but not HasZero. Most
functions that "want" a zero have two forms, for example,
sum :: (HasZero a, AbelianGroup a) => [a] -> a
sumWithZero :: (AbelianGroup a) => a -> [a] -> a
although I may eventually require all types to have a corresponding Ty
class and change this to
sumWithTy :: (AbelianGroup a) => AblieanGroupTy a -> [a] -> a
Matrices are another example that fits this model. Numeric prelude
defines zero/one to be 1x1 matrices, but asserts dimensions match in
various operations, so they don't actually seem usable.
Cotton
On Thu, Jul 3, 2008 at 1:22 AM, Henning Thielemann
On Wed, 2 Jul 2008, Cotton Seed wrote:
Hi everyone,
I'm working on a computational algebra program and I've run into a problem. In my program, I have types for instances of algebraic objects, e.g. ZModN for modular integers, and types for the objects themselves, e.g. ZModNTy for the ring of modular integers.
Maybe you are also interested in: http://darcs.haskell.org/numericprelude/src/Number/ResidueClass.hs http://darcs.haskell.org/numericprelude/src/Number/ResidueClass/

Slightly off-topic - but I'm curious to know why you want objects representing the structures as well as the elements - what will they be used for?

A number of operations -- like order above -- are conceptually
connected not to the elements but to the structures themselves. Here
is the outline of a more complicated example. I also have a vector
space class
class VectorSpaceTy a b | a - > b where
dimension :: a -> Integer
basis :: (Field c) => a -> [b c]
where `b' is a vector space over the field `c'.
Suppose I have a haskell function `f :: a c -> b c' representing a
linear transformation between (elements) of two vector spaces. I can
write
transformationMatrix :: VectorSpaceTy ta a -> VectorSpaceTy tb b -> (a
c -> b c) -> Matrix c
to compute the matrix of the linear transformation.
Another alternative is something like ModuleBasis from the numeric prelude:
class (Module.C a v) => C a v where
{- | basis of the module with respect to the scalar type,
the result must be independent of argument,
'Prelude.undefined' should suffice. -}
basis :: a -> [v]
To compute the basis (for type reasons?) basis needs an (ignored)
element of the vector space, but this seems ugly to me.
In my case, the vector space is the space of modular forms. Computing
a basis requires a tremendous amount of work. I only want to do it
once. The ...Ty object gives me a place to stash the result.
How would you do this?
Cotton
On Thu, Jul 3, 2008 at 7:01 AM, DavidA
Slightly off-topic - but I'm curious to know why you want objects representing the structures as well as the elements - what will they be used for?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

class RingTy a b where order :: a -> Integer units :: a -> [b]
class VectorSpaceTy a b | a - > b where dimension :: a -> Integer basis :: (Field c) => a -> [b c]
where `b' is a vector space over the field `c'.
It looks like you are using the first (of two) type arguments to the RingTy and VectorSpaceTy type classes as abstract types; in other words, operations on rings and vector spaces don't really care what the type "a" is in "RingTy a b" and "VectorSpaceTy a b". Is that true? Assuming so, if I may strip away the (extremely sweet) syntactic sugar afforded by type classes for a moment, what you seem to be doing is to pass dictionaries of types data RingTy a b = RingTy { order :: a -> Integer, units :: a -> [b] } data VectorSpaceTy a b = VectorSpaceTy { dimension :: a -> Integer, basis :: forall c. (Field c) => a -> [b c] } to operations on rings and vector spaces. Because the type "a" is abstract, you may as well pass dictionaries of types data RingTy b = RingTy { order :: Integer, units :: [b] } data VectorSpaceTy b = VectorSpaceTy { dimension :: Integer, basis :: forall c. (Field c) => [b c] } to these operations. The information that you want computed just once per ring or per vector space can be defined as lexically scoped variables where you create these dictionaries in the first place. To add back the syntactic sugar (i.e., to make the dictionary arguments implicit) and to make the type system check that elements of different vector spaces are not confused, you may find Dylan Thurston's technique useful: http://www.cs.rutgers.edu/~ccshan/prepose/prepose.pdf -- Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig 2008-07-04 Independence from America! http://caab.org.uk/ 2008-07-05 International Co-operative Day http://ica.coop/ http://www.guardian.co.uk/politics/2008/jul/02/labour.tradeunions
participants (5)
-
Chung-chieh Shan
-
Cotton Seed
-
Dan Doel
-
DavidA
-
Henning Thielemann