Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  ErrorT Identity (Michael Mossey)
   2. Re:  Class definition syntax (Joe Fredette)
   3. Re:  Class definition syntax (Daniel Fischer)
   4.  several questions: multi-param typeclasses, etc. (Michael Mossey)
   5. Re:  several questions: multi-param       typeclasses, etc.
      (Brent Yorgey)
   6. Re:  several questions: multi-param       typeclasses,    etc.
      (Michael Mossey)
   7. Re:  several questions: multi-param       typeclasses, etc.
      (Brent Yorgey)
   8. Re:  several questions: multi-param typeclasses,  etc.
      (Chadda? Fouch?)


----------------------------------------------------------------------

Message: 1
Date: Sat, 31 Oct 2009 20:48:48 -0700
From: Michael Mossey <m...@alumni.caltech.edu>
Subject: [Haskell-beginners] ErrorT Identity
To: beginners@haskell.org
Message-ID: <4aed0520.3060...@alumni.caltech.edu>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Does using ErrorT Identity have advantages over Either?

-Mike


------------------------------

Message: 2
Date: Sat, 31 Oct 2009 23:53:16 -0400
From: Joe Fredette <jfred...@gmail.com>
Subject: Re: [Haskell-beginners] Class definition syntax
To: Shawn Willden <shawn-hask...@willden.org>
Cc: beginners@haskell.org
Message-ID: <992836ac-4c2b-45b1-8aea-8809989c2...@gmail.com>
Content-Type: text/plain; charset=US-ASCII; format=flowed; delsp=yes

Ahh, I see what you need, you want to "lift" the IArray functions into  
your type. Well, Rather than trying to instance the type- you could  
define your type like this:

        newtype Board = Board IArray.IArray ... whatever

        (!) :: Board -> Location -> Int
        (!) = IArray.(!)

That is, create synonyms manually for each function you _absolutely  
need, assuming they don't conflict elsewhere. You would have to  
manually import each -- I feel like there is probably a better way to  
do this, but this will definitely work. Though, I'm not sure why you'd  
need to be instancing another class with a type like this, it's a  
_very_ specific type, I imagine one or the other set of functions  
ought to be easy enough to define simply about the type (dodging the  
typeclass entirely). I imagine extensibility comes to play here.

One thing you might be able to do is

        class IArray a Location Int , OtherClass a ... => MyClass a ... where

Which would force you to have a type which is an IArray of Location ->  
Ints, and an OtherClass, etc. I don't know all the details of your  
implementation, so I don't know how well this would work, but I  
imagine thats probably the "better" solution I'm thinking of...


/Joe

On Oct 31, 2009, at 11:42 PM, Shawn Willden wrote:

> On Saturday 31 October 2009 08:55:56 pm Joe Fredette wrote:
>> Well, I think the issue is you're thinking too OOPy...
>
> I understand what you're saying, but I don't think I am.
>
>> But let me answer the actual problem first, type classes are
>> (basically) functions on types. So a type of "kind" `* -> * -> *`
>> means it is a type which accepts two type variables. So:
>>
>>      newtype Foo a b = Foo (a, b)
>
> Okay, that makes sense.  What I'd read about kinds was considerably  
> less
> clear.  Thanks.
>
>>      newtype Board = Board IArray ...
>>
>> means that _you can just use the IArray types_! Well, almost, really
>> what you want is a type-synonym:
>>
>>      type Board = IArray Location ...
>>
>> Now you can write functions like
>>
>>      foo :: Board -> Int
>>      foo = Board !! (1,2)
>>
>> and it will "just work" because Board _is_ an "IArray".
>>
>> Hope that makes sense...
>
> It does make sense, but it doesn't solve my problem.  See, Board  
> isn't the
> only type I have (and, also, Board has to be a newtype rather than a  
> type
> synonym because it's also an instance of another class -- well,  
> unless I want
> to turn on the extension that allows instances of synonyms, and I'm  
> not sure
> what the etiquette is there), and some of the others aren't just  
> IArrays with
> an aliased name, they have other data elements as well.  For example:
>
> data ScoredBoard = ScoredBoard {
>    arry     :: (IArray Location String)
>    score    :: Int
>    maxScore :: Int
> }
>
> I would like to be able to use (!), (//), bound, range, etc., on  
> those as
> well, and without having to say "range (arry sb)", or having to  
> define a
> bunch of fooRange, barRange, bazRange, etc., functions.
>
> Basically I want to take this set of common array operations and  
> overload them
> for a bunch of different types.  As I understand it, classes are  
> effectively
> the only way to overload in Haskell.
>
> Perhaps it just isn't possible to do what I want?  If kind  
> signatures must
> match, then that's a problem, because different types will have  
> different
> numbers of construction parameters.
>
> Thanks for the help,
>
>       Shawn.



------------------------------

Message: 3
Date: Sun, 1 Nov 2009 05:44:07 +0100
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Class definition syntax
To: beginners@haskell.org
Message-ID: <200911010544.07399.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

First, the IArray class from Data.Array.IArray is not the real thing.
Looking at the class in Data.Array.Base, we see

{- | Class of immutable array types.

An array type has the form @(a i e)@ where @a@ is the array type
constructor (kind @* -> * -> *@), @i@ is the index type (a member of
the class 'Ix'), and @e@ is the element type.  The @IArray@ class is
parameterised over both @a@ and @e@, so that instances specialised to
certain element types can be defined.
-}
class IArray a e where
    -- | Extracts the bounds of an immutable array
    bounds           :: Ix i => a i e -> (i,i)
    numElements      :: Ix i => a i e -> Int
    unsafeArray      :: Ix i => (i,i) -> [(Int, e)] -> a i e
    unsafeAt         :: Ix i => a i e -> Int -> e
    unsafeReplace    :: Ix i => a i e -> [(Int, e)] -> a i e
    unsafeAccum      :: Ix i => (e -> e' -> e) -> a i e -> [(Int, e')] -> a i e
    unsafeAccumArray :: Ix i => (e -> e' -> e) -> e -> (i,i) -> [(Int, e')] -> 
