Send Beginners mailing list submissions to
        beginners@haskell.org

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
        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. Re:  Need help understanding the tell function in the Monad
      Writer example in LYAH (Olumide)
   2. Re:  Ambiguous type variable prevents the constraint `(Ord
      t0)' from being solved. (Sylvain Henry)
   3.  Applicative for State (mike h)
   4. Re:  Applicative for State (Francesco Ariis)
   5. Re:  Applicative for State (mike h)
   6. Re:  Semigroup Instances (Theodore Lief Gannon)


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

Message: 1
Date: Mon, 6 Feb 2017 14:50:25 +0000
From: Olumide <50...@web.de>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Need help understanding the tell
        function in the Monad Writer example in LYAH
Message-ID: <de5d8587-2942-e47c-ceb2-474161180...@web.de>
Content-Type: text/plain; charset=utf-8; format=flowed

I think I get it now. tell() is defined in Control.Monad.Writer as:

     tell   :: w -> m ()
     tell w = writer ((),w)

*also* the result if the do notation is the last expression; and that's 
why the result of the computation will be lost (or disregarded) if 
tell() comes last.

- Olumide

On 03/02/2017 13:54, Francesco Ariis wrote:
>     a Writer do block can be read as a series of function which all have
> a "hidden parameter". This parameter is the pile of log messages.
> So you could as well substitute `tell ...` with
>
>     myTell :: String -> Writer [String] ()
>     myTell s = writer ((), [s])
>
> and then in the do block
>
>     -- ... receiving a list of log messages
>     c <- myTell "something" -- adding mine to the list (and binding
>                             -- a variable)
>     return (a*b) -- c is not being used!
>                  -- but the log message *is* there
>
> You can verify this yourself by adding `logNumber` statement in a do
> block and not using them in the last return statement. There too log
> will appear even if the bound variable is unused.
>
>     multWithLog :: Writer [String] Int
>     multWithLog = do
>           a <- logNumber 3
>           b <- logNumber 5 -- not used but logged
>         -- equivalent to: logNumber 5 (without b <-)
>           return (a)
>
>> Also, I don't understand the paragraph following the example:
>>
>> "It's important that return (a*b) is the last line, because the result of
>> the last line in a do expression is the result of the whole do expression.
>> Had we put tell as the last line, () would have been the result of this do
>> expression. We'd lose the result of the multiplication. However, the log
>> would be the same."
>
> `tell` is really not much different from `myTell`. Let's examine it again:
>
>     myTell :: String -> Writer [String] ()
>     myTell s = writer ((), [s])
>
> See the ()? It means it is *actually* returning something, a ().
> Remember that `return` isn't the same `return` as in some imperative
> languages: it only wraps a value in the monad we are using:
>
>     return 5
>     -- takes `5` and 'lifts' so it is usable inside the Writer
>     -- monad: `(5, [])`
>
> Putting a `tell "something"` after a return statement would overwrite
> that result (and gives us back a () instead).
>
> Did this help?
> My tip for really getting a Monad in your brain is to reimplement it.
> It is a very useful exercise.
> Also learning *not* to use the `do notation` helps too, as having
> operators instead of magic makes things easier to understand.
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>



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

Message: 2
Date: Mon, 6 Feb 2017 16:09:14 +0100
From: Sylvain Henry <sylv...@haskus.fr>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] Ambiguous type variable prevents the
        constraint `(Ord t0)' from being solved.
Message-ID: <52a6bdf3-95df-93c9-9140-0787ff05f...@haskus.fr>
Content-Type: text/plain; charset=utf-8; format=flowed

Try removing the lambda:

applyd f d x =
     let apply_listd l d x = [..]
     in let k =  5 -- hash x - todo
     [...]

Regards,
Sylvain

