Re: [Haskell-beginners] Custom type classes

May I suggest using FunctionalDependencies
https://wiki.haskell.org/Functional_dependencies
The class declaration is changed to
class Indexable idx a | idx -> a where
first :: idx -> a
This just means that *a* is fully determined by idx (your tuple).
Hence, instead of using as suggested
first $ Tuple3 (1::Int) 'a' False::Int
You can simplify and let the inference do its magic and use:
first $ Tuple3 1 'a' False
On Mon, Jan 25, 2016 at 8:42 AM, Imants Cekusins
Hello Daniel,
it works with these tweaks:
-- begin
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FlexibleContexts #-} module TupInst where
data Tuple3 a b c = Tuple3 a b c deriving (Show)
data Tuple2 a b = Tuple2 a b deriving (Show)
class Indexable idx a where first :: idx -> a
instance Indexable (Tuple2 a b) a where first (Tuple2 a0 b0) = a0
instance Indexable (Tuple3 a b c) a where first (Tuple3 a0 b0 c0) = a0
-- end
call it in ghci like this:
first $ Tuple3 (1::Int) 'a' False::Int _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

Thank you Guillaume fun deps are new for me too. quoting from the above wiki link: -- Read as: "container" type determines "elem" type. class Extract container elem | container -> elem where extract :: container -> elem The functional dependency "container -> elem" promises that we won't declare multiple instances with the same "container" type. Without the functional dependency, both instances above would be allowed, and the type of v would be potentially ambiguous. Even if only one instance is defined, the type system will not figure it out without the functional dependency.

On Wed, Jan 27, 2016 at 9:41 AM, Imants Cekusins
Thank you Guillaume
fun deps are new for me too.
quoting from the above wiki link:
-- Read as: "container" type determines "elem" type. class Extract container elem | container -> elem where extract :: container -> elem The functional dependency "container -> elem" promises that we won't declare multiple instances with the same "container" type.
Without the functional dependency, both instances above would be allowed, and the type of v would be potentially ambiguous. Even if only one instance is defined, the type system will not figure it out without the functional dependency.
At first this is weird because we have the feeling that `instance Indexable (Tuple2 a b) a` fully qualifie the second type "a" as equivalent to the first subtype "a" of Tuple2. This is True for this instance, but the typechecker does not try to find one instance which match, it tries to find if , knowing the class definition, it is possible to be sure that there will only be one instance matching, and this is not the case because someone can easily define `instance Indexable (Tuple2 a b) String`. That's something I really like about this mecanism, is that adding new instances later cannot change the behavior of previous one. [A bit of digression] Actually, I don't know why, but at first though I always think in the wrong direction when reasoning about types. FunctionalDependencies is one example, but I had the same issue when I tried to understand why `fmap` cannot work on unboxed Vector. When reading the types, `fmap :: Functor f => (a -> b) -> f a -> f b`, I was understanding that it accepts any `a` as input. It was working on `Vector a`, but not on `Unbox a => Vector a` which appears more constrained, so if `fmap` was accepting any `a` as argument, it will certainly accept an `Unbox a` which is more constrained. But actually it works the opposite, `fmap` types means that `a` should be anything, and not something constrained.

`fmap` types mean that `a` should be anything, and not something constrained.
just wondering: is it something specific to Functor class or does this hold for any class declaration: (a -> b) is not the same as ... a => (a -> b) in other words, if class expects (a -> b) with any a, instance must not constrain a. as opposed to ... a => a -> b which seems ok

On Wed, Jan 27, 2016 at 11:11 AM, Imants Cekusins
`fmap` types mean that `a` should be anything, and not something constrained.
just wondering: is it something specific to Functor class or does this hold for any class declaration:
(a -> b) is not the same as ... a => (a -> b)
a => (a -> b) does not really mean anything as far as I know because a is not a constraint (i.e: a typeclass). Perhaps you mean something such as Constraint a => (a -> b)
in other words, if class expects (a -> b) with any a, instance must not constrain a.
However I discovered the `ConstraintKinds` extension which may improve the situation. -- G.

Le mer. 27 janv. 2016 à 14:29, Guillaume Bouchard < guillaum.bouchard+haskell@gmail.com> a écrit :
However I discovered the `ConstraintKinds` extension which may improve the situation.
It does, it is in fact quite easy in modern Haskell to write a typeclass analogue to a functor but which may have further constraints on the types contained. But it won't be the historic "Functor" typeclass which is ubiquitous in the Haskell packages... {-# LANGUAGE ConstraintKinds, TypeFamilies #-} module ConstrainedFunctor where import GHC.Exts (Constraint) import qualified Data.Vector.Unboxed as V class CFunctor f where type FConstraint f x :: Constraint type instance FConstraint f x = () cfmap :: (FConstraint f a, FConstraint f b) => (a -> b) -> f a -> f b instance CFunctor V.Vector where type FConstraint V.Vector x = V.Unbox x cfmap f v = V.map f v doubleVector :: V.Vector Int -> V.Vector Int doubleVector = cfmap (*2) -- Jedaï
participants (4)
-
Chaddaï Fouché
-
Guillaume Bouchard
-
Imants Cekusins
-
Theodore Lief Gannon