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:  Using scanl for Fibonacci sequence (Apoorv Ingle)
   2.  Monadic functions definitions for free monadic   DSL (Sumit Raja)
   3. Re:  Monadic functions definitions for free monadic DSL
      (David McBride)


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

Message: 1
Date: Wed, 12 Oct 2016 17:24:22 -0500
From: Apoorv Ingle <apoorv.in...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Using scanl for Fibonacci sequence
Message-ID: <e7e07b42-cee4-4618-81fa-419dfe2da...@gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi Boon,

I guess it is difficult to comprehend what scanl exactly does here.
If you see the definition of scanl from hackage 
<http://hackage.haskell.org/package/base-4.9.0.0/docs/Prelude.html#v:scanl>

scanl :: (b -> a -> b) -> b -> [a] -> [b]
scanl is similar to foldl, but returns a list of successive reduced values from 
the left:
scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, …]

Think of calculating a running sum of the first 10 positive integers, it can be 
easily computed using scanl
λ> scanl (+) 0 [1..10]
[0,1,3,6,10,15,21,28,36,45,55]

For fibonacci, you calculate the nth number by adding n-1th number and n-2th 
number.
Lets try to unfold the definition of fibs

fibs  = 1 : scanl (+) 1 fibs

now first element of fibs is by definition, ofcourse
1 (say x1)

second element of fibs will be (the first element generated by scanl)
1 (i.e. z — say x2)

Third element of fibs will be calculated as (the second element generated by 
scanl)
z `f` x1 = 1 + 1 = 2 (say x3)

Fourth element will be (and also the 3rd element generated by scanl)
(z `f` x1) `f` x2 = (1 + 1) + 1 = 3 (say x4)

Fifth element will be
((z `f` x1) `f` x2) `f` x3 = ((1 + 1) + 1) + 2 = 5 (say x5)

and so on..

The elegance is of course achieved because of the lazy evaluation of the 
infinite list
Hope this makes it some what clear.

Regards, 
Apoorv

> On 11-Oct-2016, at 23:23, Lai Boon Hui <laibo...@gmail.com> wrote:
> 
> Hi All,
> 
> i am not very sure how this can work
> fibs = 1 : scanl (+) 1 fibs
> 
> Appreciate it if someone can guide me through by showing me a few steps of 
> the function evaluation
> 
> -- 
> Best Regards,
> Boon Hui
> _______________________________________________
> 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/20161012/33a59cd5/attachment-0001.html>

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

Message: 2
Date: Thu, 13 Oct 2016 13:15:43 +1100
From: Sumit Raja <sumitr...@gmail.com>
To: beginners@haskell.org
Subject: [Haskell-beginners] Monadic functions definitions for free
        monadic DSL
Message-ID:
        <CAD4nrSc3pZ-K72GBt3=frduziwp0utgsmx9rhggaeysb9ew...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

Hello,

I am trying to get my head around free monads by developing a simple
network abstraction DSL.
I've made good progress before adding TCP/IP semantics of accepting
connections. I'm now stuck with the creation of monadic functions.

I've defined the following:

    data NetworkActivity chan next = Accept chan next (chan -> next) |
            Send chan ByteString (Bool -> next) |
            Recv chan (ByteString -> next) |
            Close chan (() -> next)

    clse :: a -> Free (NetworkActivity a) Text
    clse chan = liftF (Close chan (const "Quit"))

    chatterServer :: a -> Free (NetworkActivity a) Text
    chatterServer svrchan = Free $ Accept svrchan (chatterServer
svrchan) chatterLoop

    chatterLoop :: a -> Free (NetworkActivity a) Text
    chatterLoop chan = Free $ Recv chan $ \bs -> case BS.uncons bs of
      Nothing -> clse chan
      Just x -> if bs == "Bye" then
          Free $ Close chan (\_ -> Pure "Quit")
        else
          Free (Send chan bs (\_ -> chatterLoop chan))

This works fine with the interpretTCP interpreter below accepting
multiple connections:

    interpretTCP :: Free (NetworkActivity TCPSocket) r -> IO r
    interpretTCP prg = case prg of
      Free (Accept serverSock svrLoop acceptProc) -> bracket (return serverSock)
        (\s-> interpretTCP (clse s))
        (\s-> do
          (ss, sa) <- accept s
          forkIO $ do
            _ <- interpretTCP (acceptProc ss)
            return ()
          interpretTCP svrLoop
        )
      Free (Recv sock g) -> do
        bs <- receive sock 4096 mempty
        putStrLn (decodeUtf8 bs)
        interpretTCP (g bs)
      Free (Close sock g) -> do
        close sock
        putStrLn ("Server bye!" :: Text)
        interpretTCP (g ())
      Pure r -> return r
      Free (Send sock pl g) -> do
        sent <- send sock pl mempty
        interpretTCP (g (sent > 0))

Where I'm stuck is defining the monadic version of accept and I'm
beginning to think my original
data type defined above may be wrong. As an initial step I've defined
the following:

    recv :: a -> Free (NetworkActivity a) ByteString
    recv chan = liftF (Recv chan identity)

    sendit :: a -> ByteString -> Free (NetworkActivity a) Bool
    sendit chan pl = liftF (Send chan pl identity)

    mchatterServer :: a -> Free (NetworkActivity a) Text
    mchatterServer chan = Free $ Accept chan (mchatterServer chan)
                                                                   (\s
-> return (identity s) >>= mchatterLoop)