On 28/01/2017 21:09, Ivan Kush wrote:
> I get this error (full message at the end of the mail). How could I correct 
> my code?
>
>
> ===================
> Code:
> ===================
>
> module Intro where
>
> import Data.Bits --  for xor, .&.
>
> data Func a b
>      = Empty
>      | Leaf Int [(a, b)]
>      | Branch Int Int (Func a b) (Func a b)
>                  
> applyd =
>      let apply_listd l d x =
>                      case l of
>                          [] -> d x
>                          (a, b) : t ->
>                              let c = compare x a
>                              in if c == EQ then b
>                                  else if c == GT then apply_listd t d x
>                                  else d x
>                                      
>       in  \f d x ->
>          let k =  5 -- hash x - todo
>          in let look t =
>                  case t of
>                      Leaf h l | h == k ->
>                          apply_listd l d x
>                      Branch p b l r | (k `xor` p) .&. (b - 1) == 0 -> --  
> (Branch p b l r) | ((k xor p) .&. (b - 1)) == 0 ->
>                          look (if k .&. b == 0 then l else r)
>                      _ -> d x
>             in look f
>
>
>
> ===================
> Error:
> ===================
>
> Intro.hs:37:25: error:
>      * Ambiguous type variable `t0' arising from a use of `apply_listd'
>        prevents the constraint `(Ord t0)' from being solved.
>        Relevant bindings include
>          l :: [(t0, t)] (bound at Intro.hs:36:28)
>          t :: Func t0 t (bound at Intro.hs:34:21)
>          look :: Func t0 t -> t (bound at Intro.hs:34:16)
>          x :: t0 (bound at Intro.hs:32:15)
>          d :: t0 -> t (bound at Intro.hs:32:13)
>          f :: Func t0 t (bound at Intro.hs:32:11)
>          (Some bindings suppressed; use -fmax-relevant-binds=N or 
> -fno-max-relevant-binds)
>        Probable fix: use a type annotation to specify what `t0' should be.
>        These potential instances exist:
>          instance Ord Ordering -- Defined in `GHC.Classes'
>          instance Ord Integer
>            -- Defined in `integer-gmp-1.0.0.1:GHC.Integer.Type'
>          instance Ord a => Ord (Maybe a) -- Defined in `GHC.Base'
>          ...plus 22 others
>          ...plus five instances involving out-of-scope types
>          (use -fprint-potential-instances to see them all)
>      * In the expression: apply_listd l d x
>        In a case alternative: Leaf h l | h == k -> apply_listd l d x
>        In the expression:
>          case t of {
>            Leaf h l | h == k -> apply_listd l d x
>            Branch p b l r
>              | (k `xor` p) .&. (b - 1) == 0
>              -> look (if k .&. b == 0 then l else r)
>            _ -> d x }
>
>
> -- 
> Best wishes,
> Ivan Kush
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners



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

Message: 3
Date: Mon, 6 Feb 2017 19:40:12 +0000
From: mike h <mike_k_hough...@yahoo.co.uk>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: [Haskell-beginners] Applicative for State
Message-ID: <d49355af-31c2-4795-a610-7a547f9af...@yahoo.co.uk>
Content-Type: text/plain; charset=utf-8

Hi,

I have a State by another name, Stat,  just to experiment and learn.

newtype Stat s a = Stat { runStat :: s -> (a, s) }

instance Functor (Stat s) where
    fmap f (Stat g) = Stat $ \s -> (f a, s) where 
        (a, s) =  g s
              

instance Applicative (Stat s) where
    pure a = Stat $ \s -> (a, s)

    (Stat f) <*> (Stat g) = Stat $ \s -> (a, s) where 
        (a, s) = undefined

I really can’t get what the <*> in the Applicative should be!
I just do see how I ‘get the f out of the Stat’ and then apply it.

I’d be really grateful if someone would explain what it should be and the 
steps/reasoning needed to get there.


Many thanks

Mike



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

Message: 4
Date: Mon, 6 Feb 2017 21:15:29 +0100
From: Francesco Ariis <fa...@ariis.it>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] Applicative for State
Message-ID: <20170206201529.ga1...@casa.casa>
Content-Type: text/plain; charset=utf-8

On Mon, Feb 06, 2017 at 07:40:12PM +0000, mike h wrote:
> I have a State by another name, Stat,  just to experiment and learn.
> [...]
> I really can’t get what the <*> in the Applicative should be!
> I just do see how I ‘get the f out of the Stat’ and then apply it.
> 
> I’d be really grateful if someone would explain what it should be and
> the steps/reasoning needed to get there.

Hello Mike,

    when writing an instance, you always have to keep in mind: (a) the
signature of the function you are writing and (b) what the instance
is designed to do.

In our case, (<*>) is:

    (<*>) :: Applicative f => f (a -> b) -> f a -> f b

    -- which we could 'rewrite' as
    (<*>) ::  Stat s (a -> b) -> Stat s a -> Stat s b

so we grab the results, one being a function and the other a value,
and apply the first to the second.

(b) is "pass the state around in the background". Good, let's put this
in action:

    (Stat f) <*> (Stat g) = Stat $ \s ->
        let (h, s')  = f s     -- h is a function :: a -> b
            (a, s'') = g s'    -- state passing
            b        = h a in  -- the application
        (b, s'') -- we're not returning just the tuple, we're returning
                 -- even the bit before the 'let' statement

And that is that. Was this clear?


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

Message: 5
Date: Mon, 6 Feb 2017 23:35:31 +0000
From: mike h <mike_k_hough...@yahoo.co.uk>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Applicative for State
Message-ID: <cf95cc11-8cf3-4266-b080-9666b327c...@yahoo.co.uk>
Content-Type: text/plain; charset=utf-8

Thanks again Francesco.
Part of my problem was confusing the data and type constructors.
With your solution and my renaming of the data constructors it all became much 
clearer!

:)

Mike


> On 6 Feb 2017, at 20:15, Francesco Ariis <fa...@ariis.it> wrote:
> 
> On Mon, Feb 06, 2017 at 07:40:12PM +0000, mike h wrote:
>> I have a State by another name, Stat,  just to experiment and learn.
>> [...]
>> I really can’t get what the <*> in the Applicative should be!
>> I just do see how I ‘get the f out of the Stat’ and then apply it.
>> 
>> I’d be really grateful if someone would explain what it should be and
>> the steps/reasoning needed to get there.
> 
> Hello Mike,
> 
>    when writing an instance, you always have to keep in mind: (a) the
> signature of the function you are writing and (b) what the instance
> is designed to do.
> 
> In our case, (<*>) is:
> 
>    (<*>) :: Applicative f => f (a -> b) -> f a -> f b
> 
>    -- which we could 'rewrite' as
>    (<*>) ::  Stat s (a -> b) -> Stat s a -> Stat s b
> 
> so we grab the results, one being a function and the other a value,
> and apply the first to the second.
> 
> (b) is "pass the state around in the background". Good, let's put this
> in action:
> 
>    (Stat f) <*> (Stat g) = Stat $ \s ->
>        let (h, s')  = f s     -- h is a function :: a -> b
>            (a, s'') = g s'    -- state passing
>            b        = h a in  -- the application
>        (b, s'') -- we're not returning just the tuple, we're returning
>                 -- even the bit before the 'let' statement
> 
> And that is that. Was this clear?
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners



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

Message: 6
Date: Mon, 6 Feb 2017 15:56:33 -0800
From: Theodore Lief Gannon <tan...@gmail.com>
To: Atrudyjane <atrudyj...@protonmail.com>,  The Haskell-Beginners
        Mailing List - Discussion of primarily beginner-level topics related
        to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Semigroup Instances
Message-ID:
        <CAJoPsuAFrmcVm-t_m4fVcs75R2G=xqvafoqc_nvsdnl3oyb...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Gmail put you in spam.

If you haven't figured this out since you asked -- it's a matter of
confusing (IMO bad) variable names. Check the data definition:

data Validation a b
  = Failure a
  | Success b
  deriving (Eq, Show)

Failures are always type a, and successes are always type b. The type
variables used in the first line correspond to these. But in the
definitions of (<>), they are just local values. The instance could be
rewritten like so:

instance Semigroup a => Semigroup (Validation a b) where
  Success x <> Success y = Success x
  Failure x <> Success y = Success y
  Success x <> Failure y = Success x
  Failure x <> Failure y = Failure (x <> y)

On Thu, Jan 26, 2017 at 1:55 PM, Atrudyjane <atrudyj...@protonmail.com>
wrote:

> I'm currently studying semigroups and trying to figure out how to
> determine which type variables need a semigroup instance. Here are a couple
> of examples from Evan Cameron's github (https://github.com/leshow/
> haskell-programming-book/blob/master/src/Ch15ex.hs):
> (1)
> data Validation a b
>   = Failure a
>     | Success b
>     deriving (Eq, Show)
>
> instance Semigroup a => Semigroup (Validation a b) where
>   Success a <> Success b = Success a
>    Failure a <> Success b = Success b
>    Success a <> Failure b = Success a
>    Failure a <> Failure b = Failure (a <> b)
>
> * Why doesn't 'b' need an instance of semigroup?
> (2)
> newtype AccumulateRight a b = AccumulateRight (Validation a b) deriving (
> Eq, Show)
>
> instance Semigroup b => Semigroup (AccumulateRight a b) where
> AccumulateRight (Success a) <>AccumulateRight (Failure b) =AccumulateRight
> (Success a)
> AccumulateRight (Failure a) <>AccumulateRight (Success b) =AccumulateRight
> (Success b)
> AccumulateRight (Failure a) <>AccumulateRight (Failure b) =AccumulateRight
> (Failure a)
>
> AccumulateRight (Success a) <> AccumulateRight (Success b) =
> AccumulateRight (Success (a <> b))
>
> * Why doesn't 'a' need an instance of semigroup?
>
>
> Thank you,
> Andrea
>
>
> Sent with ProtonMail <https://protonmail.com> Secure Email.
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20170206/b9629a1d/attachment.html>

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

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


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

End of Beginners Digest, Vol 104, Issue 3
*****************************************

Reply via email to