RE: [Haskell-cafe] strictness and the simple continued fraction

2004-10-12 Thread Simon Peyton-Jones
If you are interested in arbitrary precision arithmetic using continued
fractions, you may want to check out the work of David Lester.  And
Peter Potts et al.  Just type exact real arithmetic into Google.

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of
| William Lee Irwin III
| Sent: 12 October 2004 04:53
| To: Scott Turner
| Cc: [EMAIL PROTECTED]
| Subject: Re: [Haskell-cafe] strictness and the simple continued
fraction
| 
| On Mon, Oct 11, 2004 at 09:53:16PM -0400, Scott Turner wrote:
|  I tried using continued fractions in a spiffy lazy list
implementation a
|  while ago. Never got them working as well as expected.
|  Evenutally I realized that calculating with lazy lists is not as
|  smooth as you might expect.
|  For example, the square root of 2 has a simple representation
|  as a lazy continued fraction, but if you multiply the square root of
2 by
|  itself, your result lazy list will never get anywhere.  The
calculation will
|  keep trying to determine whether or not the result is less than 2,
this being
|  necessary to find the first number in the representation. But every
finite
|  prefix of the square root of 2 leaves uncertainty both below and
above, so
|  the determination will never be made.
|  Your problems may have some other basis, but I hope this helps.
| 
| I hit that one, too. That's nasty enough it may be best to give up on
| the infinite case, at least. I can't think of a way to salvage all
this.
| 
| 
| -- wli
| ___
| Haskell-Cafe mailing list
| [EMAIL PROTECTED]
| http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] strictness and the simple continued fraction

2004-10-12 Thread William Lee Irwin III
On Tue, Oct 12, 2004 at 08:48:27AM +0100, Simon Peyton-Jones wrote:
 If you are interested in arbitrary precision arithmetic using continued
 fractions, you may want to check out the work of David Lester.  And
 Peter Potts et al.  Just type exact real arithmetic into Google.

That's where I got the ContFrac.hs I started with, though I used a
different search string. =)


-- wli
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: OCaml list sees abysmal Language Shootout results

2004-10-12 Thread MR K P SCHUPKE
One to add to your list, string edit distance - as its hard, and useful.

Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] List implementation.

2004-10-12 Thread MR K P SCHUPKE

With reference to the discussion a couple of days ago
about list implementations, here is some code showing the
idea I was talking about... Its a list that you can write
either single elements or blocks (UArrays) to, but it always
reads like a list of elements, so blocks can be read in, but
you can recurse over individual elements. There is obviously
some overhead with this in-haskell implementation, but if this
were the default list implementation in the RTS, you could use
the encoding trick I mentioned before to get practically no
overhead for its use.

--
{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-undecidable-instances #-}

module List where

import Data.Array.Unboxed

data AList a = One !a (AList a) | Many !Int !(UArray Int a) (AList a) | Nil

class List l where
   head :: IArray UArray a = l a - a
   tail :: IArray UArray a = l a - l a
   (+:) :: IArray UArray a = a - l a - l a
   (++:) :: IArray UArray a = (UArray Int a) - l a - l a

infixr 9 +:
infixr 9 ++:

instance List AList where
   head (One a _) = a
   head (Many i a _) = a!i
   tail (One _ l) = l
   tail (Many i a l)
  | i  la = (Many (i+1) a l)
  | otherwise = l
  where (_,la) = bounds a
   a +: l = One a l
   a ++: l = Many 0 a l

---

Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] List implementation.

2004-10-12 Thread Ronny Wichers Schreur
Keean writes (in the Haskell cafe):
[..] 
data AList a = One !a (AList a)
 | Many !Int !(UArray Int a) (AList a) | Nil
[..]
   head (Many i a _) = a!i
[..]
   a ++: l = Many 0 a l
You probably want to test in the definition of (++:) that
the array a is not of length 0.
Cheers,
Ronny Wichers Schreur
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] List implementation.

2004-10-12 Thread MR K P SCHUPKE
Hows this:

...
   tail (Many i a l)
  | i  (e-s) = (Many (i+1) a l)
  | otherwise = l
  where (s,e) = bounds a
...
  a ++: l
  | e = s = Many s a l
  | otherwise = l
  where (s,e) = bounds a

A futher though is that with constructors you can do:

f (a:as) =
f [] =

As you cannot use the constructors to access the list elements here,
maybe the following would be more useful:

class List l where
   head :: IArray UArray a = l a - Maybe a
   tail :: IArray UArray a = l a - Maybe (l a)

then you can write:

f x
 | Just h - head x = ...
 | otherwise = ...



Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] List implementation.

2004-10-12 Thread MR K P SCHUPKE
class List l where
   head :: IArray UArray a = l a - Maybe a
   tail :: IArray UArray a = l a - Maybe (l a)

changed my mind about this... you cannot do: tail $ tail $ tail x
so added a 'null' test instead.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Strict evaluation not working?