a i e

    unsafeReplace arr ies = runST (unsafeReplaceST arr ies >>= unsafeFreeze)
    unsafeAccum f arr ies = runST (unsafeAccumST f arr ies >>= unsafeFreeze)
    unsafeAccumArray f e lu ies = runST (unsafeAccumArrayST f e lu ies >>= 
unsafeFreeze)

That's more like it, isn't it?
Doesn't solve your kind problems, though.

Am Sonntag 01 November 2009 04:42:24 schrieb Shawn Willden:
> On Saturday 31 October 2009 08:55:56 pm Joe Fredette wrote:
> > Well, I think the issue is you're thinking too OOPy...
>
> I understand what you're saying, but I don't think I am.
>
> > But let me answer the actual problem first, type classes are
> > (basically) functions on types. So a type of "kind" `* -> * -> *`
> > means it is a type which accepts two type variables. So:
> >
> >     newtype Foo a b = Foo (a, b)
>
> Okay, that makes sense.  What I'd read about kinds was considerably less
> clear.  Thanks.
>
> >     newtype Board = Board IArray ...
> >
> > means that _you can just use the IArray types_! Well, almost, really
> > what you want is a type-synonym:
> >
> >     type Board = IArray Location ...
> >
> > Now you can write functions like
> >
> >     foo :: Board -> Int
> >     foo = Board !! (1,2)
> >
> > and it will "just work" because Board _is_ an "IArray".
> >
> > Hope that makes sense...
>
> It does make sense, but it doesn't solve my problem.  See, Board isn't the
> only type I have (and, also, Board has to be a newtype rather than a type
> synonym because it's also an instance of another class -- well, unless I
> want to turn on the extension that allows instances of synonyms, and I'm
> not sure what the etiquette is there),

That's not much of a problem. It may not be portable (maybe it is, maybe not, I 
don't 
know), but it's nothing unsafe.
Or you could use FlexibleInstances and
instance OtherClass (Array Location Int) where...

> and some of the others aren't just
> IArrays with an aliased name, they have other data elements as well.  For
> example:
>
> data ScoredBoard = ScoredBoard {
>     arry     :: (IArray Location String)
>     score    :: Int
>     maxScore :: Int
> }

Would something like

import Data.Array.Base

data ScoreBoard i e = ScoreBoard
    { arry :: Array i e
    , score :: Int
    , maxScore :: Int
    }

instance  IArray ScoreBoard e where
    bounds sb = bounds (arry sb)
    numElements sb = numElements (arry sb)
    unsafeArray bds ass = ScoreBoard (unsafeArray bds ass) 0 0
    unsafeAt sb i = unsafeAt (arry sb) i
    ...

be an option (analogous for Board)?

