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.  Re: Problems with ghc (Christian Maeder)
   2. Re:  fix (Justin Bailey)
   3.  Mathematical Blundering (Jeffrey Drake)
   4. RE:  Mathematical Blundering (Paul Johnston)
   5. solved: implementation dependent (was Re: [Haskell-beginners]
      better    way to create Array defined on all      indices (Larry Evans)
   6. Re:  better way to create Array defined on all    indices
      (Daniel Fischer)
   7.  HaXml.SAX successfully parses a malformed XML    document
      (David Frey)
   8.  IO Problem (Jamie McCloskey)
   9. Re:  IO Problem (Daniel Fischer)


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

Message: 1
Date: Wed, 15 Oct 2008 16:06:33 +0200
From: Christian Maeder <[EMAIL PROTECTED]>
Subject: [Haskell-beginners] Re: Problems with ghc
To: Paul Johnston <[EMAIL PROTECTED]>
Cc: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=ISO-8859-1

Paul Johnston wrote:
> [EMAIL PROTECTED]:~/haskell/aht/3$ ghc
> -L=/usr/local/lib/ -o Haq --make Haq.hs
> [1 of 1] Compiling Main             ( Haq.hs, Haq.o )
> Linking Haq ...
> [EMAIL PROTECTED]:~/haskell/aht/3$ ./Haq "Bother"
> "Haq! BotherOr not!"
> [EMAIL PROTECTED]:~/haskell/aht/3$
> 
> Tried putting /usr/local/lib in $LD_LIBRARY_PATH but that didn't seem to
> work, pity.
> Anyway many, many thanks

I think setting LIBRARY_PATH would work.

Cheers Christian


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

Message: 2
Date: Wed, 15 Oct 2008 16:02:50 -0700
From: "Justin Bailey" <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] fix
To: "Matthew J. Williams" <[EMAIL PROTECTED]>
Cc: beginners@haskell.org
Message-ID:
        <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=ISO-8859-1

n decreases on each step of the recursion, which will allow it to
terminate. You need to expand AND substitute arguments:

fix (\rec n -> if n == 0 then 1 else n * rec (n-1)) 5
> fix (\rec 5 -> if 5 == 0 then 1 else n * rec (5 -1))
> fix (\rec 5 -> if 5 == 0 then 1 else n * (fix (\rec 4 -> if 4 == 0 then 1 
> else 4 * rec (3-1))))

And so on.

On Wed, Oct 15, 2008 at 3:51 PM, Matthew J. Williams
<[EMAIL PROTECTED]> wrote:
> hello listers, a few days ago A fellow lister sent me the following link:
>
> http://en.wikibooks.org/wiki/Haskell/Fix_and_recursion
>
>        The 'fix' function is interesting to say the least. There is one
> example that I've had difficulty expanding:
>
>        fix (\rec n -> if n == 0 then 1 else n * rec (n-1)) 5
>        120
>
>        My interpretation:
>        fix (\rec n -> if n == 0 then 1 else n * rec (n-1)) 5
>        ((\rec n -> if n == 0 then 1 else n * rec (n-1)) (fix (\rec n -> if n
> == 0 then 1 else n * rec (n-1)) )) 5
>        . . .
>
>        Yet, it does not quite explain how 'fix' does not result in infinite
> recursion.
>
>        Sincerely
>        Matthew J. Williams
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>


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

Message: 3
Date: Thu, 16 Oct 2008 04:46:47 -0400
From: Jeffrey Drake <[EMAIL PROTECTED]>
Subject: [Haskell-beginners] Mathematical Blundering
To: Haskell Beginners <beginners@haskell.org>
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain


I have defined myself a set of functions to test:

fact 1 = 1
fact n = n * (fact $ n - 1)

sine x = x - (x^3/(fact 3)) + (x^5/(fact 5)) - (x^7/(fact 7))

Where my code is 'sine' and the prelude's is sin:
*Main> sine 1
0.841468253968254
*Main> sin 1
0.8414709848078965

*Main> sine 2
0.9079365079365079
*Main> sin 2
0.9092974268256817

*Main> sine 3
9.107142857142847e-2
*Main> sin 3
0.1411200080598672

*Main> sine 4
-1.3841269841269837
*Main> sin 4
-0.7568024953079282

After 2 they seem to diverge rather rapidly, and I am not sure why. Any
ideas?

I would have thought that 4 terms would have been enough.

- Jeff.



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

Message: 4
Date: Thu, 16 Oct 2008 09:57:39 +0100
From: "Paul Johnston" <[EMAIL PROTECTED]>
Subject: RE: [Haskell-beginners] Mathematical Blundering
To: "Jeffrey Drake" <[EMAIL PROTECTED]>,        "Haskell Beginners"
        <beginners@haskell.org>
Message-ID:
        <[EMAIL PROTECTED]>
Content-Type: text/plain;       charset="iso-8859-1"

Bit of basic maths.
You are using a power series to approximate sine
This works by taking an expansion about a fixed point, usually zero.
It only works well around that point.
If you get far away it works badly.
You need to exploit the cyclic nature of the trignometrical functions i.e.
Sin x = sin ((2 * pi) + x) = sin ((4 * pi) + x)
Essentially consider the shift in multiples of 2 * pi and calculate the value 
of x nearest to zero.

See
http://en.wikipedia.org/wiki/Taylor_series
The diagram on the top right is very instructive.

Paul

-----Original Message-----
From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Jeffrey Drake
Sent: Thursday, October 16, 2008 9:47 AM
To: Haskell Beginners
Subject: [Haskell-beginners] Mathematical Blundering


I have defined myself a set of functions to test:

fact 1 = 1
fact n = n * (fact $ n - 1)

sine x = x - (x^3/(fact 3)) + (x^5/(fact 5)) - (x^7/(fact 7))

Where my code is 'sine' and the prelude's is sin:
*Main> sine 1
0.841468253968254
*Main> sin 1
0.8414709848078965

*Main> sine 2
0.9079365079365079
*Main> sin 2
0.9092974268256817

*Main> sine 3
9.107142857142847e-2
*Main> sin 3
0.1411200080598672

*Main> sine 4
-1.3841269841269837
*Main> sin 4
-0.7568024953079282

After 2 they seem to diverge rather rapidly, and I am not sure why. Any ideas?

I would have thought that 4 terms would have been enough.

- Jeff.

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


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