2004-10-12 Thread Christian Hofer
Hi,
having found a bit of time to play with Haskell, I am trying to figure 
out how to enforce strict evaluation.
I wrote the following program:

main =
let x = zipWith (+) [5..] [6..]
in putStrLn $ show $ x `seq` head x
I expected this program not to terminate - because of the seq-Operator, 
but it happily returns 11 in ghc as well as in ghci. What do I make 
wrong?

Chris
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Language extension idea (was Re: [Haskell-cafe] Re: OCaml list sees...)

2004-10-12 Thread Jon Fairbairn
On 2004-10-10 at 11:20BST Malcolm Wallace wrote:
 As an example, instead of the following list-only code,
 
 f :: List a - ...
 f []= ...
 f (h:t) = ...
 
 you could write this more general version, which assumes only some
 class Sequence with operations null, head, tail, etc.
 
 f :: Sequence s = s a - ...
 f list | null list   = ...
| h - head list, t - tail list  = ...
 
 Although slightly more verbose, it still achieves something like the
 clarity of pattern-matching.

Here's my take on this:

 module SQC where
 import Array

Split the reading from the writing, and allow the avoidance
of head and tail wherever possible:

 class Sequential f where
   examine :: f a - Maybe (a, f a)

the next three aren't really necessary

   first :: f a - a
   rest :: f a - f a
   isEmpty:: f a - Bool

The default method for first and rest typify the usage.  I
think this is slightly prettier than using head and tail:

   first l | Nothing - e = error ugh
   | Just (hd, tl) - e = hd
   where e = examine l 

   rest  l | Nothing - e = error agh
   | Just (hd, tl) - e = tl
   where e = examine l

   isEmpty l | Nothing - examine l = True
 | otherwise = False
 

 class Sequential s = 
   Sequence s where
   cons :: a - s a - s a
   nils :: s a

With the reading and writing separated, we can do things
like map and filter without requiring the thing being read
from to have all the properties of a list:

 mapS:: (Sequential s, Sequence t) = (a - b) - s a - t b
 mapS f l | Nothing - e = nils
  | Just (h, t) - e = cons (f h) (mapS f t)
  where e = examine l

 filterS:: (Sequential s, Sequence t) = (a - Bool) - s a - t a
 filterS p l | Nothing - e = nils
 | Just (h, t) - e, p h = cons h (filterS p t)
 | Just (h, t) - e = filterS p t
 where e = examine l

The instances for [] are straightforward

 instance Sequential [] where
 first = head
 rest = tail
 examine [] = Nothing
 examine (a:b) = Just (a,b)

 instance Sequence [] where
 cons = (:)
 nils = []

Actually, in Ponder, the list type was just a (recursive)
synonym for something similar to List t = Maybe (t, List t),
so examine would just have been the identity -- which
suggests that this ought to be cheap to implement.

We can give a read-only instance for (part of) an array:

 data ArrayTail i e = AT i (Array i e) deriving Show

 instance (Enum i, Ix i) = Sequential (ArrayTail i)
 where examine (AT i a) | inRange (bounds a) i = Just (a!i, AT (succ i) a)
| otherwise = Nothing

so that 

filterS ((==0).(`rem`2)) (AT 1 (array (1,10) ([1..10]`zip`[20..30])))::[Int]
= [20,22,24,26,28]

which might be handy for selecting stuff from an array
represented sequence without having to build an array for
the result.

  Jón


-- 
Jón Fairbairn [EMAIL PROTECTED]


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strict evaluation not working?

2004-10-12 Thread Jon Fairbairn
On 2004-10-12 at 18:07+0200 Christian Hofer wrote:
 Hi,
 
 having found a bit of time to play with Haskell, I am trying to figure 
 out how to enforce strict evaluation.
 I wrote the following program:
 
 main =
   let x = zipWith (+) [5..] [6..]
   in putStrLn $ show $ x `seq` head x
 
 I expected this program not to terminate - because of the seq-Operator, 
 but it happily returns 11 in ghc as well as in ghci. What do I make 
 wrong?

head is strict in its first argument, so x `seq` head x is
equivalent to head x.  seq only evaluates to (w?)hnf. To do
more you would need deepSeq.

-- 
Jón Fairbairn [EMAIL PROTECTED]


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] One-way and two-way monads.

2004-10-12 Thread Kwanghoon Choi

Dear All,

List and IO are both monads when appropriate operations are defined. 

The IO monad, which is a one-way monad, does not have a function of
type IO a - a, in general, except an unsafe function 
unsafePerformIO :: IO a - a. A two-way monad, such as List, has such 
a function head :: [a] - a.

My rough question is:
  Is there any intersting theory on the relationship between one-way monads
  and two-way monads? For example, a restriction on the IO monad would offer
  a *safe* unsafePerformIO, and so the IO monad would become a two-way 
  monad. 

Does this question make sense at all?


Thanks in advance.

Kwanghoon Choi 


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] OO idioms redux

