Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/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.  import module with (..) (Miro Karpis)
   2. Re:  import module with (..) (Brandon Allbery)
   3. Re:  Merge Sort Stack Overflow (Bob Ippolito)
   4.  Exception: bind: resource busy (Address already  in use)
      (Miro Karpis)


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

Message: 1
Date: Mon, 16 Sep 2013 22:01:35 +0200
From: Miro Karpis <miroslav.kar...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <Beginners@haskell.org>
Subject: [Haskell-beginners] import module with (..)
Message-ID:
        <cajnnbxgexsbo++ny_pgmo9huxo7vfzsjfwp58zgskx144hp...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Please, what does mean the (..) brackets when we are importing a package?

For example:

import Network (listenOn, accept, *PortID(..)*, Socket)


cheers,
m.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20130916/f4b5c72f/attachment-0001.html>

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

Message: 2
Date: Mon, 16 Sep 2013 16:04:05 -0400
From: Brandon Allbery <allber...@gmail.com>
To: Miro Karpis <miroslav.kar...@gmail.com>,  The Haskell-Beginners
        Mailing List - Discussion of primarily beginner-level topics related
        to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] import module with (..)
Message-ID:
        <CAKFCL4WVn8-31hnwP9qPTY7dT659vMMKuy1A8uAfw8Z7r+gZ=q...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

On Mon, Sep 16, 2013 at 4:01 PM, Miro Karpis <miroslav.kar...@gmail.com>wrote:

> Please, what does mean the (..) brackets when we are importing a package?
>
> import Network (listenOn, accept, *PortID(..)*, Socket)
>

PortID is a type, for which you can list in parentheses the specific
constructors you want to import or .. for all of its constructors.

-- 
brandon s allbery kf8nh                               sine nomine associates
allber...@gmail.com                                  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonad        http://sinenomine.net
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20130916/476b5245/attachment-0001.html>

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

Message: 3
Date: Mon, 16 Sep 2013 13:24:33 -0700
From: Bob Ippolito <b...@redivi.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Merge Sort Stack Overflow
Message-ID:
        <CACwMPm8+MoRzZnWB0-Uz-midh7UfijFjK2eD=vG7APu=-cp...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

I an iterative solution works much better. Here's an example, using your
merge function.

mergeSort1 :: Ord a => [a] -> [a]
mergeSort1 = go . map (:[])
  where go [] = []
        go [xs] = xs
        go xss = go (mergePairs xss)
        mergePairs (xs:ys:pairs) = merge xs ys : mergePairs pairs
        mergePairs pairs = pairs

h> :!ghc -O2 Merge -fforce-recomp
[1 of 1] Compiling Merge            ( Merge.hs, Merge.o )
h> :m + Data.List
h> :load Merge
Ok, modules loaded: Merge.
h> :set +s
h> length $ let n = 1000000 in mergeSort [n, n-1 .. 1]
1000000
(5.15 secs, 2924212128 bytes)
h> length $ let n = 1000000 in mergeSort1 [n, n-1 .. 1]
1000000
(1.58 secs, 1027356744 bytes)
h> length $ let n = 1000000 in sort [n, n-1 .. 1]
1000000
(0.24 secs, 107481296 bytes)

The source to Data.List's sort is clever, you should give it a read:
http://www.haskell.org/ghc/docs/latest/html/libraries/base/src/Data-List.html#sort


On Mon, Sep 16, 2013 at 10:35 AM, Florian Lammel <m...@florianlammel.com>wrote:

> Hi,
>
> I've just started learning Haskell and am trying to implement some basic
> algorithms. My shot at merge sort looks like this:
>
> mergeSort :: Ord a => [a] -> [a]
> mergeSort [] = []
> mergeSort [x] = [x]
> mergeSort xs = merge (mergeSort as) (mergeSort bs)
>     where
>         (as, bs) = splitInHalf xs
>
> splitInHalf :: [a] -> ([a], [a])
> splitInHalf [] = ([], [])
> splitInHalf [x] = ([x], [])
> splitInHalf (x:y:xys) = (x:xs, y:ys)
>     where (xs, ys) = splitInHalf xys
>
> merge :: Ord a => [a] -> [a] -> [a]
> merge xs [] = xs
> merge [] ys = ys
> merge (x:xs) (y:ys) = if x < y
>                       then x:(merge xs (y:ys))
>                       else y:(merge ys (x:xs))
>
> As far as I can tell, my implementation is more or less the same as on
> rosetta code [0], literate programs [1] and several stack overflow
> questions [2][3].
>
> The algorithm works, but for large lists (for example, 500k random
> numbers), I get a stack overflow.
>
> So my question is: How can I change my code so that it works on larger
> inputs? Or, more generally, how can I write recursive algorithms in
> functional languages that require more nested function calls than fit in
> the stack?
>
> Regards
> Florian
>
> [0] http://rosettacode.org/wiki/Sorting_algorithms/Merge_sort#Haskell
> [1] http://en.literateprograms.org/Merge_sort_(Haskell)
> [2]
> http://stackoverflow.com/questions/7554226/haskell-merge-sort-sorting-words-and-numbers
> [3] http://stackoverflow.com/questions/1215432/merge-sort-in-haskell
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20130916/d322226a/attachment-0001.html>

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

Message: 4
Date: Tue, 17 Sep 2013 00:17:57 +0200
From: Miro Karpis <miroslav.kar...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <Beginners@haskell.org>
Subject: [Haskell-beginners] Exception: bind: resource busy (Address
        already in use)
Message-ID:
        <cajnnbxe4gqkwcj7pvarcu0hgi2zoj5prnvuhqiqn5z2fd1l...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi, I'm trying to work on following code below (code is a copy from
here<http://cogsandlevers.blogspot.no/2013/05/a-tcp-server-haskell-example.html>).
Problem is that when I close the server with ctrl+c and try to run it again
I get: *** Exception: bind: resource busy (Address already in use).

In documentation of listenOn is written: NOTE: To avoid the "Address
already in use" problems popped up several times on the GHC-Users mailing
list we set the
ReuseAddr<http://hackage.haskell.org/packages/archive/network/2.3.0.14/doc/html/Network-Socket.html#v:ReuseAddr>socket
option on the listening socket. If you don't want this behaviour, please
use the lower level
listen<http://hackage.haskell.org/packages/archive/network/2.3.0.14/doc/html/Network-Socket.html#v:listen>
instead.
Please how can I fix this? (ghci version 7.6.3)

cheers m.


import Network (listenOn, accept, PortID(..), Socket)
import System.IO (hSetBuffering, hGetLine, hPutStrLn, BufferMode(..),
Handle)

import Control.Concurrent (forkIO)

echoImpl :: Handle -> IO ()
echoImpl client = do
  line <- hGetLine client
  hPutStrLn client line
  echoImpl client

clientHandler :: Socket -> IO ()
clientHandler sock = do

  (client, _, _) <- accept sock
  hSetBuffering client NoBuffering
  forkIO $ echoImpl client
  clientHandler sock

felix :: IO ()
felix = do
   sock <- listenOn $ PortNumber 5002
   putStrLn $ "Echo server started .."
   clientHandler sock
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20130917/52a49aa3/attachment-0001.html>

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

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


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

End of Beginners Digest, Vol 63, Issue 22
*****************************************

Reply via email to