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.  Comments on Map/Reduce Code (Thomas Bach)
   2.  arbitrary rank polymorphism and ghc language     pragmas (rickmurphy)
   3. Re:  [Haskell-cafe] arbitrary rank polymorphism and ghc
      language pragmas (rickmurphy)
   4.  Expert systems using Haskell (Ramesh Kumar)


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

Message: 1
Date: Thu, 5 Jul 2012 15:50:32 +0200
From: Thomas Bach <thb...@students.uni-mainz.de>
Subject: [Haskell-beginners] Comments on Map/Reduce Code
To: <beginners@haskell.org>
Message-ID: <87ipe2mi53....@roku.box>
Content-Type: text/plain; charset="utf-8"

Hello there,

I'm new to Haskell and want to learn it a bit while experimenting with
Hadoop's Map/Reduce programming model. So, I wanted to implement the
standard ?word counter? problem in Haskell. The problem is as follows:

We have several texts with words separated by white-space. We want to
count the occurrences of all words in all the texts (where ?but? and
?but,? can be seen as two different words). This is done in two
phases. In the Map phase a program gets a part of the text from stdout
and has to produce a "KEY\tVALUE" pair (that is, the key separated with
a tab to the value), which has to be passed to stdin. In our case we
simply produce "WordX\t1" for every word WordX. This list is sorted by
the key and later on fed as stdin to the reducer (the second phase). The
reducer now has to sum up all the occurrences we trivially counted in
the Map phase and put it as "WordX\tNumber" to stdout.

So, here is an example:
vince@roku:~/tmp echo "foo foo bar bar foo bar zoo bar foo" | runhaskell 
mapper.hs 
foo     1                                                                       
  
foo     1
bar     1
bar     1
foo     1
bar     1
zoo     1
bar     1
foo     1
vince@roku:~/tmp echo "foo foo bar bar foo bar zoo bar foo" | runhaskell 
mapper.hs | sort | runhaskell reducer.hs
bar     4
foo     4
zoo     1

And here is the code I've come up with:

vince@roku:~/tmp cat mapper.hs
import qualified Data.ByteString.Lazy.Char8 as C

postFix :: C.ByteString
postFix = C.pack "\t1"

formatter :: C.ByteString -> C.ByteString
formatter x = C.append x postFix

main :: IO ()
main = do
  contents <- fmap C.words C.getContents
  C.putStr . C.unlines $ map formatter contents


vince@roku:~/tmp cat reducer.hs
import qualified Data.ByteString.Lazy.Char8 as C
import qualified Data.List as L

tuppleize :: String -> (String, Int)
tuppleize line = (\xs -> (head xs, read (last xs))) $ words line

group :: Eq a => [(a, b)] -> [[(a, b)]]
group = L.groupBy (\x y -> fst x == fst y)

summation :: Num b => [(a, b)] -> (a, b)
summation (x:[]) = x
summation (x:xs) = (fst x, (snd x) + (snd (summation xs)))

formatter :: (String, Int) -> String
formatter = (\w -> (fst w ++ "\t" ++ show (snd w)))

main = do
  contents <- C.getContents
  putStr . unlines $ map formatter $ map summation $ group $ map tuppleize $ 
lines $ C.unpack contents

As already said, I'm a Haskell beginner. Could you provide some comments
on the code?

Thanks in advance,

       Thomas.



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

Message: 2
Date: Thu, 05 Jul 2012 11:18:00 -0400
From: rickmurphy <r...@rickmurphy.org>
Subject: [Haskell-beginners] arbitrary rank polymorphism and ghc
        language        pragmas
To: beginners <beginners@haskell.org>, haskell-c...@haskell.org
Message-ID: <1341501480.13998.36.camel@metho-laptop>
Content-Type: text/plain; charset="UTF-8"

Hi All:

I've been working through some details in these papers [1], [2] and
noticed a language pragma configuration that I hope you can confirm.

When using explicit foralls in a data constructor, it appears that GHC
7.4.2 requires Rank2Types in the Language pragma for what the papers
consider rank 1 types. 

Here's an example:

data T = TC (forall a b. a -> b -> a)

Am I correct, or is there another extension? The ExplicitForAll does not
appear to support rank 1 types in data constructors.

1. Practical Type Inference for Arbitrary-Rank Types.
2. A Direct Algorithm for Type Inference in the Rank 2 Fragment of the
Second-Order Lambda Calculus.

--
Rick




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

Message: 3
Date: Thu, 05 Jul 2012 13:17:12 -0400
From: rickmurphy <r...@rickmurphy.org>
Subject: Re: [Haskell-beginners] [Haskell-cafe] arbitrary rank
        polymorphism and ghc language pragmas
To: beginners <beginners@haskell.org>, haskell-c...@haskell.org
Message-ID: <1341508632.14924.3.camel@metho-laptop>
Content-Type: text/plain; charset="UTF-8"

Thanks Francesco. And I did verify that ExplicitForAll does in fact
allow Rank 1 Types in functions like the following ...

f :: (forall a. a -> a)

--
Rick

On Thu, 2012-07-05 at 16:28 +0100, Francesco Mazzoli wrote:
> At Thu, 05 Jul 2012 11:18:00 -0400,
> rickmurphy  wrote:
> > data T = TC (forall a b. a -> b -> a)
> 
> The type of `TC' will be `(forall a b. a -> b -> a) -> T', a Rank-2
> type.
> 
> --
> Francesco * Often in error, never in doubt
> 
> _______________________________________________
> Haskell-Cafe mailing list
> haskell-c...@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 





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

Message: 4
Date: Fri, 6 Jul 2012 01:25:53 -0700 (PDT)
From: Ramesh Kumar <rameshkumar.techdynam...@ymail.com>
Subject: [Haskell-beginners] Expert systems using Haskell
To: Haskell Beginners <Beginners@haskell.org>
Message-ID:
        <1341563153.10903.yahoomail...@web120206.mail.ne1.yahoo.com>
Content-Type: text/plain; charset="us-ascii"

Hello Folks,

1) Is it practical, if at all possible, to build rule-based expert systems 
using Haskell in comparison with Prolog?

2) Are there any good texts which could guide one to build expert systems using 
Haskell? 


I'm not really able to get clear answers googling.

Thanks very much.

Ramesh
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120706/eb5462ae/attachment-0001.htm>

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

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


End of Beginners Digest, Vol 49, Issue 7
****************************************

Reply via email to