2004-10-12 Thread John Goerzen
OK, recently I posed a question about rethinking some OO idioms, and
that spawned some useful discussion.

I now have a followup question.

One of the best features of OO programming is that of inheritance.  It
can be used to slightly alter the behavior of objects without requiring
modification to existing code or breaking compatibility with existing
APIs.

As an example, say I have a ConfigParser class.  This class can read in
configuration files, provides various get/set methods to access them,
and can write them back out.

Now say I would like to make this a little more powerful.  Maybe I want
to support the use of environment variables in my config file, so if
there's a reference to $FOO in the file, it will be replaced by the
contents of $FOO in the environment.

In OO, I would make a new EnvConfigParser class.  I'd override the
read() method.  My new read() would probably start by calling the
parent's read() method, to get parsing for free.  Then it could iterate
over the data, doing its environment variable substitution.


Now, in Haskell, we obviously have no objects like this.  We do have
something that provides some of the same benefits -- typeclasses.
However, from what I can determine, they don't support algorithm
inheritance like objects do in an OOP.  Specifically, it seems impossible to
have two instances of a single typeclass that work on the same type,
while having one share most of the code with the other.

I'm wondering if there is a Haskell design pattern that I'm missing that
would provid ethe kind of benefits that one gets from inheritance in the
OO world.

-- John


-- 
John Goerzen
Author, Foundations of Python Network Programming
http://www.amazon.com/exec/obidos/tg/detail/-/1590593715

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] OO idioms redux

2004-10-12 Thread Ben Rudiak-Gould
On Tue, 12 Oct 2004, John Goerzen wrote:

 One of the best features of OO programming is that of inheritance.  It
 can be used to slightly alter the behavior of objects without requiring
 modification to existing code or breaking compatibility with existing
 APIs.

I hesitate to express a contrary opinion since it'll sound as though I'm
defending Haskell's limitations, but that's actually not the case here --
this was true even before I learned Haskell.

In my own OOP code (mainly C++) I've rarely used implementation
inheritance, and when I have I've never felt entirely happy about the way
it turned out; it always seemed a bit fragile and hacky. When I want to
take advantage of polymorphism I usually use abstract interfaces, and when
I want to share code I usually use containment and delegation, which has
always struck me as more robust.

In any case, Haskell does support polymorphic abstract interfaces and
containment and delegation. In your ConfigParser example you would have an
interface (say IConfigParser) which would be represented as a type class,
and two implementations (ConfigParser and EnvConfigParser) which would be
represented as instances of the type class. E.g.

class IConfigParser a where
  newConfigParser :: IO a
  readConfigFile :: a - FilePath - IO ()
  getFoo :: a - IO Foo
  setFoo :: a - Foo - IO ()
  ...

data ConfigParser = ...

instance IConfigParser ConfigParser where ...

data EnvConfigParser = ECP ConfigParser

instance IConfigParser EnvConfigParser where
  newConfigParser = liftM ECP newConfigParser
  readConfigFile (ECP cp) path =
readConfigFile cp path  envSubst cp
  getFoo (ECP cp) = getFoo cp
  ...

I should say, though, that this is very unidiomatic code. Partly this is
because I don't quite understand the meaning of your ConfigParser class --
does it exist before a configuration file is read? What is the meaning of
having more than one instance? Parsing configuration files strikes me as
more verb than noun, and I'd be more inclined in this case to declare a
single ConfigData type, a single function to write it to a file, and two
functions to read it, one with environment substitution and one without.
So I suppose my advice is twofold:

1. Try replacing implementation inheritance with containment and
   delegation when you translate to Haskell.

2. Try revisiting the original problem and thinking about how to
   solve it in a Haskellish way, rather than solving it in another
   language and then translating.

-- Ben

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] strictness and the simple continued fraction

2004-10-12 Thread Dylan Thurston
On Mon, Oct 11, 2004 at 09:53:16PM -0400, Scott Turner wrote:
 Evenutally I realized that calculating with lazy lists is not as
 smooth as you might expect. For example, the square root of 2 has a
 simple representation as a lazy continued fraction, but if you
 multiply the square root of 2 by itself, your result lazy list will
 never get anywhere.  The calculation will keep trying to determine
 whether or not the result is less than 2, this being necessary to
 find the first number in the representation. But every finite prefix
 of the square root of 2 leaves uncertainty both below and above, so
 the determination will never be made.

Right, one way to think about this problem is that the representations
by continued fractions are unique, so there's no way to compute the
prefix of a representation for something right on the boundary.
Representing numbers by lazy strings of, say, decimal digits has the
same problem.

There are known solutions, but they lack the elegance of continued
fraction representations.  You fundamentally have to have non-unique
representations, and that causes some other problems.  One popular
version is to use base 2 with digits -1, 0, and +1.

Simon Peyton-Jones already posted the references.

These methods appear to lose out in practice to using a large fixed
precision and interval arithmetic, increasing the precision and
recomputing as necessary.

Peace,
Dylan


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe