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
        [EMAIL PROTECTED]

You can reach the person managing the list at
        [EMAIL PROTECTED]

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  do not understand Semantics of Case Expressions  in report
      (Michael Mekhanoshin)
   2.  Weird compilation error while doing Euler        problems? (Ian Duncan)
   3. Re:  Weird compilation error while doing Euler    problems?
      (Brandon S. Allbery KF8NH)
   4. Re:  Weird compilation error while doing Euler    problems?
      (Daniel Fischer)
   5. Re:  do not understand Semantics of Case  Expressions in
      report (John Dorsey)
   6. Re:  do not understand Semantics of Case  Expressions in
      report (Michael Mekhanoshin)
   7.  what type is 'Val 9' when 'Val Int' a ctor for   'Expr e'? 
      (Larry Evans)


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

Message: 1
Date: Tue, 21 Oct 2008 00:17:56 +0600
From: "Michael Mekhanoshin" <[EMAIL PROTECTED]>
Subject: [Haskell-beginners] do not understand Semantics of Case
        Expressions     in report
To: Beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=UTF-8

at http://www.haskell.org/onlinereport/exps.html

on figure Figure 4 (Semantics of Case Expressions, Part 2)

one can see:

(m)      case  v  of {  K  { f1  =  p1  ,  f2  =  p2  ,  ... } ->  e ; _ -
>  e'  }
       =  case e' of {
          y ->
           case  v  of {
             K  {  f1  =  p1  } ->
                   case  v  of { K  { f2  =  p2  ,  ...  } ->  e ; _ ->
y  };
                   _ ->  y  }}
       where f1, f2, ... are fields of constructor K; y is a new variable

(In Figures 3.1--3.2: e, e' and ei are expressions; g and gi are
boolean-valued expressions; p and pi are patterns; v, x, and xi are
variables; K and K' are algebraic datatype (data) constructors
(including tuple constructors); and N is a newtype constructor.)


I'm totally confused with this identity. Especialy with " =  case e'".
Can anyone explain a little what does this rule stand, please?
It is better to see some example.

Respect,
Michael


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

Message: 2
Date: Mon, 20 Oct 2008 22:36:03 -0500
From: "Ian Duncan" <[EMAIL PROTECTED]>
Subject: [Haskell-beginners] Weird compilation error while doing Euler
        problems?
To: beginners@haskell.org
Message-ID:
        <[EMAIL PROTECTED]>
Content-Type: text/plain; charset="iso-8859-1"

'm trying to compile my file that has my Euler problems in it to output the
solution to problem four, but I'm getting a compile error. Here's my .hs
file:
-------------------------
module Euler1 where
import Data.List
import Data.Ord

main = mapM_ putStrLn problem4

problem1 = foldl1' (+) $ nub $ (takeWhile (< 1000) [3,6..] ++ takeWhile (<
1000) [5,10..])
problem2 = sum $ takeWhile (<= 4000000) [x | x <- fibs, even x]
where fibs = unfoldr (\(a,b) -> Just (a,(b,a+b))) (0,1)

problem3 z = maximumBy compare (filter (\x -> z `mod` x == 0) (takeWhile (<=
ceiling (sqrt (fromIntegral z))) primes))

problem4 = nub [ show $ y * z | y <- [100..999], z <- [100..999], show (y*z)
== reverse (show $ y*z)]

prime p = p `elem` primes

primes = small ++ large
where
 1:p:candidates = roll $ mkWheel small
 small          = [2,3,5,7]
 large          = p : filter isPrime candidates
 isPrime n      = all (not . divides n) $ takeWhile (\p -> p*p <= n) large
 divides n p    = n `mod` p == 0
mkWheel ds = foldl nextSize w0 ds
nextSize (Wheel n rs) p =
 Wheel (p*n) [r' | k <- [0..(p-1)], r <- rs, let r' = n*k+r, r' `mod` p /=
0]
w0 = Wheel 1 [1]
roll (Wheel n rs) = [n*k+r | k <- [0..], r <- rs]
data Wheel = Wheel Integer [Integer]
------------------------

Here's my output when I try to compile:

