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:  How to call popCnt64#? (John Ky)
   2. Re:  How to call popCnt64#? (Marcin Mrotek)
   3.  Need help groking the statement: expression1 in
      term:expression2 (Olumide)
   4.  Do IO actions *have* to be glued by the do       syntax? (Olumide)
   5. Re:  Need help groking the statement:     expression1 in
      term:expression2 (Quanyang Liu)
   6. Re:  Do IO actions *have* to be glued by the do   syntax?
      (Quanyang Liu)
   7. Re:  Do IO actions *have* to be glued by the do   syntax?
      (Daniel Wright)


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

Message: 1
Date: Mon, 21 Mar 2016 22:30:17 +0000
From: John Ky <newho...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] How to call popCnt64#?
Message-ID:
        <CAMB4o-BugzHt=7mWFLodApGA=opi28wdewj8exepz-nynua...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi Michael,

Yes, that did the trick.

Thanks!

-John

On Mon, 21 Mar 2016 at 01:13 Michael Snoyman <mich...@snoyman.com> wrote:

> Here's an example:
>
> {-# LANGUAGE MagicHash #-}
> import GHC.Prim
> import GHC.Types
> import Data.Word
>
> main :: IO ()
> main = do
>     let word = 5 :: Word
>         res =
>             case word of
>                 W# w -> W# (popCnt64# w)
>     print res
>
>
> On Sun, Mar 20, 2016 at 12:19 PM, John Ky <newho...@gmail.com> wrote:
>
>> Hello Haskellers,
>>
>> Does anyone know how to call popCnt64# from the GHC.Prim module?
>>
>> This was my failed attempt:
>>
>> ?> popCnt64# 1
>>
>>
>> <interactive>:14:11:
>> Couldn't match kind ?*? with ?#?
>> When matching types
>> a0 :: *
>> Word# :: #
>> Expected type: Integer -> Word#
>> Actual type: Integer -> a0
>> In the first argument of ?popCnt64#?, namely ?1?
>> In the expression: popCnt64# 1
>> In an equation for ?it?: it = popCnt64# 1
>>
>> -John
>>
>>
>> _______________________________________________
>> Beginners mailing list
>> Beginners@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>>
>>
> _______________________________________________
> 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/20160321/b9dcb05f/attachment-0001.html>

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

Message: 2
Date: Tue, 22 Mar 2016 08:25:15 +0100
From: Marcin Mrotek <marcin.jan.mro...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] How to call popCnt64#?
Message-ID:
        <CAJcfPzmrgQgu85FVMit0POEXLOJ43Lz_u1=ppezo2ee4nku...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi,

In general, the problem is that GHCi is attempting to call `show` on the
results of expressions you type in, but `show` (like any other polymorphic
function; though you can look into "levity polymorphism" if you want to
know more) can only accept values of types of kind * (boxed, lifted) - so
it can print Word, but not Word#.

If you wanted to stay in GHCi, you can do it like:

Prelude> import GHC.Prim
Prelude GHC.Prim> import GHC.Types
Prelude GHC.Prim GHC.Types> :set -XMagicHash
Prelude GHC.Prim GHC.Types> :t W#
W# :: Word# -> Word
Prelude GHC.Prim GHC.Types> :t popCnt64#
popCnt64# :: Word# -> Word#
Prelude GHC.Prim GHC.Types> let foo = (1 :: Word)
Prelude GHC.Prim GHC.Types> :set -XBangPatterns
Prelude GHC.Prim GHC.Types> let !(W# w) = foo in W# (popCnt64# w)
1

Best regards,
Marcin Mrotek
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20160322/3ecebfb8/attachment-0001.html>

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

Message: 3
Date: Tue, 22 Mar 2016 10:43:46 +0000
From: Olumide <50...@web.de>
To: beginners@haskell.org
Subject: [Haskell-beginners] Need help groking the statement:
        expression1 in  term:expression2
Message-ID: <56f121e2.2010...@web.de>
Content-Type: text/plain; charset=utf-8; format=flowed

Hello List,

I'd appreciate help understanding the second line of following block of 
code (from LYH, first line added for completeness),

http://learnyouahaskell.com/input-and-output#randomness
randoms' :: (RandomGen g, Random a) => g -> [a]
randoms' gen = let (value, newGen) = random gen in value:randoms' newGen

The part I'm really struggling with is random gen in value:randoms' newGen

Thanks,

- Olumide


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

Message: 4
Date: Tue, 22 Mar 2016 10:52:41 +0000
From: Olumide <50...@web.de>
To: beginners@haskell.org
Subject: [Haskell-beginners] Do IO actions *have* to be glued by the
        do      syntax?
Message-ID: <56f123f9.1050...@web.de>
Content-Type: text/plain; charset=utf-8; format=flowed

Hello List,

Do IO actions *have* to be glued by the do syntax? Many, if not all, the 
examples that I've come across in LYH seem to suggest so. And if so, why?

BTW, if possible I'd appreciate an explanation that does not resort to 
monads. I haven't studied them yet and I'm sure I'd struggle to 
understand any explanation that resorts to monads.

Thanks,

- Olumide


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

Message: 5
Date: Tue, 22 Mar 2016 18:57:56 +0800
From: Quanyang Liu <lqy...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Need help groking the statement:
        expression1 in term:expression2
Message-ID: <87egb2ixu3....@gmail.com>
Content-Type: text/plain

On Tue, Mar 22 2016 at 18:43:46 +0800, Olumide wrote:
> Hello List,
>
> I'd appreciate help understanding the second line of following block
> of code (from LYH, first line added for completeness),
>
> http://learnyouahaskell.com/input-and-output#randomness
> randoms' :: (RandomGen g, Random a) => g -> [a]
> randoms' gen = let (value, newGen) = random gen in value:randoms' newGen
>

It's equivalent to the following:
     randoms' gen = let (value, newGen) = random gen
                    in value:(randoms' newGen)

> The part I'm really struggling with is random gen in value:randoms' newGen
>
> Thanks,
>
> - Olumide

-- 
Thanks,
Quanyang


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

Message: 6
Date: Tue, 22 Mar 2016 19:06:21 +0800
From: Quanyang Liu <lqy...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Do IO actions *have* to be glued by
        the do  syntax?
Message-ID: <87a8lqixg2....@gmail.com>
Content-Type: text/plain

On Tue, Mar 22 2016 at 18:52:41 +0800, Olumide wrote:
> Hello List,
>
> Do IO actions *have* to be glued by the do syntax? Many, if not all,
> the examples that I've come across in LYH seem to suggest so. And if
> so, why?
>
> BTW, if possible I'd appreciate an explanation that does not resort to
> monads. I haven't studied them yet and I'm sure I'd struggle to
> understand any explanation that resorts to monads.
>

I think you should google that first... do blocks are just sugar...

> Thanks,
>
> - Olumide

-- 
Thanks,
Quanyang


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

Message: 7
Date: Tue, 22 Mar 2016 20:26:00 +0900
From: Daniel Wright <d...@dpwright.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Do IO actions *have* to be glued by
        the do  syntax?
Message-ID: <70b029b6-60b1-4b5d-91aa-9d38596c3...@dpwright.com>
Content-Type: text/plain;       charset=us-ascii

Hello Olumide,

The simple answer is "no", do syntax is an entirely optional piece of syntactic 
sugar that is just there to make the code easier to read in some cases.  But, 
IO actions do have to be glued together by something, and that something is the 
>>= operator (pronounced "bind").

>>= takes an IO action on the left, (let's use getLine, which reads a line from 
>>the user, for our example) and a function on the right which takes the result 
>>of that action and returns the next IO action to perform.  For example:

> getLine >>= (\line -> putStrLn line)

Here we can see the getLine action on the left.  The result of that is passed, 
through the mechanism provided by >>=, to the function on the right, which is a 
lambda function taking that line as a parameter and calling the action 
"putStrLn" to print it back out again.  This is equivalent to the following do 
notation:

> do
>   line <- getLine
>   putStrLn line

What if you want to string together more than two actions, though?  For 
example, say we wanted to get two lines and concatenation them in the output, 
like so:

> do
>   line1 <- getLine
>   line2 <- getLine
>   putStrLn (line1 ++ line2)

Since >>= can only take two parameters, what do we do?  Well, since the result 
of >>= is itself an IO action, we can use it again in the function on the 
right!  Like this:

> getLine >>= (\line1 -> (getLine >>= (\line2 -> putStrLn (line1 ++ line2))))

Now, this may be starting to look a little bit like lisp with all the 
parentheses!  In fact, because of the associativity of the >>= operator, the 
brackets are all optional, but they may be helpful for you to see what's going 
on.  Without the brackets, it looks like this:

> getLine >>= \line1 -> getLine >>= \line2 -> putStrLn (line1 ++ line2)

Which, if you were to lay it out a little differently, looks like this:

> getLine >>= \line1 ->
> getLine >>= \line2 ->
> putStrLn (line1 ++ line2)

...Starting to look a little more like the do syntax version above, isn't it?

What if you don't care about the value of the parameter?  Well, you could 
ignore it using the _ syntax like this:

> getLine >>= \_ -> putStrLn "42"

But Haskell actually provides an operator to save you the effort, called >>, so 
you can do:

> getLine >> putStrLn "42"

Do notation is a purely syntactic transformation that emits code using these 
operators.

Incidentally, the function on the right doesn't have to be a lambda function!  
Any function taking a value of whatever type is returned by the action on the 
left will do, and in the case of getLine/putStrLn they match!  So the first 
example could be rewritten:

> getLine >>= putStrLn

Which many would argue looks nicer than the equivalent do notation.

Hope that helps, sorry if it was a little verbose!

-Dani.

PS- I know you said not to mention monads, but if you followed everything above 
you're 90% of the way there anyway -- a monad is just a type class providing 
the >>= operator, and the "return" function, which takes a value and turns it 
into an action returning that value (at least in terms of the IO monad).

> On Mar 22, 2016, at 19:52, Olumide <50...@web.de> wrote:
> 
> Hello List,
> 
> Do IO actions *have* to be glued by the do syntax? Many, if not all, the 
> examples that I've come across in LYH seem to suggest so. And if so, why?
> 
> BTW, if possible I'd appreciate an explanation that does not resort to 
> monads. I haven't studied them yet and I'm sure I'd struggle to understand 
> any explanation that resorts to monads.
> 
> Thanks,
> 
> - Olumide
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


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

Subject: Digest Footer

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


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

End of Beginners Digest, Vol 93, Issue 15
*****************************************

Reply via email to