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.  Installing dph-examples in Mac OS X Version      10.7.2
      (mukesh tiwari)
   2. Re:  Spoj BWHEELER problem - input problem (Artur Tadra?a)
   3.  LYAH Control.Monad.Writer tell (TJ Takei)
   4. Re:  LYAH Control.Monad.Writer tell (David McBride)


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

Message: 1
Date: Sun, 15 Jan 2012 18:44:20 +0530
From: mukesh tiwari <mukeshtiwari.ii...@gmail.com>
Subject: [Haskell-beginners] Installing dph-examples in Mac OS X
        Version 10.7.2
To: beginners@haskell.org
Message-ID:
        <cafhzve9epjietuoggj_htxo3joytjlksii5ngqvjeg76jyb...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hello all
I am trying to install dph-examples on Mac OS X. First I have Xcode 4.2.1
and during the installation i got this <http://hpaste.org/56445> error


Installing library in
/Users/mukesh/.cabal/lib/dph-seq-0.5.1.1/ghc-7.2.1Registering
dph-seq-0.5.1.1...Downloading dph-examples-0.5.1.2...Configuring
dph-examples-0.5.1.2...Building dph-examples-0.5.1.2...Preprocessing
executable 'dph-sumsq-seq' for dph-examples-0.5.1.2...[1 of 5]
Compiling SumSquaresVectorised (
imaginary/SumSquares/dph/SumSquaresVectorised.hs,
dist/build/dph-sumsq-seq/dph-sumsq-seq-tmp/SumSquaresVectorised.o
)Error (fd:12: hGetLine: end of file)Warning: Couldn't figure out LLVM
version!Make sure you have installed LLVMghc: could not execute:
optcabal: Error: some packages failed to install:dph-examples-0.5.1.2
failed during the building phase. The exception was:ExitFailure 1


On 
stackoverflow<http://stackoverflow.com/questions/8864696/installing-dph-examples-in-mac-os-x-10-7-2>
, i got suggestion to remove Xcode 4.2 and install Xcode 3.2. After
installing Xcode 3.2  , I am still getting this error.

Macintosh:~ mukesh$ cabal install dph-examples
Resolving dependencies...
Configuring dph-examples-0.5.1.2...
Building dph-examples-0.5.1.2...
Preprocessing executable 'dph-sumsq-seq' for dph-examples-0.5.1.2...
[1 of 5] Compiling SumSquaresVectorised (
imaginary/SumSquares/dph/SumSquaresVectorised.hs,
dist/build/dph-sumsq-seq/dph-sumsq-seq-tmp/SumSquaresVectorised.o )
Error (fd:11: hGetLine: end of file)
Warning: Couldn't figure out LLVM version!
Make sure you have installed LLVM
ghc: could not execute: opt
cabal: Error: some packages failed to install:
dph-examples-0.5.1.2 failed during the building phase. The exception was:
ExitFailure 1

Macintosh:~ mukesh$ uname -a
Darwin Macintosh 11.2.0 Darwin Kernel Version 11.2.0: Tue Aug  9 20:56:15
PDT 2011; root:xnu-1699.24.8~1/RELEASE_I386 i386

Macintosh:~ mukesh$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 7.2.1

Xcode 3.2 ( 64 bit )

Could some one please tell me how to resolve this issue.
Regards
Mukesh Tiwari
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120115/b25d943e/attachment-0001.htm>

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

Message: 2
Date: Sun, 15 Jan 2012 16:08:06 +0100
From: Artur Tadra?a <artur.tadr...@gmail.com>
Subject: Re: [Haskell-beginners] Spoj BWHEELER problem - input problem
To: beginners@haskell.org
Message-ID:
        <CA+U-+Kijw=OSpSBZoPE=sx7mhx7nag4-zdu9f4hl9mhmhok...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-2"

Thanks for help David! It was indeed really silly thing: encoding of end of
the line on Windows. BS.unlines does not remove CR from input ByteString.
In my case that was crucial.

Regards
Artur

W dniu 15 stycznia 2012 09:54 u?ytkownik David McBride
<toa...@gmail.com>napisa?:

> It works fine for me, whether compiled or interpretted.  Are you sure
> there isn't some residual files left from a previous compile that you
> are running?  Try rm *.o *.hi.  Or something more mundane, not saving
> the file, or running the wrong executable.
>
> 2012/1/14 Artur Tadra?a <artur.tadr...@gmail.com>:
> > Hello
> >
> > While learning Haskell I'm trying to solve some simple problems on
> spoj.pl
> > occasionally. Currently I'm working on:
> > http://www.spoj.pl/problems/BWHEELER/. I figured out how to solve it
> but I
> > have some problems with reading input (that's my guess)
> >
> > Here is my solution:
> >
> > import Data.List
> > import Data.Array
> > import qualified Data.ByteString.Lazy.Char8 as BS
> > import IO
> >
> > traverse :: Array Int (Char, Int) -> Int -> Int -> String -> String
> > traverse endings n k acc =
> >     let (c,i) = endings ! n
> >     in if k == 0
> >         then acc
> >         else traverse endings i (k-1) (c:acc)
> >
> > solve :: (Int, String) -> String
> > solve (n,w) =
> >     let l = length w
> >         endings = sort $ zip w [0..]
> >         endingsArray = array (0, l) (zip [0..] endings)
> >     in reverse $ traverse endingsArray (n-1) l ""
> >
> > parseCases :: [BS.ByteString] -> [(Int, String)]
> > parseCases (l:l':ls) =
> >     let n = readInt l
> >         w = BS.unpack l'
> >     in (n,w):parseCases ls
> > parseCases _ = []
> >
> > main :: IO ()
> > main = do
> >   ls <- BS.lines `fmap` (BS.readFile "input.txt")
> > --BS.getContents
> >   putStr $ unlines $ map solve $ parseCases ls
> >
> > readInt :: BS.ByteString -> Int
> > readInt x =
> >   case BS.readInt x of Just (i,_) -> i
> >                        Nothing    -> error ("Unparsable Int" ++ (show x))
> >
> >
> > The input.txt file contains following text:
> > 2
> > bacab
> > 3
> > rwlb
> > 11
> > baaabaaaabbbaba
> > 0
> >
> > When I compile and execute this code i get follwing output:
> > aaaaaa
> > lllll
> > bbb
> >
> > It's different  when compared to this in ghci ( this is what I expect):
> >  > map solve [(2,"bacab"), (3, "rwlb"), (11,"baaabaaaabbbaba")]
> > ["abcba","rbwl","baaabbbbaaaaaab"]
> >
> > Can you explain me what I'm doing wrong?
> > I appreciate any tips how to improve this code also.
> >
> > Thanks for help!
> > Artur Tadra?a
> >
> > _______________________________________________
> > 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/20120115/beb959e0/attachment-0001.htm>

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

Message: 3
Date: Sun, 15 Jan 2012 17:07:34 -0800
From: TJ Takei <tj.ta...@gmail.com>
Subject: [Haskell-beginners] LYAH Control.Monad.Writer tell
To: Beginners@haskell.org
Message-ID:
        <cagyeonxxwzk9j00sb-tca7qa-0gs5whqgzcrktr+fxc_73r...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi

I have a trouble to run an example of "Learn Your A Haskell.." Chap 13
below:

========
import Data.Monoid
--Don't import Control.Monad.Writer

newtype Writer w a = Writer { runWriter :: (a, w) }

instance (Monoid w) => Monad (Writer w) where
    return x = Writer (x, mempty)
    (Writer (x,v)) >>= f = let (Writer (y, v')) = f x in Writer (y, v
`mappend` v')

--Define tell
tell :: [String] -> Writer [String] Int
tell w = Writer (0, w)  -- what'sa hell "0" for ???!!!

logNumber :: Int -> Writer [String] Int
logNumber x = Writer (x, ["Got number: " ++ show x])

multWithLog :: Writer [String] Int
multWithLog = do
    a <- logNumber 3
    b <- logNumber 5
    tell ["Gonna multiply these two"]
    return (a*b)

main = putStrLn . show $ runWriter multWithLog
========

I changed two places to run it without error:
[1] Ambiguity error of Writer, uneless I comment out "import
Control.Monad.Writer", and
[2] Define tell function

My questions are:
Why does LYAH sample fail as is?
Do the changes above look reasonable?
I'm not certain about my "tell". Where is the correct instantiation of
"tell" included?

Thanks,
TJ
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120115/690996e6/attachment-0001.htm>

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

Message: 4
Date: Mon, 16 Jan 2012 02:52:36 -0500
From: David McBride <toa...@gmail.com>
Subject: Re: [Haskell-beginners] LYAH Control.Monad.Writer tell
To: TJ Takei <tj.ta...@gmail.com>
Cc: Beginners@haskell.org
Message-ID:
        <CAN+Tr408-evecjNyt3yQ0Or2QOpg5q+LXoENL9a+2=dz7wj...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Reading that chapter, he seemed to have veered off course at some
point.  He started having you implement your own simple writer type,
but he stopped short of actually making it usable, then he started
showing you how you would use the real writer class.  Unless I'm
mistaken, he also didn't tell you how to reimplement logNumber with
the real library, so of course the code didn't work.

So the tell class is part of the MonadWriter class, which he didn't
explain the point of (along with listen).  Tell just takes a list of
things and adds them to the list of things you have.  The reason why
his Writer class has a tuple, is that in addition to concatenating log
messages, when you do a return from runWriter, you will get a first
argument in a tuple.  That argument ends up being the last item that
was returned or the last value returned from any monad passed as an
argument into listen.

Why would it do that?  Well I don't think it is used very often (or
possibly at all), but originally the idea was that the writer monad
can encompass both the ability to track what has happened in a program
and also its final return value.  I'm having trouble thinking of a use
for it, perhaps returning a failure code from a compilation, as well
as the log of messages?  Generally if you wanted to keep state you
would use the state monad for something like that, which allows you to
query it as well as set it.

The actual running code that you would have at that point in the book would be:

import Data.Monoid
import Control.Monad.Writer

logNumber :: Int -> Writer [String] Int
logNumber x = do
  tell ["Got number: " ++ show x]
  return x

multWithLog :: Writer [String] Int
multWithLog = do
    a <- logNumber 3
    b <- logNumber 5
    tell ["Gonna multiply these two"]
    return (a*b)

main = putStrLn . show $ runWriter multWithLog

which returns
(15,["Got number: 3","Got number: 5","Gonna multiply these two"])

On Sun, Jan 15, 2012 at 8:07 PM, TJ Takei <tj.ta...@gmail.com> wrote:
> Hi
>
> I have a trouble to run an example of "Learn Your A Haskell.." Chap 13
> below:
>
> ========
> import Data.Monoid
> --Don't import Control.Monad.Writer
>
> newtype Writer w a = Writer { runWriter :: (a, w) }
>
> instance (Monoid w) => Monad (Writer w) where
> ? ? return x = Writer (x, mempty)
> ? ? (Writer (x,v)) >>= f = let (Writer (y, v')) = f x in Writer (y, v
> `mappend` v')
>
> --Define tell
> tell :: [String] -> Writer [String] Int
> tell w = Writer (0, w) ?-- what'sa hell "0" for ???!!!
>
> logNumber :: Int -> Writer [String] Int
> logNumber x = Writer (x, ["Got number: " ++ show x])
>
> multWithLog :: Writer [String] Int
> multWithLog = do
> ? ? a <- logNumber 3
> ? ? b <- logNumber 5
> ? ? tell ["Gonna multiply these two"]
> ? ? return (a*b)
>
> main = putStrLn . show $ runWriter multWithLog
> ========
>
> I changed two places to run it without error:
> [1] Ambiguity error of Writer, uneless I comment out "import
> Control.Monad.Writer", and
> [2] Define tell function
>
> My questions are:
> Why does LYAH sample fail as is?
> Do the changes above look reasonable?
> I'm not certain about my "tell". Where is the correct instantiation of
> "tell" included?
>
> Thanks,
> TJ
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



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

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


End of Beginners Digest, Vol 43, Issue 20
*****************************************

Reply via email to