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:  Monadic functions definitions for free monadic DSL
      (Sumit Raja)
   2.  Why QuickCheck's Char value is limited to ASCII  characters
      only? (Birmjin In)
   3. Re:  Monadic functions definitions for free       monadic DSL
      (鲍凯文)
   4. Re:  Why QuickCheck's Char value is limited to ASCII
      characters only? (Simon Jakobi)


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

Message: 1
Date: Fri, 14 Oct 2016 10:44:25 +1100
From: Sumit Raja <sumitr...@gmail.com>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] Monadic functions definitions for
        free monadic DSL
Message-ID:
        <CAD4nrSfNbxxm=T1_yu-a1ibfGa+Fa9u=fbtojy9byc0otfu...@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.
>
Imports are:

import Protolude
import Control.Monad.Free
import System.Socket
import System.Socket.Family.Inet
import System.Socket.Type.Stream
import System.Socket.Protocol.TCP
import Control.Exception ( bracket, catch )
import Data.ByteString as BS (uncons)

    decodeUtf8 :: ByteString -> Text
    encodeUtf8 :: Text -> ByteString

I'm using the socket library for the actual networking
(https://hackage.haskell.org/package/socket-0.6.0.1)

    type TCPSocket = Socket Inet Stream TCP
    receive :: Socket f t p -> Int -> MessageFlags -> IO ByteString Source
    send :: Socket f t p -> ByteString -> MessageFlags -> IO Int
    accept :: (Family f, Storable (SocketAddress f)) => Socket f t p
-> IO (Socket f t p, SocketAddress f)

If it helps the full source is at
https://bitbucket.org/sumitraja/network-free/src/a4fcbc74c9e178e81d8b10b60d912b32c542b661/src/Lib.hs.

Looking forward to your assistance.

Thanks

Sumit


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

Message: 2
Date: Fri, 14 Oct 2016 17:39:56 +0900
From: Birmjin In <yinbirm...@gmail.com>
To: beginners@haskell.org
Subject: [Haskell-beginners] Why QuickCheck's Char value is limited to
        ASCII   characters only?
Message-ID:
        <CACmhrqqDSnkD=sc-djczhvqez_veo8m8bvybqi4bslbsdfg...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi,

I found that the Arbitrary instance for the Char type generates only ASCII
values while Char type represent Unicode characters.

I can't figure out why it has such a limit. Not knowing this pitfall, one
can misjudge the test results.

Is this intended thing or just not being implemented yet?

Thanks.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20161014/831fc548/attachment-0001.html>

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

Message: 3
Date: Fri, 14 Oct 2016 02:22:40 -0700
From: 鲍凯文 <traqueofzi...@gmail.com>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] Monadic functions definitions for
        free    monadic DSL
Message-ID:
        <CAMjcG+EFJEYDbt+8xQ9kLnQ4xarPKBb0DyZj6wH=zycjry+...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

 Hi,

 Although I don't really understand the contents of your code, I think the
type error results from the fact that the 3rd field of the Accept
constructor has type (chan ->  next). In the context of 'acc', (chan :: a)
and (next :: NetworkActivity a Text).
I'm guessing the type error refers to when you used 'identity' (which I'm
hoping is just 'id' from Prelude); its type gets inferred to be
(NetworkActivity a Text -> NetworkActivity a text) instead of what it
expected (chan -> next, i.e. a ->NetworkActivity a Text). Whether or not
acc is the right type for your needs, I don't know.

Hope that helps,

toz

P.S. I don't know if it's good practice, but I usually use type variables
in data declarations consistently in other type signatures, e.g. since you
declared NetworkActivity using 'chan' and 'next', in 'clse', it'd make more
sense (to me) to use (clse :: chan -> Free (NetworkActivity chan) Text)
since it seems that 'chan' as a word has some extra connotations as opposed
to 'a', which when I read, I think it can be absolutely anything.

>
> ------------------------------
>
> 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=fRDuziWP0UtGsmX9RHGGaEYSB9ewMcQ@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
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20161014/794303aa/attachment-0001.html>

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

Message: 4
Date: Fri, 14 Oct 2016 13:12:54 +0200
From: Simon Jakobi <simon.jak...@googlemail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>,
        yinbirm...@gmail.com
Subject: Re: [Haskell-beginners] Why QuickCheck's Char value is
        limited to ASCII characters only?
Message-ID:
        <cagtp2sio2itmd+lrf8rikecavtyfurwyx9d214vuh6gx2sm...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

You'll be interested in the discussion on this PR:
https://github.com/nick8325/quickcheck/pull/119

2016-10-14 10:39 GMT+02:00 Birmjin In <yinbirm...@gmail.com>:

> Hi,
>
> I found that the Arbitrary instance for the Char type generates only
> ASCII values while Char type represent Unicode characters.
>
> I can't figure out why it has such a limit. Not knowing this pitfall, one
> can misjudge the test results.
>
> Is this intended thing or just not being implemented yet?
>
> Thanks.
>
> _______________________________________________
> 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/20161014/e834421d/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 11
******************************************

Reply via email to