ian$ ghc ~/Documents/eulerProblem1.hs -o test
Undefined symbols:
 "___stginit_ZCMain", referenced from:
     ___stginit_ZCMain$non_lazy_ptr in libHSrts.a(Main.o)
 "_ZCMain_main_closure", referenced from:
     _ZCMain_main_closure$non_lazy_ptr in libHSrts.a(Main.o)
ld: symbol(s) not found
collect2: ld returned 1 exit status

What's going on? I'm running GHC 6.8.3, if that helps.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20081020/b8085c7d/attachment-0001.htm

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

Message: 3
Date: Mon, 20 Oct 2008 23:46:50 -0400
From: "Brandon S. Allbery KF8NH" <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] Weird compilation error while doing
        Euler   problems?
To: "Ian Duncan" <[EMAIL PROTECTED]>
Cc: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset="us-ascii"

On 2008 Oct 20, at 23:36, Ian Duncan wrote:
> 'm trying to compile my file that has my Euler problems in it to  
> output the solution to problem four, but I'm getting a compile  
> error. Here's my .hs file:
> -------------------------
> module Euler1 where

If you're not using the standard module Main, you need to tell ghc  
which module you put your main function in:

     ghc --main-is Euler1 ...

-- 
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon university    KF8NH


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20081020/d5ea5eb7/attachment-0001.htm

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

Message: 4
Date: Tue, 21 Oct 2008 05:55:41 +0200
From: Daniel Fischer <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] Weird compilation error while doing
        Euler   problems?
To: "Ian Duncan" <[EMAIL PROTECTED]>, beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain;  charset="iso-8859-1"

Am Dienstag, 21. Oktober 2008 05:36 schrieb Ian Duncan:
> 'm trying to compile my file that has my Euler problems in it to output the
> solution to problem four, but I'm getting a compile error. Here's my .hs
> file:
> -------------------------
> module Euler1 where
> import Data.List
> import Data.Ord
>
> main = mapM_ putStrLn problem4
>
> problem1 = foldl1' (+) $ nub $ (takeWhile (< 1000) [3,6..] ++ takeWhile (<
> 1000) [5,10..])
> problem2 = sum $ takeWhile (<= 4000000) [x | x <- fibs, even x]
> where fibs = unfoldr (\(a,b) -> Just (a,(b,a+b))) (0,1)
>
> problem3 z = maximumBy compare (filter (\x -> z `mod` x == 0) (takeWhile
> (<= ceiling (sqrt (fromIntegral z))) primes))
>
> problem4 = nub [ show $ y * z | y <- [100..999], z <- [100..999], show
> (y*z) == reverse (show $ y*z)]
>
> prime p = p `elem` primes
>
> primes = small ++ large
> where
>  1:p:candidates = roll $ mkWheel small
>  small          = [2,3,5,7]
>  large          = p : filter isPrime candidates
>  isPrime n      = all (not . divides n) $ takeWhile (\p -> p*p <= n) large
>  divides n p    = n `mod` p == 0
> mkWheel ds = foldl nextSize w0 ds
> nextSize (Wheel n rs) p =
>  Wheel (p*n) [r' | k <- [0..(p-1)], r <- rs, let r' = n*k+r, r' `mod` p /=
> 0]
> w0 = Wheel 1 [1]
> roll (Wheel n rs) = [n*k+r | k <- [0..], r <- rs]
> data Wheel = Wheel Integer [Integer]
> ------------------------
>
> Here's my output when I try to compile:
>
> ian$ ghc ~/Documents/eulerProblem1.hs -o test
> Undefined symbols:
>  "___stginit_ZCMain", referenced from:
>      ___stginit_ZCMain$non_lazy_ptr in libHSrts.a(Main.o)
>  "_ZCMain_main_closure", referenced from:
>      _ZCMain_main_closure$non_lazy_ptr in libHSrts.a(Main.o)
> ld: symbol(s) not found
> collect2: ld returned 1 exit status
>
> What's going on? I'm running GHC 6.8.3, if that helps.

Your module isn't named Main, so to produce an executable you must pass the 
flag
-main-is ModuleName
on the command line.
Another thing, it is recommendable to develop the habit of passing the --make 
flag to ghc.




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