>
> I would like to be able to use (!), (//), bound, range, etc., on those as
> well, and without having to say "range (arry sb)", or having to define a
> bunch of fooRange, barRange, bazRange, etc., functions.

If you don't want to change the kind of Board etc, another option would be a 
multiparameter type class with functional dependencies or type families:

With fundeps:

class KindOfArrayLike a i e | a -> i, a -> e where
    (!) :: a -> i -> e
    (//) :: a -> [(i,e)] -> a
    ...

instance KindOfArrayLike Board Location Int where
    (Board a) ! i = a Data.Array.IArray.! i
    (Board a) // upd = Board (a Data.Array.IArray.// upd)
    ...

instance KindOfArrayLike ScoreBoard Location String where
    sb ! i = arry sb Data.Array.IArray.! i
    sb // upd = sb{ arry = arry sb Data.Array.IArray.// upd }
    ...

With type families:

class ArrayLike a where
    type Idx a :: *
    type Elt a :: *
    (!) :: a -> Idx a -> Elt a
    (//) :: a -> [(Idx a, Elt a)] -> a

instance ArrayLike Board where
    type Idx Board = Location
    type Elt Board = Int
    (implementation as before)

>
> Basically I want to take this set of common array operations and overload
> them for a bunch of different types.  As I understand it, classes are
> effectively the only way to overload in Haskell.
>
> Perhaps it just isn't possible to do what I want?  If kind signatures must
> match, then that's a problem, because different types will have different
> numbers of construction parameters.
>
> Thanks for the help,
>
>       Shawn.





------------------------------

Message: 4
Date: Sun, 1 Nov 2009 07:15:17 -0800 (PST)
From: "Michael Mossey" <m...@alumni.caltech.edu>
Subject: [Haskell-beginners] several questions: multi-param
        typeclasses, etc.
To: beginners@haskell.org
Message-ID:
        <1754.75.50.168.229.1257088517.squir...@mail.alumni.caltech.edu>
Content-Type: text/plain;charset=iso-8859-1

I'm trying to understand multi-param typeclasses; a particular one
(MonadError); and functional dependencies.

For example, throwError in in the MonadError class definition:

class Monad m => MonadError e m | m -> e where
    throwError :: e -> m a


The concept of a multi-parameter class is a litte tricky. It's no
longer so simple to say that "ONE type is AN instance of ONE class."
Instead, it seems more appropriate to say that "in a context where e
and m fulfill the criteria for class MonadError, the function
throwError is available."

In a sense, there is no single type that is an instance of MonadError.

Is this the right way to put it?

So I went looking for an instance of MonadError, in particular with
use with Either.

I couldn't find actual source code with an instance, but the Haddock
documentation lists this:

Instances:

   Error e => MonadError e (Either e)

The code doesn't give the definition, but I suppose it would be:

             throwError e = Left e ???

Now I'm interested in understanding this functional dependency between
m and e. For the compiler to decide that a particular instance's
definition of throwError is available, it  must decide that

   e is of class Error (it is given by class constraint)
   m is a Monad (Either e is such)
   and then this m -> e thing: I don't know how to put this into words

Any explanation/clarification/correction appreciated.

Thanks,
Mike



------------------------------

Message: 5
Date: Sun, 1 Nov 2009 10:41:37 -0500
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] several questions: multi-param
        typeclasses, etc.
To: beginners@haskell.org
Message-ID: <20091101154137.ga22...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

Hi Michael,

On Sun, Nov 01, 2009 at 07:15:17AM -0800, Michael Mossey wrote:
> I'm trying to understand multi-param typeclasses; a particular one
> (MonadError); and functional dependencies.
> 
> For example, throwError in in the MonadError class definition:
> 
> class Monad m => MonadError e m | m -> e where
>     throwError :: e -> m a
>
> In a sense, there is no single type that is an instance of MonadError.
> 
> Is this the right way to put it?

I think a better way to put it is that an instance of MonadError is a
PAIR of types, instead of a single type.

>    Error e => MonadError e (Either e)
> 
> The code doesn't give the definition, but I suppose it would be:
> 
>              throwError e = Left e ???

Right. (No pun intended ;)

> Now I'm interested in understanding this functional dependency between
> m and e. For the compiler to decide that a particular instance's
> definition of throwError is available, it  must decide that
> 
>    e is of class Error (it is given by class constraint)
>    m is a Monad (Either e is such)
>    and then this m -> e thing: I don't know how to put this into words

The m -> e thing isn't a constraint that needs to be satisfied; it
gives some extra information to help the compiler with inferring which
instance to use.  In particular, "m -> e" says "the type chosen for m
DETERMINES the type chosen for e"; put another way, "there cannot be
two instances with the same type for m but different types for e".  So
in this case you could not also make an instance

  MonadError String (Either e).

-Brent


------------------------------

Message: 6
Date: Sun, 01 Nov 2009 08:32:34 -0800
From: Michael Mossey <m...@alumni.caltech.edu>
Subject: Re: [Haskell-beginners] several questions: multi-param
        typeclasses,    etc.
To: Brent Yorgey <byor...@seas.upenn.edu>
Cc: beginners@haskell.org
Message-ID: <4aedb822.7020...@alumni.caltech.edu>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed



Brent Yorgey wrote:
> The m -> e thing isn't a constraint that needs to be satisfied; it
> gives some extra information to help the compiler with inferring which
> instance to use.  In particular, "m -> e" says "the type chosen for m
> DETERMINES the type chosen for e"; put another way, "there cannot be
> two instances with the same type for m but different types for e".  So
> in this case you could not also make an instance
> 
>   MonadError String (Either e).
> 

Thanks, Brent.  Now what I'm a bit confused about:
if you wrote

instance (Error e) => MonadError e (Either e)

and no other instance with Either e, then the compiler would have only one 
choice. So why would it need the extra information in the functional 
dependency?

On the other hand, if you added

instance (Error e) => MonadError String (Either e)

and didn't include the functional dependency, the compiler would still run 
into a problem with overlapping instances and have no way to decide, which 
I presume is still an error.

So it looks to me (no doubt because I don't understand correctly) that the 
functional dependency doesn't add any information or clarify any situation. 
Please explain!

Thanks,
Mike




------------------------------

Message: 7
Date: Sun, 1 Nov 2009 12:25:55 -0500
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] several questions: multi-param
        typeclasses, etc.
To: beginners@haskell.org
Message-ID: <20091101172555.ga25...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Sun, Nov 01, 2009 at 08:32:34AM -0800, Michael Mossey wrote:
>
>
> Brent Yorgey wrote:
>> The m -> e thing isn't a constraint that needs to be satisfied; it
>> gives some extra information to help the compiler with inferring which
>> instance to use.  In particular, "m -> e" says "the type chosen for m
>> DETERMINES the type chosen for e"; put another way, "there cannot be
>> two instances with the same type for m but different types for e".  So
>> in this case you could not also make an instance
>>
>>   MonadError String (Either e).
>>
>
> Thanks, Brent.  Now what I'm a bit confused about:
> if you wrote
>
> instance (Error e) => MonadError e (Either e)
>
> and no other instance with Either e, then the compiler would have only one 
> choice. So why would it need the extra information in the functional 
> dependency?

Because type classes are open: when compiling a module, the compiler
is never allowed to assume that the instances it sees are the only
instances, because there could always be another instance declared in
a module it hasn't seen yet.

>
> On the other hand, if you added
>
> instance (Error e) => MonadError String (Either e)
>
> and didn't include the functional dependency, the compiler would still run 
> into a problem with overlapping instances and have no way to decide, which 
> I presume is still an error.

True.  In the case of this particular *instance*, the functional
dependency doesn't really add all that much.  But that doesn't mean
the functional dependency on the *class* is useless; there can be
other instances of the class as well.

-Brent


------------------------------

Message: 8
Date: Sun, 1 Nov 2009 20:21:11 +0100
From: Chadda? Fouch? <chaddai.fou...@gmail.com>
Subject: Re: [Haskell-beginners] several questions: multi-param
        typeclasses,    etc.
To: Michael Mossey <m...@alumni.caltech.edu>
Cc: beginners@haskell.org
Message-ID:
        <e9350eaf0911011121h6095571evff61398cf281...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Sun, Nov 1, 2009 at 5:32 PM, Michael Mossey <m...@alumni.caltech.edu> wrote:
> On the other hand, if you added
>
> instance (Error e) => MonadError String (Either e)
>
> and didn't include the functional dependency, the compiler would still run
> into a problem with overlapping instances and have no way to decide, which I
> presume is still an error.

Right, in this case it is true, but supposing the MonadError instance
for Either was rather :

> instance (Error e) => MonadError (Maybe String) (Either e)

There would be nothing a priori that would prevent you from writing
another instance :

> instance (Error e) => MonadError String (Either e)

There are a certain number of case where this functional constraint is
thus useful.

-- 
Jedaï


------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 17, Issue 1
****************************************

Reply via email to