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.  Read package name, version from .cabal file (Shakthi Kannan)
   2. Re:  Read package name, version from .cabal file (Michael Snoyman)
   3. Re:  What's the difference between those two solution?
      (Brent Yorgey)
   4. Re:  Pattern matching over functions (Ken KAWAMOTO)
   5. Re:  What's the difference between those two      solution?
      (Haisheng Wu)
   6.  How to remove some duplication from this code? (Peter Hall)
   7. Re:  Read package name, version from .cabal file (Shakthi Kannan)


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

Message: 1
Date: Tue, 13 Dec 2011 17:53:50 +0530
From: Shakthi Kannan <shakthim...@gmail.com>
Subject: [Haskell-beginners] Read package name, version from .cabal
        file
To: beginners@haskell.org
Message-ID:
        <CABG-yt0ubva3UiuPu5oQgDXkNgr=9wr+cr1oq3kwdu1wlze...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

Hi,

I am trying to read a .cabal find and print the package name and
version. Here is the code snippet:

=== Code ===

getName :: FilePath -> IO ()
getName cabal = do
           gdesc <- readPackageDescription normal cabal
           let desc = flattenPackageDescription gdesc
               final = pkgName $ package desc
           putStrLn final

=== END ===

=== Output ===

    Couldn't match expected type `[Char]'
                with actual type `PackageName'

=== END ===

I see that the method 'package' from:

  
http://www.haskell.org/cabal/release/cabal-latest/doc/API/Cabal/Distribution-PackageDescription.html#t%3APackageDescription

allows me to return the PackageIdentifier. Using pkgName returns a PackageName.

  
http://www.haskell.org/cabal/release/cabal-latest/doc/API/Cabal/Distribution-Package.html#t%3APackageIdentifier

But, how can I obtain the string value from it?

Appreciate any help in this regard.

Thanks!

SK

-- 
Shakthi Kannan
http://www.shakthimaan.com



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

Message: 2
Date: Tue, 13 Dec 2011 14:27:43 +0200
From: Michael Snoyman <mich...@snoyman.com>
Subject: Re: [Haskell-beginners] Read package name, version from
        .cabal file
To: Shakthi Kannan <shakthim...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <caka2jg+b-qnn6ffgc1cewrffntxb3upa9ci6ce5bojhd8gh...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On Tue, Dec 13, 2011 at 2:23 PM, Shakthi Kannan <shakthim...@gmail.com> wrote:
> Hi,
>
> I am trying to read a .cabal find and print the package name and
> version. Here is the code snippet:
>
> === Code ===
>
> getName :: FilePath -> IO ()
> getName cabal = do
> ? ? ? ? ? gdesc <- readPackageDescription normal cabal
> ? ? ? ? ? let desc = flattenPackageDescription gdesc
> ? ? ? ? ? ? ? final = pkgName $ package desc
> ? ? ? ? ? putStrLn final
>
> === END ===
>
> === Output ===
>
> ? ?Couldn't match expected type `[Char]'
> ? ? ? ? ? ? ? ?with actual type `PackageName'
>
> === END ===
>
> I see that the method 'package' from:
>
> ?http://www.haskell.org/cabal/release/cabal-latest/doc/API/Cabal/Distribution-PackageDescription.html#t%3APackageDescription
>
> allows me to return the PackageIdentifier. Using pkgName returns a 
> PackageName.
>
> ?http://www.haskell.org/cabal/release/cabal-latest/doc/API/Cabal/Distribution-Package.html#t%3APackageIdentifier
>
> But, how can I obtain the string value from it?
>
> Appreciate any help in this regard.
>
> Thanks!
>
> SK
>
> --
> Shakthi Kannan
> http://www.shakthimaan.com
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners

You need to use pattern patching, e.g.:

let PackageName str = pkgName $ ...

HTH,
Michael



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

Message: 3
Date: Tue, 13 Dec 2011 07:37:09 -0500
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] What's the difference between those
        two solution?
To: beginners@haskell.org
Message-ID: <20111213123709.ga1...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Tue, Dec 13, 2011 at 11:49:03AM +0800, Haisheng Wu wrote:
> Hello,
>   I'm trying to solve Euler problem 104 with the solution "My Solution"
> below but it takes quite long time therefore I quite.
>   Then I turn to haskell wiki for better solution which work well but I can
> not figure out why it is better than mine.
>   I'm wondering whether more function call decrease the performance.
> 
>   Could you please help a little?
>   Thank you.
> 
> *-- | My Solution *
> main = print $ snd $ head $ dropWhile (\(x,y) -> (not . bothNinePandigit
> "123456789") x) (zip fibs [1..])
> 
> bothNinePandigit digits n = isFirstNinePandigit digits n &&
> isLastNinePandigit digits n
> 
> isLastNinePandigit  digits n = digits == sort (lastDigits 9 n)
> isFirstNinePandigit digits n = digits == sort (firstDigits 9 n)
> 
> firstDigits k n = take k (show n)
> lastDigits  k n = show (n `mod` 10^k)
> 
> fibs = 0 : 1 : zipWith (+) fibs (tail fibs)
> 
> *-- | From Haskell Wiki *
> fibs = 1 : 1 : zipWith (+) fibs (tail fibs)
> 
> isFibPan n =
>   let a = n `mod` 1000000000
>       b = sort (show a)
>       c = sort $ take 9 $ show n
>   in  b == "123456789" && c == "123456789"
> 
> ex_104 = snd $ head $ dropWhile (\(x,y) -> (not . isFibPan) x) (zip fibs
> [1..])

Aha, this is sneaky!  

Having a bunch of function calls should not make
a difference if you are compiling with -O2 (you are compiling with
-O2, aren't you)?  Nonetheless, even compiling with -O2 I was also
getting the results you mention -- the wiki version was pretty fast
(about 24s) whereas your version took more than 15 minutes.

So I ran your version with profiling to help figure out what was going
on.  I compiled with

  ghc --make -O2 -prof -auto-all -rtsopts PE104.hs

and then ran with

  ./PE104 +RTS -p -RTS

This causes a file "PE104.prof" to be written which has a bunch of
data on execution time and allocation broken down by function. The
results showed that 95% of the program's run time was being spent in
'firstDigits'.

And then it hit me -- the difference is due to the fact that your
version and the wiki version test the first digits and the last digits
in a different order!

'show' on integers is (relatively) very slow.  Your version first
tests the first 9 digits of the number -- note that computing the
first digits of a number requires computing all the digits, even the
ones that don't get shown.  Only if the first 9 digits are "123456789"
does your version go on to test the last nine digits (since (&&) is
lazy).  The wiki version, on the other hand, first tests the last 9
digits (much faster) and only if those are "123456789" does it bother
doing the (expensive) test for the first 9 digits.  Since only 112 out
of the first 329000 or so Fibonacci numbers end in the digits 1..9,
this makes a huge difference.

-Brent



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

Message: 4
Date: Tue, 13 Dec 2011 23:16:08 +0900
From: Ken KAWAMOTO <kentaro.kawam...@gmail.com>
Subject: Re: [Haskell-beginners] Pattern matching over functions
To: Brandon Allbery <allber...@gmail.com>, Giacomo Tesio
        <giac...@tesio.it>,     simplex.math.servi...@gmail.com,
        beginners@haskell.org,  Daniel Fischer
        <daniel.is.fisc...@googlemail.com>
Message-ID:
        <cagbyekoywolcdnuqsvct87bkj+yrthgfafrx-vbf+ayqktm...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Thank you all. Reading through this thread from the top again, I got it finally.
I was stupid and missing the context of the original question.

*if* we have that map function that can only incompletely distinguish
functions, then by using the map function we could tell "f" from "id
f", breaking referential transparency. (assuming it couldn't detect
the equality between "f" and "id f")

Regards,
Ken



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

Message: 5
Date: Tue, 13 Dec 2011 22:22:14 +0800
From: Haisheng Wu <fre...@gmail.com>
Subject: Re: [Haskell-beginners] What's the difference between those
        two     solution?
To: Brent Yorgey <byor...@seas.upenn.edu>
Cc: beginners@haskell.org
Message-ID:
        <cafj8lze6d+fw6axkcqjoxxkwhmb0wbzumos0-sr4eso4kc6...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi Brent,
  You are the man!

  After such a little refactoring, it solved the problem around 12s.

-Haisheng


On Tue, Dec 13, 2011 at 8:37 PM, Brent Yorgey <byor...@seas.upenn.edu>wrote:

> On Tue, Dec 13, 2011 at 11:49:03AM +0800, Haisheng Wu wrote:
> > Hello,
> >   I'm trying to solve Euler problem 104 with the solution "My Solution"
> > below but it takes quite long time therefore I quite.
> >   Then I turn to haskell wiki for better solution which work well but I
> can
> > not figure out why it is better than mine.
> >   I'm wondering whether more function call decrease the performance.
> >
> >   Could you please help a little?
> >   Thank you.
> >
> > *-- | My Solution *
> > main = print $ snd $ head $ dropWhile (\(x,y) -> (not . bothNinePandigit
> > "123456789") x) (zip fibs [1..])
> >
> > bothNinePandigit digits n = isFirstNinePandigit digits n &&
> > isLastNinePandigit digits n
> >
> > isLastNinePandigit  digits n = digits == sort (lastDigits 9 n)
> > isFirstNinePandigit digits n = digits == sort (firstDigits 9 n)
> >
> > firstDigits k n = take k (show n)
> > lastDigits  k n = show (n `mod` 10^k)
> >
> > fibs = 0 : 1 : zipWith (+) fibs (tail fibs)
> >
> > *-- | From Haskell Wiki *
> > fibs = 1 : 1 : zipWith (+) fibs (tail fibs)
> >
> > isFibPan n =
> >   let a = n `mod` 1000000000
> >       b = sort (show a)
> >       c = sort $ take 9 $ show n
> >   in  b == "123456789" && c == "123456789"
> >
> > ex_104 = snd $ head $ dropWhile (\(x,y) -> (not . isFibPan) x) (zip fibs
> > [1..])
>
> Aha, this is sneaky!
>
> Having a bunch of function calls should not make
> a difference if you are compiling with -O2 (you are compiling with
> -O2, aren't you)?  Nonetheless, even compiling with -O2 I was also
> getting the results you mention -- the wiki version was pretty fast
> (about 24s) whereas your version took more than 15 minutes.
>
> So I ran your version with profiling to help figure out what was going
> on.  I compiled with
>
>  ghc --make -O2 -prof -auto-all -rtsopts PE104.hs
>
> and then ran with
>
>  ./PE104 +RTS -p -RTS
>
> This causes a file "PE104.prof" to be written which has a bunch of
> data on execution time and allocation broken down by function. The
> results showed that 95% of the program's run time was being spent in
> 'firstDigits'.
>
> And then it hit me -- the difference is due to the fact that your
> version and the wiki version test the first digits and the last digits
> in a different order!
>
> 'show' on integers is (relatively) very slow.  Your version first
> tests the first 9 digits of the number -- note that computing the
> first digits of a number requires computing all the digits, even the
> ones that don't get shown.  Only if the first 9 digits are "123456789"
> does your version go on to test the last nine digits (since (&&) is
> lazy).  The wiki version, on the other hand, first tests the last 9
> digits (much faster) and only if those are "123456789" does it bother
> doing the (expensive) test for the first 9 digits.  Since only 112 out
> of the first 329000 or so Fibonacci numbers end in the digits 1..9,
> this makes a huge difference.
>
> -Brent
>
> _______________________________________________
> 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/20111213/e0719bbf/attachment-0001.htm>

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

Message: 6
Date: Tue, 13 Dec 2011 21:40:13 +0000
From: Peter Hall <peter.h...@memorphic.com>
Subject: [Haskell-beginners] How to remove some duplication from this
        code?
To: beginners@haskell.org
Message-ID:
        <CAA6hAk4VMTjFG2bxfcZEpOg=X--=qcp3wZY8DxdqwXj=kmq...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

I'm following this article about GADTs
[http://en.wikibooks.org/wiki/Haskell/GADT] and it suggests, as an
exercise, to handle invalid trees at runtime, without GADTs, when
evaluating a simple arithmetic syntax tree. My attempt is below.

It seems to work, but I could do with some feedback, as it isn't quite
satisfactory. It feels like I should be able to remove some of the
duplicated code in the eval function, and also in evalIntExpr and
evalBoolExpr, which are identical except for having Left and Right
reversed.

Thanks,

Peter


-------- Arithmetic.hs

module Arithmetic where
import Data.Maybe

data Expr = I Int
    | B Bool
    | Add Expr Expr
    | Mult Expr Expr
    | Eq Expr Expr

eval :: Expr -> Maybe (Either Bool Int)
eval (B b) = return $ Left b
eval (I i) = return $ Right i
eval (Mult e1 e2) = do
    a1 <- evalIntExpr e1
    a2 <- evalIntExpr e2
    return $ Right $ a1 * a2
eval (Add e1 e2) = do
    a1 <- evalIntExpr e1
    a2 <- evalIntExpr e2
    return $ Right $ a1 + a2
eval (Eq e1 e2) = do
    a1 <- evalIntExpr e1
    a2 <- evalIntExpr e2
    return $ Left $ a1 == a2


evalIntExpr :: Expr -> Maybe Int
evalIntExpr e = eval e >>= unwrap
        where
            unwrap (Right x) = Just x
            unwrap (Left x) = Nothing


evalBoolExpr :: Expr -> Maybe Bool
evalBoolExpr e = eval e >>= unwrap
        where
            unwrap (Left x) = Just x
            unwrap (Right x) = Nothing



------- Main.hs

module Main (
    main
) where

import Arithmetic
import Data.Maybe
import Data.Either

test :: Expr
test = Eq
        (Mult
            (Add
                (I 1)
                (I 2)
            )
            (I 5)
        )
        (I 15)

main :: IO ()
main = do
    putStrLn $ case eval test of
        Nothing -> "Invalid expression"
        Just (Left x) -> show x
        Just (Right x) -> show x



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

Message: 7
Date: Wed, 14 Dec 2011 11:06:25 +0530
From: Shakthi Kannan <shakthim...@gmail.com>
Subject: Re: [Haskell-beginners] Read package name, version from
        .cabal file
To: Michael Snoyman <mich...@snoyman.com>
Cc: beginners@haskell.org
Message-ID:
        <cabg-yt2urdk8d-rt9elts-g4rjgbb0lntvb3ty1exuer1bg...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

Hi Michael,

--- On Tue, Dec 13, 2011 at 5:57 PM, Michael Snoyman
<mich...@snoyman.com> wrote:
| You need to use pattern patching, e.g.:
|
| let PackageName str = pkgName $ ...
\--

Thank you. That worked!

SK

-- 
Shakthi Kannan
http://www.shakthimaan.com



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

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


End of Beginners Digest, Vol 42, Issue 19
*****************************************

Reply via email to