Message: 5
Date: Tue, 21 Oct 2008 12:30:47 -0400
From: John Dorsey <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] do not understand Semantics of Case
        Expressions in report
To: Beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=us-ascii

Michael,

(Sorry for duplicates; I sent this from the wrong address initially.)

> (m)      case  v  of {  K  { f1  =  p1  ,  f2  =  p2  ,  ... } ->  e ; _ ->  
> e'  }
>        =  case e' of {
>           y ->
>            case  v  of {
>              K  {  f1  =  p1  } ->
>                    case  v  of { K  { f2  =  p2  ,  ...  } ->  e ; _ -> y  };
>                    _ ->  y  }}
>        where f1, f2, ... are fields of constructor K; y is a new variable
[...]
> I'm totally confused with this identity. Especialy with " =  case e'".
> Can anyone explain a little what does this rule stand, please?
> It is better to see some example.

You got me curious, so I looked over this.  The table you reference
lists identities that should hold for all implementations of case
expressions.

(m) is about how case matches against constructors with named fields,
and it shows that a case expression that matches against multiple
fields (f1, f2, etc.) can be broken into nested case expressions which
each match a single field (eg. f1).  It looks like

   "case e' of { y -> ..."

was introduced solely to give e' a name that can be used in two places,
since the nested form may fail to match at each level.  It seems to me
that without this, you could get code explosion from duplicating the
expression e' below; with this you get sharing.

Here it is with a interim step added:

-- Match v against a constructor with multiple fields
case v  of {  K  { f1  =  p1  ,  f2  =  p2  ,  ... } ->  e ; _ ->  e'  }

-- Same, but introduce y to represent e' without loss of sharing
case e' of { y ->
     case  v  of {  K  { f1  =  p1  ,  f2  =  p2  ,  ... } ->  e ; _ ->  y  }}

-- Same, but match first field of K independent of the rest
case e' of { y ->
    case v  of { K  {  f1  =  p1  } ->
        case  v  of { K  { f2  =  p2  ,  ...  } ->  e ; _ -> y  };
        _ ->  y  }}

I hope this helps.

Regards,
John



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

Message: 6
Date: Tue, 21 Oct 2008 23:35:46 +0600
From: "Michael Mekhanoshin" <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] do not understand Semantics of Case
        Expressions in report
To: Beginners@haskell.org
Message-ID:
        <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=UTF-8

2008/10/21 John Dorsey <[EMAIL PROTECTED]>:
>  It looks like
>
>   "case e' of { y -> ..."
>
> was introduced solely to give e' a name that can be used in two places,
> since the nested form may fail to match at each level.  It seems to me
> that without this, you could get code explosion from duplicating the
> expression e' below; with this you get sharing.
...
>
> -- Match v against a constructor with multiple fields
> case v  of {  K  { f1  =  p1  ,  f2  =  p2  ,  ... } ->  e ; _ ->  e'  }
>
> -- Same, but introduce y to represent e' without loss of sharing
> case e' of { y ->
>     case  v  of {  K  { f1  =  p1  ,  f2  =  p2  ,  ... } ->  e ; _ ->  y  }}
>
> I hope this helps.
>
Surely it does.
Most tricky part here (for me) is that e' goes in outer scope. It
works here like in rule (c) . I got it. Thank you for your help.

Regards,
Michael


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

Message: 7
Date: Tue, 21 Oct 2008 13:25:53 -0500
From: Larry Evans <[EMAIL PROTECTED]>
Subject: [Haskell-beginners] what type is 'Val 9' when 'Val Int' a
        ctor for        'Expr e'? 
To: Beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset="iso-8859-1"

Skipped content of type multipart/alternative-------------- next part 
--------------
A non-text attachment was scrubbed...
Name: uniplate.try.hs
Type: text/x-haskell
Size: 956 bytes
Desc: not available
Url : 
http://www.haskell.org/pipermail/beginners/attachments/20081021/1669ad30/uniplate.try.bin

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

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


End of Beginners Digest, Vol 4, Issue 8
***************************************

Reply via email to