mchatterServer works as is, the interpreter accepts multiple
connections. Similarly all good with recv and sendit.
I am struggling with converting the Accept in mchatterServer into a
function to use in the do syntax. The signature I think I should be
using is

    acc :: a -> NetworkActivity a Text -> Free (NetworkActivity a)
(NetworkActivity a Text)

What I can't figure out is why it can't follow the pattern of recv and
sendit above:

    acc chan next = liftF $ Accept chan next identity

Which results in error on identity (using Protolude):

    Expected type: a -> NetworkActivity a Text
    Actual type: NetworkActivity a Text -> NetworkActivity a Text

I can't really see how to get the types to line up and have now can't
see through the type fog. What am I missing in my reasoning about the
types?

Help much appreciated!

Thanks

Sumit


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

Message: 3
Date: Thu, 13 Oct 2016 08:09:59 -0400
From: David McBride <toa...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Monadic functions definitions for
        free monadic DSL
Message-ID:
        <can+tr43m+_wi9jcozb8ty7ozjx-wk0wf2psk5ngancv0krc...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

I would really like to help you, but without your imports, packages, etc,
it is really hard to interpret your program.  Like where does decodeUtf8
come from, or receive, or TCPSocket?  If they are functions you wrote, I
don't need their code, the types would be sufficient.

On Wed, Oct 12, 2016 at 10:15 PM, Sumit Raja <sumitr...@gmail.com> wrote:

> Hello,
>
> I am trying to get my head around free monads by developing a simple
> network abstraction DSL.
> I've made good progress before adding TCP/IP semantics of accepting
> connections. I'm now stuck with the creation of monadic functions.
>
> I've defined the following:
>
>     data NetworkActivity chan next = Accept chan next (chan -> next) |
>             Send chan ByteString (Bool -> next) |
>             Recv chan (ByteString -> next) |
>             Close chan (() -> next)
>
>     clse :: a -> Free (NetworkActivity a) Text
>     clse chan = liftF (Close chan (const "Quit"))
>
>     chatterServer :: a -> Free (NetworkActivity a) Text
>     chatterServer svrchan = Free $ Accept svrchan (chatterServer
> svrchan) chatterLoop
>
>     chatterLoop :: a -> Free (NetworkActivity a) Text
>     chatterLoop chan = Free $ Recv chan $ \bs -> case BS.uncons bs of
>       Nothing -> clse chan
>       Just x -> if bs == "Bye" then
>           Free $ Close chan (\_ -> Pure "Quit")
>         else
>           Free (Send chan bs (\_ -> chatterLoop chan))
>
> This works fine with the interpretTCP interpreter below accepting
> multiple connections:
>
>     interpretTCP :: Free (NetworkActivity TCPSocket) r -> IO r
>     interpretTCP prg = case prg of
>       Free (Accept serverSock svrLoop acceptProc) -> bracket (return
> serverSock)
>         (\s-> interpretTCP (clse s))
>         (\s-> do
>           (ss, sa) <- accept s
>           forkIO $ do
>             _ <- interpretTCP (acceptProc ss)
>             return ()
>           interpretTCP svrLoop
>         )
>       Free (Recv sock g) -> do
>         bs <- receive sock 4096 mempty
>         putStrLn (decodeUtf8 bs)
>         interpretTCP (g bs)
>       Free (Close sock g) -> do
>         close sock
>         putStrLn ("Server bye!" :: Text)
>         interpretTCP (g ())
>       Pure r -> return r
>       Free (Send sock pl g) -> do
>         sent <- send sock pl mempty
>         interpretTCP (g (sent > 0))
>
> Where I'm stuck is defining the monadic version of accept and I'm
> beginning to think my original
> data type defined above may be wrong. As an initial step I've defined
> the following:
>
>     recv :: a -> Free (NetworkActivity a) ByteString
>     recv chan = liftF (Recv chan identity)
>
>     sendit :: a -> ByteString -> Free (NetworkActivity a) Bool
>     sendit chan pl = liftF (Send chan pl identity)
>
>     mchatterServer :: a -> Free (NetworkActivity a) Text
>     mchatterServer chan = Free $ Accept chan (mchatterServer chan)
>                                                                    (\s
> -> return (identity s) >>= mchatterLoop)
>
> mchatterServer works as is, the interpreter accepts multiple
> connections. Similarly all good with recv and sendit.
> I am struggling with converting the Accept in mchatterServer into a
> function to use in the do syntax. The signature I think I should be
> using is
>
>     acc :: a -> NetworkActivity a Text -> Free (NetworkActivity a)
> (NetworkActivity a Text)
>
> What I can't figure out is why it can't follow the pattern of recv and
> sendit above:
>
>     acc chan next = liftF $ Accept chan next identity
>
> Which results in error on identity (using Protolude):
>
>     Expected type: a -> NetworkActivity a Text
>     Actual type: NetworkActivity a Text -> NetworkActivity a Text
>
> I can't really see how to get the types to line up and have now can't
> see through the type fog. What am I missing in my reasoning about the
> types?
>
> Help much appreciated!
>
> Thanks
>
> Sumit
> _______________________________________________
> 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/20161013/87816ab1/attachment-0001.html>

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

Subject: Digest Footer

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


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

End of Beginners Digest, Vol 100, Issue 10
******************************************

Reply via email to