Send Beginners mailing list submissions to
[email protected]
To subscribe or unsubscribe via the World Wide Web, visit
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
[email protected]
You can reach the person managing the list at
[email protected]
When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."
Today's Topics:
1. What should be inside the Monad or MonadTrans's type
declaration? --Bound library question2. (Anthony Lee)
2. Re: What should be inside the Monad or MonadTrans's type
declaration? --Bound library question2. (David McBride)
----------------------------------------------------------------------
Message: 1
Date: Sun, 19 Aug 2018 16:31:57 -0400
From: Anthony Lee <[email protected]>
To: [email protected]
Subject: [Haskell-beginners] What should be inside the Monad or
MonadTrans's type declaration? --Bound library question2.
Message-ID:
<CA+pBo5F5RJpBCPp47q9K6NjJ+8qP6b-J3SYyMhS=ex8iprf...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"
Hi,
In Scope.hs there is one instance of Monad and one instance of MonadTrans
for Scope,
For the Monad instance, it is defined like this: Monad (Scope b f);
For the MonadTrans instance, it is like this: MonadTrans (Scope b);
Does it mean:
In ">>=" the e represents (a) of (Scope b f a)?
In lift function the m represents (f a) of (Scope b f a)?
https://github.com/ekmett/bound/blob/master/src/Bound/Scope.hs
========================Scope.hs================================
instance Monad f => Monad (Scope b f) where
#if !MIN_VERSION_base(4,8,0)
return a = Scope (return (F (return a)))
{-# INLINE return #-}
#endif
Scope e >>= f = Scope $ e >>= \v -> case v of
B b -> return (B b)
F ea -> ea >>= unscope . f
{-# INLINE (>>=) #-}
instance MonadTrans (Scope b) where
lift m = Scope (return (F m))
{-# INLINE lift #-}
-------------- next part --------------
An HTML attachment was scrubbed...
URL:
<http://mail.haskell.org/pipermail/beginners/attachments/20180819/c8fdfb22/attachment-0001.html>
------------------------------
Message: 2
Date: Sun, 19 Aug 2018 17:20:05 -0400
From: David McBride <[email protected]>
To: The Haskell-Beginners Mailing List - Discussion of primarily
beginner-level topics related to Haskell <[email protected]>
Subject: Re: [Haskell-beginners] What should be inside the Monad or
MonadTrans's type declaration? --Bound library question2.
Message-ID:
<CAN+Tr43zYzQf5TUctHj+yMazZGQi1QOuXzp8GBt8-E+0=zr...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"
When you are defining a class, the actual type that the class will accept
can be further restricted. For example
:i Num
class Num a where
is shorthand for
class Num (a :: *) where
When you see the *, you should say in your head the word "type". Off
topic, but In fact in future ghc releases, you will stop using * and use
the Type type in its place, because it is clearer. So any Num instances
require a single Type to be complete.
That means that only types that can be an instance of Num must have a kind
*. Things that have that type are plain types that don't have extra
variables, such as Int, (), and Char. If you tried to make Maybe an
instance of Num it just wouldn't work.
Monad takes a different type
:i Monad
class Applicative m => Monad (m :: * -> *) where
It says that the only Monad instances take a Type and return a Type. For
example Maybe takes a * and returns a *. That means you can apply Int, (),
and Char to Maybe and you will get back a complete Type (ie. Maybe Int).
So while Maybe can't be a num, Maybe Int absolutely can be an instance of
Num. Other types that can be Monads - IO, [] (list) for example.
MonadTrans is even more involed
class MonadTrans (t :: (* -> *) -> * -> *) where
So, in this case it takes a type that is like Maybe or IO, and then also
takes another that is like Int or Char. The standard example is StateT.
newtype StateT s (m :: * -> *) a
instance [safe] MonadTrans (StateT s)
So you can see how the types fit together. MonadTrans requires a type that
has the right shape, and StateT s without the extra paramters fits
perfectly.
So when you have a
newtype Scope b f a = Scope { unscope :: f (Var b (f a)) }
You can see that if a is a monomorphic type like Char or Int, then f has
to be something like Maybe [], or IO, or Maybe. So you can see how Scope
fits into both Monad and MonadTrans.
instance Monad f => Monad (Scope b f) where
instance MonadTrans (Scope b) where
Hopefully this gives you some intuition on how it works?
On Sun, Aug 19, 2018 at 4:31 PM, Anthony Lee <[email protected]> wrote:
> Hi,
> In Scope.hs there is one instance of Monad and one instance of MonadTrans
> for Scope,
> For the Monad instance, it is defined like this: Monad (Scope b f);
> For the MonadTrans instance, it is like this: MonadTrans (Scope b);
> Does it mean:
> In ">>=" the e represents (a) of (Scope b f a)?
> In lift function the m represents (f a) of (Scope b f a)?
>
> https://github.com/ekmett/bound/blob/master/src/Bound/Scope.hs
> ========================Scope.hs================================
> instance Monad f => Monad (Scope b f) where
> #if !MIN_VERSION_base(4,8,0)
> return a = Scope (return (F (return a)))
> {-# INLINE return #-}
> #endif
> Scope e >>= f = Scope $ e >>= \v -> case v of
> B b -> return (B b)
> F ea -> ea >>= unscope . f
> {-# INLINE (>>=) #-}
>
> instance MonadTrans (Scope b) where
> lift m = Scope (return (F m))
> {-# INLINE lift #-}
>
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL:
<http://mail.haskell.org/pipermail/beginners/attachments/20180819/b14d72c7/attachment-0001.html>
------------------------------
Subject: Digest Footer
_______________________________________________
Beginners mailing list
[email protected]
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
------------------------------
End of Beginners Digest, Vol 122, Issue 10
******************************************