You know, I was wondering... if Monads are a subset of Functors, and Applicative is a subset of Functors, and Monads are a subset of Applicative... shouldn't it be possible to tack on the definitions that automatically derive Functor and Applicative? Isn't it the case that there is really only one way to define Applicative for a Monad anyway? And isn't there only one way to define fmap for a Monad that makes sense?
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-request@haskell.org
You can reach the person managing the list at
beginners-owner@haskell.org
When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."
Today's Topics:
1. Re: Re: Thinking about monads (Brent Yorgey)
2. Re: How would you run a monad within another monad?
(Arthur Chan)
3. Re: How would you run a monad within another monad?
(Arthur Chan)
4. Re: How would you run a monad within another monad?
(Arthur Chan)
5. Re: How would you run a monad within another monad?
(Jason Dusek)
----------------------------------------------------------------------
Message: 1
Date: Tue, 14 Apr 2009 16:42:08 -0400
From: Brent Yorgey <byorgey@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Re: Thinking about monads
To: beginners@haskell.org
Message-ID: <20090414204207.GA16671@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii
On Mon, Apr 13, 2009 at 03:11:42PM -0700, Michael Mossey wrote:
>
> I know Maybe is both a functor and a monad, and I was thinking: what's the
> difference? They are both wrappers on types. Then I realized, the
> difference is: they have different class definitions.
In fact, every monad should be a functor, but not every functor is a
monad. Being a monad is a much stronger condition than being a functor.
>
> class Functor f where
> fmap :: (a->b) -> f a -> f b
>
> (Note how fussy this definition would be in C++. It would be a kind of
> template, but would probably look a lot more complex and would require
> lengthy declarations.)
>
> class Monad m where
> a >>= b :: m a -> (a -> m b) -> m b
Don't forget return :: a -> m a ! That's the other key method in the Monad
class. (There are also >> and 'fail' but those are unimportant---the
first is just a specialization of >>=, and fail is a hack).
-Brent
------------------------------
Message: 2
Date: Tue, 14 Apr 2009 14:05:22 -0700
From: Arthur Chan <baguasquirrel@gmail.com>
Subject: Re: [Haskell-beginners] How would you run a monad within
another monad?
To: Jason Dusek <jason.dusek@gmail.com>
Cc: beginners@haskell.org
Message-ID:
<74cabd9e0904141405i1fbadb85u8b87ffb05d61c493@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"
Here's my contrived example that threw the error.
If you go into ghci, and do a `:t (foo' "blah" myDoohickey)`, you will get
the type signature "IO ()".
Doing the same for myOtherDoohickey returns "IO True"
So you would think that you'd be able to uncomment the code that makes IO an
instance of Toplevel. foo' is a function that allows IO to run monadic
values of type Doohickey. But it doesn't work.
---
import IO
import Control.Monad.Reader
class (Monad n) => Doohickey n where
putRecord :: String -> n ()
class (Monad m) => Toplevel m where
foo :: (Doohickey n) => FilePath -> n a -> m a
newtype IOToplevelT a = IOToplevelT { runIOToplevelT :: ReaderT Handle IO a
} deriving (Monad, MonadReader Handle, MonadIO)
instance Doohickey IOToplevelT where
putRecord = liftIO . putStrLn
foo' s k = do
f <- liftIO $ openFile s AppendMode
runReaderT (runIOToplevelT k) f
--instance Toplevel IO where
-- foo = foo'
myDoohickey = do
putRecord "foo"
putRecord "bar"
myOtherDoohickey = do
putRecord "hello"
putRecord "world"
return True
On Mon, Apr 13, 2009 at 7:55 PM, Jason Dusek <jason.dusek@gmail.com> wrote:
> Copypasting and loading your code doesn't throw an error. Please,
> pastebin an example that demonstrates the error.
>
> --
> Jason Dusek
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/beginners/attachments/20090414/0c3d6d92/attachment-0001.htm
------------------------------
Message: 3
Date: Tue, 14 Apr 2009 14:39:56 -0700
From: Arthur Chan <baguasquirrel@gmail.com>
Subject: Re: [Haskell-beginners] How would you run a monad within
another monad?
To: Jason Dusek <jason.dusek@gmail.com>
Cc: beginners@haskell.org
Message-ID:
<74cabd9e0904141439u6b146b78n727cc83b0c16a7ca@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"
I seem to have finally solved my own problem, via something I learned from
RWH. The solution is to use functional dependencies...
The problem was that the compiler needed to know the relationship between
Doohickeys and Toplevels, and I couldn't figure out how to tell it that...
{-# LANGUAGE GeneralizedNewtypeDeriving, NoMonomorphismRestriction,
FunctionalDependencies, MultiParamTypeClasses #-}
import IO
import Control.Monad.Reader
class (Monad n) => Doohickey n where
putRecord :: String -> n ()
class (Monad m, Doohickey n) => Toplevel m n | m -> n where
foo :: FilePath -> n a -> m a
newtype IODoohickey a = IODoohickey { runIODoohickey :: ReaderT Handle IO a
} deriving (Monad, MonadReader Handle, MonadIO)
instance Doohickey IODoohickey where
putRecord = liftIO . putStrLn
instance Toplevel IO IODoohickey where
foo s k = do
f <- liftIO $ openFile s AppendMode
runReaderT (runIODoohickey k) f
myDoohickey = do
putRecord "foo"
putRecord "bar"
myOtherDoohickey = do
putRecord "hello"
putRecord "world"
return True
On Tue, Apr 14, 2009 at 2:05 PM, Arthur Chan <baguasquirrel@gmail.com>wrote:
> Here's my contrived example that threw the error.
>
> If you go into ghci, and do a `:t (foo' "blah" myDoohickey)`, you will get
> the type signature "IO ()".
> Doing the same for myOtherDoohickey returns "IO True"
>
> So you would think that you'd be able to uncomment the code that makes IO
> an instance of Toplevel. foo' is a function that allows IO to run monadic
> values of type Doohickey. But it doesn't work.
>
>
> ---
>
> import IO
> import Control.Monad.Reader
>
>
> class (Monad n) => Doohickey n where
> putRecord :: String -> n ()
>
> class (Monad m) => Toplevel m where
> foo :: (Doohickey n) => FilePath -> n a -> m a
>
> newtype IOToplevelT a = IOToplevelT { runIOToplevelT :: ReaderT Handle IO a
> } deriving (Monad, MonadReader Handle, MonadIO)
>
> instance Doohickey IOToplevelT where
> putRecord = liftIO . putStrLn
>
> foo' s k = do
> f <- liftIO $ openFile s AppendMode
> runReaderT (runIOToplevelT k) f
>
> --instance Toplevel IO where
> -- foo = foo'
>
> myDoohickey = do
> putRecord "foo"
> putRecord "bar"
>
> myOtherDoohickey = do
> putRecord "hello"
> putRecord "world"
> return True
>
>
>
> On Mon, Apr 13, 2009 at 7:55 PM, Jason Dusek <jason.dusek@gmail.com>wrote:
>
>> Copypasting and loading your code doesn't throw an error. Please,
>> pastebin an example that demonstrates the error.
>>
>> --
>> Jason Dusek
>>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/beginners/attachments/20090414/c3fd4db2/attachment-0001.htm
------------------------------
Message: 4
Date: Tue, 14 Apr 2009 14:40:25 -0700
From: Arthur Chan <baguasquirrel@gmail.com>
Subject: Re: [Haskell-beginners] How would you run a monad within
another monad?
To: Jason Dusek <jason.dusek@gmail.com>
Cc: beginners@haskell.org
Message-ID:
<74cabd9e0904141440p3ef435c1mba2e7323b196efcf@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"
I wonder how you would do this with type familes...
On Tue, Apr 14, 2009 at 2:39 PM, Arthur Chan <baguasquirrel@gmail.com>wrote:
> I seem to have finally solved my own problem, via something I learned from
> RWH. The solution is to use functional dependencies...
>
> The problem was that the compiler needed to know the relationship between
> Doohickeys and Toplevels, and I couldn't figure out how to tell it that...
>
>
>
> {-# LANGUAGE GeneralizedNewtypeDeriving, NoMonomorphismRestriction,
> FunctionalDependencies, MultiParamTypeClasses #-}
>
> import IO
> import Control.Monad.Reader
>
>
> class (Monad n) => Doohickey n where
> putRecord :: String -> n ()
>
> class (Monad m, Doohickey n) => Toplevel m n | m -> n where
> foo :: FilePath -> n a -> m a
>
> newtype IODoohickey a = IODoohickey { runIODoohickey :: ReaderT Handle IO a
> } deriving (Monad, MonadReader Handle, MonadIO)
>
> instance Doohickey IODoohickey where
> putRecord = liftIO . putStrLn
>
> instance Toplevel IO IODoohickey where
> foo s k = do
> f <- liftIO $ openFile s AppendMode
> runReaderT (runIODoohickey k) f
>
>
> myDoohickey = do
> putRecord "foo"
> putRecord "bar"
>
> myOtherDoohickey = do
> putRecord "hello"
> putRecord "world"
> return True
>
>
>
>
> On Tue, Apr 14, 2009 at 2:05 PM, Arthur Chan <baguasquirrel@gmail.com>wrote:
>
>> Here's my contrived example that threw the error.
>>
>> If you go into ghci, and do a `:t (foo' "blah" myDoohickey)`, you will get
>> the type signature "IO ()".
>> Doing the same for myOtherDoohickey returns "IO True"
>>
>> So you would think that you'd be able to uncomment the code that makes IO
>> an instance of Toplevel. foo' is a function that allows IO to run monadic
>> values of type Doohickey. But it doesn't work.
>>
>>
>> ---
>>
>> import IO
>> import Control.Monad.Reader
>>
>>
>> class (Monad n) => Doohickey n where
>> putRecord :: String -> n ()
>>
>> class (Monad m) => Toplevel m where
>> foo :: (Doohickey n) => FilePath -> n a -> m a
>>
>> newtype IOToplevelT a = IOToplevelT { runIOToplevelT :: ReaderT Handle IO
>> a } deriving (Monad, MonadReader Handle, MonadIO)
>>
>> instance Doohickey IOToplevelT where
>> putRecord = liftIO . putStrLn
>>
>> foo' s k = do
>> f <- liftIO $ openFile s AppendMode
>> runReaderT (runIOToplevelT k) f
>>
>> --instance Toplevel IO where
>> -- foo = foo'
>>
>> myDoohickey = do
>> putRecord "foo"
>> putRecord "bar"
>>
>> myOtherDoohickey = do
>> putRecord "hello"
>> putRecord "world"
>> return True
>>
>>
>>
>> On Mon, Apr 13, 2009 at 7:55 PM, Jason Dusek <jason.dusek@gmail.com>wrote:
>>
>>> Copypasting and loading your code doesn't throw an error. Please,
>>> pastebin an example that demonstrates the error.
>>>
>>> --
>>> Jason Dusek
>>>
>>
>>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/beginners/attachments/20090414/e56db9ad/attachment-0001.htm
------------------------------
Message: 5
Date: Tue, 14 Apr 2009 14:52:29 -0700
From: Jason Dusek <jason.dusek@gmail.com>
Subject: Re: [Haskell-beginners] How would you run a monad within
another monad?
To: Arthur Chan <baguasquirrel@gmail.com>
Cc: beginners@haskell.org
Message-ID:
<42784f260904141452j28f12881re823d3b6e3a4d1a5@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8
Congratulations.
--
Jason Dusek
------------------------------
_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners
End of Beginners Digest, Vol 10, Issue 14
*****************************************