[mercury-users] Failing at typeclasses.

Julian Fondren ayrnieu at gmail.com
Sat Feb 17 00:23:25 AEDT 2007


I get the attached errors from compiling the attached module,
which itself is meant to yield these errors that I get from
a much longer random.m that I work on, with similar typeclass
use (or attempted use).

Can someone please just show me a correct typeclass use with
this many variables?

:- typeclass prng(T, S, R) <= (state(T), seed(S), return(R)) where [
    pred seed(S::in, T::uo) is det,
    pred random(R::out, T::di, T::uo) is det
].
:- typeclass fox_prng(T) <= prng(fox_state, fox_seed, T) where [ ].
:- instance fox_prng(int).
:- instance fox_prng(char).

Sorry if this request is a bit lame, but I'm at the point
where I think I'd progress more by throwing the typeclasses
away entirely and using module-based polymorphism, or by
learning about existential types.  Insofar as I understand
these errors, they don't seem fixable.

For instance, I think a fox_seed(T) would help things
typeclass-side, but there's no place in the -actual type-
to fit this artificial dispatch:

:- type fox_seed(T) ---> fox_state(string).  % ???

thanks,
Julian.
-------------- next part --------------
:- module unconstrained.
:- interface.
:- import_module int, char, pair, string.

:- typeclass seed(T) where [ ].
:- typeclass state(T) where [ ].
:- typeclass return(T) where [ ].

:- typeclass prng(T, S, R) <= (state(T), seed(S), return(R)) where [
    pred seed(S::in, T::uo) is det,
    pred random(R::out, T::di, T::uo) is det
].

:- type fox_seed == string.
:- type fox_state == pair(string, int).

:- instance seed(fox_seed).
:- instance state(fox_state).

:- typeclass fox_prng(T) <= prng(fox_state, fox_seed, T) where [ ].

:- instance fox_prng(int).
:- instance fox_prng(char).

:- implementation.

:- instance seed(fox_seed) where [ ].
:- instance state(fox_state) where [ ].

:- instance fox_prng(int) where [
    pred(seed/2) is fox_seed,
    (random(R, !RNG) :- fox_rand(R0, !RNG), char.to_int(R0, R))
].

:- instance fox_prng(char) where [
    pred(seed/2) is fox_seed,
    pred(random/3) is fox_rand
].

:- pred fox_seed(fox_seed::in, fox_state::uo) is det.
fox_seed(S, RNG) :- RNG = pair(S, 0).

:- pred fox_rand(char::out, fox_state::di, fox_state::uo) is det.
fox_rand(R, !RNG) :-
    !.RNG = pair(S, I),
    string.index_det(S, I, R),
    (
        string.length(S) < I + 1
    ->
        !:RNG = pair(S, 0)
    ;
        !:RNG = pair(S, I + 1)
    ).
-------------- next part --------------
unconstrained.m:035: In instance declaration for `unconstrained.fox_prng'/1:
unconstrained.m:035:   incorrect method name(s): predicate
unconstrained.m:035:   `unconstrained.seed'/2 predicate
unconstrained.m:035:   `unconstrained.random'/3.
unconstrained.m:035: In instance declaration for
unconstrained.m:035:   `unconstrained.fox_prng(character)': superclass
unconstrained.m:035:   constraint(s) not satisfied:
unconstrained.m:035:   `unconstrained.prng((pair.pair(string, int)), string,
unconstrained.m:035:   character)'.
unconstrained.m:030: In instance declaration for `unconstrained.fox_prng'/1:
unconstrained.m:030:   incorrect method name(s): predicate
unconstrained.m:030:   `unconstrained.seed'/2 predicate
unconstrained.m:030:   `unconstrained.random'/3.
unconstrained.m:030: In instance declaration for `unconstrained.fox_prng(int)':
unconstrained.m:030:   superclass constraint(s) not satisfied:
unconstrained.m:030:   `unconstrained.prng((pair.pair(string, int)), string,
unconstrained.m:030:   int)'.
unconstrained.m:023: In instance declaration for
unconstrained.m:023:   `unconstrained.fox_prng(character)': superclass
unconstrained.m:023:   constraint(s) not satisfied:
unconstrained.m:023:   `unconstrained.prng((pair.pair(string, int)), string,
unconstrained.m:023:   character)'.
unconstrained.m:022: In instance declaration for `unconstrained.fox_prng(int)':
unconstrained.m:022:   superclass constraint(s) not satisfied:
unconstrained.m:022:   `unconstrained.prng((pair.pair(string, int)), string,
unconstrained.m:022:   int)'.
unconstrained.m:010: In declaration for predicate `unconstrained.seed/2':
unconstrained.m:010:   error in type class constraints: type variable R occurs
unconstrained.m:010:   in the constraints, but is not determined by the
unconstrained.m:010:   predicate's argument types.
unconstrained.m:010:   All types occurring in typeclass constraints must be
unconstrained.m:010:   fully determined. A type is fully determined if one of
unconstrained.m:010:   the following holds:
unconstrained.m:010:   1) All type variables occurring in the type are
unconstrained.m:010:   determined.
unconstrained.m:010:   2) The type occurs in a constraint argument, that
unconstrained.m:010:   argument is in the range of some functional dependency
unconstrained.m:010:   for that class, and the types in all of the domain
unconstrained.m:010:   arguments for that functional dependency are fully
unconstrained.m:010:   determined.
unconstrained.m:010:   A type variable is determined if one of the following
unconstrained.m:010:   holds:
unconstrained.m:010:   1) The type variable occurs in the argument types of the
unconstrained.m:010:   predicate, function, or constructor which is
unconstrained.m:010:   constrained.
unconstrained.m:010:   2) The type variable occurs in a type which is fully
unconstrained.m:010:   determined.
unconstrained.m:010:   See the "Functional dependencies" section of the
unconstrained.m:010:   reference manual for details.
unconstrained.m:011: In declaration for predicate `unconstrained.random/3':
unconstrained.m:011:   error in type class constraints: type variable S occurs
unconstrained.m:011:   in the constraints, but is not determined by the
unconstrained.m:011:   predicate's argument types.
unconstrained.m:011:   All types occurring in typeclass constraints must be
unconstrained.m:011:   fully determined. A type is fully determined if one of
unconstrained.m:011:   the following holds:
unconstrained.m:011:   1) All type variables occurring in the type are
unconstrained.m:011:   determined.
unconstrained.m:011:   2) The type occurs in a constraint argument, that
unconstrained.m:011:   argument is in the range of some functional dependency
unconstrained.m:011:   for that class, and the types in all of the domain
unconstrained.m:011:   arguments for that functional dependency are fully
unconstrained.m:011:   determined.
unconstrained.m:011:   A type variable is determined if one of the following
unconstrained.m:011:   holds:
unconstrained.m:011:   1) The type variable occurs in the argument types of the
unconstrained.m:011:   predicate, function, or constructor which is
unconstrained.m:011:   constrained.
unconstrained.m:011:   2) The type variable occurs in a type which is fully
unconstrained.m:011:   determined.
unconstrained.m:011:   See the "Functional dependencies" section of the
unconstrained.m:011:   reference manual for details.


More information about the users mailing list