Message: 5
Date: Thu, 16 Oct 2008 09:17:40 -0500
From: Larry Evans <[EMAIL PROTECTED]>
Subject: solved: implementation dependent (was Re: [Haskell-beginners]
        better  way to create Array defined on all      indices
To: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset="iso-8859-1"

On 10/15/08 23:50, Larry Evans wrote:
> On 10/15/08 16:05, Larry Evans wrote:
>> I'd like to have an Array indices values
>> (see http://haskell.org/onlinereport/array.html)
>> defined on [minBound::indices ... maxBound::indices].
[snip]
> The aforementioned array.html has:
>
>                             _     -> error "Array.!: \
>                                            \multiply defined array element")
>
> suggesting it should detect redefinitions; 

> Is this a bug in my ghc library?
According to:

  
http://www.haskell.org/ghc/docs/6.6-latest/html/libraries/base/Data-Array.html

it's not.  It's just implemented differently by libraries:

> The Haskell 98 Report further specifies that if any two associations 
> in the list have the same index, the value at that index is undefined 
> (i.e. bottom). However in GHC's implementation, the value at such an 
> index is the value part of the last association with that index in the 
> list. 
So, if I want multiple definitions diagnosed as an error, I'll have to 
do it myself :(


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

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

Message: 6
Date: Thu, 16 Oct 2008 16:26:30 +0200
From: Daniel Fischer <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] better way to create Array defined on
        all     indices
To: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain;  charset="iso-8859-1"

Am Mittwoch, 15. Oktober 2008 23:05 schrieb Larry Evans:
> I'd like to have an Array indices values
> (see http://haskell.org/onlinereport/array.html)
> defined on [minBound::indices ... maxBound::indices].
> The attached does this; however, it also allows
> duplicate definitions (e.g. in the attached, the
> value for Term index is defined twice).
>
> Is there a better way to do this?  Maybe a
> way that doesn't use all the contexts?

I don't know of a better way to do it, your way is fine.
What do you mean by "contexts" here? Of course, Bounded and Ix are necessary 
to define array_complete. If you want to perhaps leave some array entries 
undefined, there's no problem with that, as long as you don't try to access 
an undefined entry later.

> Also, is there a way to do it so that the value
> associated with an index is not redefined?

>From GHC's user's guide, section 13.1.1.6:
GHC's implementation of array takes the value of an array slot from the last 
(index,value) pair in the list, and does no checking for duplicates. The 
reason for this is efficiency, pure and simple.

If you want to throw an error for duplicate definitions, you have to scan the 
eqs list manually before passing it to array.
>
> In effect, I'm making a map, but using an Array
> as the implementation because, I guess, it would be
> a bit faster.
>
> TIA.

Cheers,
Daniel


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

Message: 7
Date: Thu, 16 Oct 2008 15:47:56 -0800
From: "David Frey" <[EMAIL PROTECTED]>
Subject: [Haskell-beginners] HaXml.SAX successfully parses a malformed
        XML     document
To: beginners@haskell.org <beginners@haskell.org>
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=ISO-8859-1

It seems that saxParse from Text.XML.HaXml.SAX will successfully parse a
malformed XML document.

Notice that the SubElem opening and closing tag are not matched in the
XML document below.

--- input.xml ---
<RootNode>
    <ElemOne>
        <SubElem attr="foo">element data</SubElemBroken>
        <NoDataElem/>
    <ElemOne>
</RootNode>
--- end input.xml ---


The Haskell code below runs without error.  It prints out the type of
elements found during the parse.


--- Haskell Code ---
module Main where

import qualified Text.XML.HaXml.SAX as SAX
import Data.Maybe

main = let inputFilename = "input.xml" in
    do content <- readFile inputFilename
       let (elements, error) = SAX.saxParse inputFilename content
       if isNothing error
            then mapM_ putStrLn (summarizeElements elements)
            else putStrLn $ "ERROR:" ++ (fromJust error)



summarizeElements :: [SAX.SaxElement] -> [String]
summarizeElements elements = map summarizeElement elements


summarizeElement :: SAX.SaxElement -> String
summarizeElement element = case element of
    (SAX.SaxDocTypeDecl d)           -> "DocType"
    (SAX.SaxProcessingInstruction p) -> "Processing Instruction"
    (SAX.SaxComment s)               -> "Comment"
    (SAX.SaxElementOpen name attrs)  -> "Element Open"
    (SAX.SaxElementClose name)       -> "Element Close"
    (SAX.SaxElementTag name attrs)   -> "No Content Element"
    (SAX.SaxCharData charData)       -> "Character Data"
    (SAX.SaxReference reference)     -> "Reference"

--- End Haskell Code ---


The Python code below throws an exception when parsing the same input
document.


--- Python Code ---
from xml.sax import make_parser
from xml.sax.handler import ContentHandler


def main():
    c = ContentHandler()
    p = make_parser()
    p.setContentHandler(c)
    p.parse(open('input.xml'))


if __name__ == '__main__':
    main()
-- End Python Code ---


Is this a bug in the HaXml SAX parser?

Thanks,
David


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

Message: 8
Date: Fri, 17 Oct 2008 19:58:45 +1300
From: Jamie McCloskey <[EMAIL PROTECTED]>
Subject: [Haskell-beginners] IO Problem
To: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain

Hi everyone,
I have just started learning Haskell, it is a very interesting language.
As a first project, I am building a brainfuck interpreter, but have hit
a stumbling block: IO. My program source is located at
http://hpaste.org/11219

My program handles the state of a brainfuck program by passing
State(lists of ints) objects around. When I added my getIn fuction,
however, it needed to return an IO State object. This broke the run
function, as it returned a State. No problem, I thought, and changed run
to return IO State. This broke my exec function, which calls run on each
element in a list.

As exec passes on the state returned by the run function to itself, it
needs to take an IO State. This causes problems in the loop function,
which calls exec on a subprogram. Because exec now takes IO State, loop
also needs to. However, loop is called by run, so now run needs to take
IO State. Now, all functions called by run need to take IO State.

All this creates a whole load of functions with IO, even though it
should not be necessary. What I would like to know, is how I can avoid
this, possibly by modifying exec to just take a State.

Whew! What a long-winded explanation!

Any ideas?

--Jamie

P.S. Please ignore my long-winded list iteration functions -- I'm
working on a cleaner version.



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

Message: 9
Date: Fri, 17 Oct 2008 15:40:46 +0200
From: Daniel Fischer <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] IO Problem
To: Jamie McCloskey <[EMAIL PROTECTED]>, beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain;  charset="iso-8859-15"

Am Freitag, 17. Oktober 2008 08:58 schrieb Jamie McCloskey:
> Hi everyone,
> I have just started learning Haskell, it is a very interesting language.
> As a first project, I am building a brainfuck interpreter, but have hit
> a stumbling block: IO. My program source is located at
> http://hpaste.org/11219
>
> My program handles the state of a brainfuck program by passing
> State(lists of ints) objects around. When I added my getIn fuction,
> however, it needed to return an IO State object. This broke the run
> function, as it returned a State. No problem, I thought, and changed run
> to return IO State. This broke my exec function, which calls run on each
> element in a list.
>
> As exec passes on the state returned by the run function to itself, it
> needs to take an IO State. This causes problems in the loop function,
> which calls exec on a subprogram. Because exec now takes IO State, loop
> also needs to. However, loop is called by run, so now run needs to take
> IO State. Now, all functions called by run need to take IO State.
>
> All this creates a whole load of functions with IO, even though it
> should not be necessary. What I would like to know, is how I can avoid
> this, possibly by modifying exec to just take a State.

exec [] st = return st
exec (x:xs) st = do
        newSt <- run x st
        exec xs newSt

or
exec (x:xs) st = run x st >>= exec xs

Once you're doing input or output, you're in IO, so run and exec must have 
type a -> b -> IO c, getIn and putOut must also live in IO, everything else 
needn't.

>
> Whew! What a long-winded explanation!
>
> Any ideas?
>
> --Jamie
>
> P.S. Please ignore my long-winded list iteration functions -- I'm
> working on a cleaner version.
>

Probably the tidiest (as if that was a criterion for a brainfuck interpreter) 
would be to rename your State to ProgramState (or whatever) and write the 
interpreter in
StateT ProgramState IO
, you'd have
run :: Operator -> StateT ProgramState IO ()
run Add = modify myAdd
run Minus = ...
run Input = do
        n <- lift $ readLn
        modify (inHelper n)

and 
exec = mapM_ run

HTH,
Daniel



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

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


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

Reply via email to