Re[2]: [Haskell-cafe] Number overflow

2007-07-11 Thread Bulat Ziganshin
Hello Thomas,

Thursday, July 12, 2007, 3:14:57 AM, you wrote:
> The differences between Int and Integer operations are mostly constant 
> factors.

well, i will be unlucky if in my real-world program Integers would be
used instead of Ints. defaulting provides a great way to solve this
dilemma, so good-for-anyone approach may be: default defaulting to
Integer instead of Int, and use (Num a) instead of Int in all standard
functions such as length. with jhc-like automatic specialization
feature this should provide enough speed

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monadic tunnelling: the art of threading one monad through another

2007-07-11 Thread Jules Bean

Derek Elkins wrote:

What you're actually showing is that these effects can be -embedded- in
IO (i.e. that IO already supports them).  I noticed you didn't try to
make an instance for the Cont monad.  Actually, if we added
continuations to IO, we'd be set.  We wouldn't even need your typeclass.



Yes, precisely. Your use of the term 'embedded' parallels the fact I 
called the method 'embed'.


It's a useful technique because it enables you to give more specific 
types to your functions: to use StateT IO instead of just using IO and 
instead of using ad-hoc IORefs yourself you can use the StateT methods 
and have the IORefs behind the scenes when you need to thread through 
another monad. Similarly you can give pure types to callbacks (either 
plain State s, or the parametric forall m. StateT s m) which makes it 
easier to specify and test them. It even has applications in an 
untrusted code environment, where it's dangerous to accept callbacks of 
IO type.


Of course, you can't do Cont or List (unless I'm missing something) 
because they are both capable of duplicating the current continuation, 
and it's not possible to duplicate the entire IO state (a.k.a. the 
RealWorld#).


Jules

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] CGI test

2007-07-11 Thread Suleiman Souhlal

Andrew Coppin wrote:

Greetings.

Can somebody write a trivial (as in: small) program so I can test my CGI 
stuff without having to actually install and configure Apache?


(Basically, I'd like something I can compile into a small binary, so 
when I double-click it, it will listen on port 80, and when it gets a 
HTTP request, it tries to find a program with that name, and run it as a 
CGI script. And that's all. Nothing fancy; if I want fancy Apache can do 
a propper job...)


Actually, might be a useful thing to have in a library somewhere.



About two years ago, I wrote a small httpd that I use to serve stuff. 
It's able to do CGI as well:


http://people.freebsd.org/~ssouhlal/stuff/rephttpd-0.4.hs

Feel free to do whatever you want with it (even though the code is not 
that great).


-- Suleiman
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] Toy compression algorithms [was: A very edgy language]

2007-07-11 Thread ajb
G'day.

Quoting Bulat Ziganshin <[EMAIL PROTECTED]>:

> what you mean by "flat" and "static" applied to PPM? static PPM models
> exist - they carry probabilities as separate table very like static
> Huffman encoding. is "flat" the same as order-0?

"Static" means that the frequency distribution is fixed.  "Flat" means
that the frequency histogram is flat.  (Every code word is predicted to
occur with the same frequency, resulting in a binary code.)

> can you give a link? i never heard about such algorithm

http://en.wikipedia.org/wiki/Canonical_Huffman_code

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Very freaky

2007-07-11 Thread Cale Gibbard

On 10/07/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:

Stefan O'Rear wrote:
> Another good example:
>
> foo :: ∀ pred : Nat → Prop . (∀ n:Nat . pred n → pred (n + 1))
>  → pred 0 → ∀ n : Nat . pred n
>

x_x

> Which you can read as "For all statements about natural numbers, if the
> statement applies to 0, and if it applies to a number it applies to the
> next number, then it applies to all numbers.".  IE, mathematical
> induction.
>

...and to think the idea of mathematical symbols is to make things
*clearer*...


As someone with a background in mathematics, I'd say that the idea of
mathematical symbols is to make things more concise, and easier to
manipulate mechanically. I'm not entirely certain that their intent is
to make things clearer, though often they can make things more precise
(which is a bit of a double edged sword when it comes to clarity). I
quite often try to avoid symbols as much as possible, only switching
to formulas when the argument I'm making is very mechanical or
computational. After all, in most circumstances, the reader is going
to have to translate the symbols back into concepts and images in
their head, and usually natural language is a little farther along in
that process, making things easier to read.

- Cale
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] better error expression in IO function

2007-07-11 Thread brad clawsie
On Wed, Jul 11, 2007 at 12:57:53PM -0700, brad clawsie wrote:
> but i would like to be able to express some of these error cases in a
> more structured manner

okay, i'm going to answer my own question for the sake of documenting it
for others who might be interested. thanks to andrew and brandon for clues



module Main (main) where

data ErrorTestType = ErrorA | ErrorB Int | ErrorC String
instance Show ErrorTestType where
show ErrorA = "Error A"
show (ErrorB n) = "Error B:" ++ (show n)
show (ErrorC s) = "Error C:" ++ (show s)
type ErrorTestT = Either ErrorTestType

f :: IO (ErrorTestT String)
f = do
  print "type something:"
  s <- getLine
  case length s of
1 -> return (Left ErrorA)
2 -> return (Left (ErrorB (length s)))
3 -> return (Left (ErrorC "error c"))
_ -> return (Right s)

main = do
  r <- f
  case r of
(Left e) -> print e
(Right a) -> print a
  return ()


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] embedding Haskell: problematic polymorphism

2007-07-11 Thread Claus Reinke

Say I have 3 boxes:

Box 1:  [1,2,5,3]:: [Float]
Box 2:  reverse  :: [a] -> [a]
Box 3:  putStrLn . show  :: (Show b) => b -> IO ()

I wonder, is it possible to create these boxes separately at runtime 
(each box being compiled/loaded separately with hsplugins), then connect 
them together like {Box 1}=>{Box 2}=>{Box 3} (with a wrapping layer 
doing appropriate type checking/error reporting), or does the whole 
thing need to be compiled statically to generate specialized variants of 
the polymorphic functions?  As hinted in #haskell :


haskell itself doesn't offer support for this. one reason why a proper
integration of Dynamic/typecase, together with orthogonal persistence
(napier88, tycoon), or first-class i/o (clean), or dynamic packages (alice), 
into the language would be nice to have..


depending on your application, though, you might be able to pretend
that you are ghci, by using the ghc api to turn your program into a 
controller for a ghci session. or look in the ghci sources for clues on

how to circumvent haskell's limitations to achieve what you want.
because ghci can do something like this (here from the prompt, but
the definitions could also be loaded from compiled modules):

   Prelude> :set -fno-monomorphism-restriction
   Prelude> let box1 = [1,2,5,3]::[Float]
   Prelude> let box2 = reverse :: [a]->[a]
   Prelude> let box3 = putStrLn . show :: Show b => b -> IO ()
   Prelude> :t box1
   box1 :: [Float]
   Prelude> :t box2
   box2 :: [a] -> [a]
   Prelude> :t box3
   box3 :: (Show b) => b -> IO ()
   Prelude> box3 $ box2 box1
   [3.0,5.0,2.0,1.0]

claus

ps: using haskell as a coordination layer over c boxes would
   be more conventional.. if you want to provide haskell
   components for a c-based framework, the latter isn't
   going to know about haskell types anyway, is it?


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] better error expression in IO function

2007-07-11 Thread Brandon S. Allbery KF8NH


On Jul 11, 2007, at 20:10 , Jeremy Shaw wrote:


At Thu, 12 Jul 2007 09:18:14 +1000,
Thomas Conway wrote:


On 7/12/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:

It's fairly common to use the Either type for this. By convention,
"Right" means "correct", and by elimination "Left" means an error...


Presumably, this is because the world is dominated by dull,
conventional, right handed people. :-)


Personally, I blame it on the Romans.

  The English word "sinister" comes from the Latin word
  "sinister,-tra,-trum", which originally meant "left" but took on
  meanings of "evil" or "unlucky" by the Classical Latin era[1].


Dig deeper; it far predates the Romans.

--
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 universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] better error expression in IO function

2007-07-11 Thread Derek Elkins
On Wed, 2007-07-11 at 17:10 -0700, Jeremy Shaw wrote:
> At Thu, 12 Jul 2007 09:18:14 +1000,
> Thomas Conway wrote:
> > 
> > On 7/12/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:
> > > It's fairly common to use the Either type for this. By convention,
> > > "Right" means "correct", and by elimination "Left" means an error...
> > 
> > Presumably, this is because the world is dominated by dull,
> > conventional, right handed people. :-)
> 
> Personally, I blame it on the Romans. 

Personally, I blame it on biology.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] better error expression in IO function

2007-07-11 Thread Jeremy Shaw
At Thu, 12 Jul 2007 09:18:14 +1000,
Thomas Conway wrote:
> 
> On 7/12/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:
> > It's fairly common to use the Either type for this. By convention,
> > "Right" means "correct", and by elimination "Left" means an error...
> 
> Presumably, this is because the world is dominated by dull,
> conventional, right handed people. :-)

Personally, I blame it on the Romans. 

  The English word "sinister" comes from the Latin word
  "sinister,-tra,-trum", which originally meant "left" but took on
  meanings of "evil" or "unlucky" by the Classical Latin era[1].

j.
[1] http://en.wikipedia.org/wiki/Left-handed
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monadic tunnelling: the art of threading one monad through another

2007-07-11 Thread Derek Elkins
What you're actually showing is that these effects can be -embedded- in
IO (i.e. that IO already supports them).  I noticed you didn't try to
make an instance for the Cont monad.  Actually, if we added
continuations to IO, we'd be set.  We wouldn't even need your typeclass.

On Wed, 2007-07-11 at 22:41 +0100, Jules Bean wrote:
> A programming style which is encouraged in haskell is to write your
> program using a special monad, rather than the IO monad. Normally some
> mixture of reader and state, possibly writer, the point of these
> monads is to help the type system to help you; help you be specific
> about which parts of your state can be modified by which parts of your
> program.
> 
> One problem with this approach comes with what an imperative programmer
> would call 'callbacks'. It's quite common with C library interfaces to
> take as a parameter an IO action (a callback) which the library will
> call with certain parameters. It's even more common with haskell
> libraries, although the type then is normally more general than IO;
> any higher order function can be thought of as using callbacks.
> 
> Now, supposing we have a library function which takes a callback. As
> an example, suppose we have a library function which reads in a file
> and calls our callback once on each line. A typical type might look
> like:
> 
> forEachLine :: Handle -> (String -> IO ()) -> IO ()
> 
> We have to provide a callback in the IO monad. But what if we don't
> want to work in the IO monad? What if we are working in, for example,
> a custom state monad of our own?
> 
> More generally, is there any sensible way to pass callbacks in one
> monad, to an action which runs in a different monad?  What does it
> mean to want to do this? In general the 'outer' action can call the
> callback as many times as it once, something like this (monospace font
> needed!):
> 
> m: <- cb ->   <- cb ->
> |  |   |  |
> n: -- outer --->  <-- outer -->  <-- outer ---
> 
> Now, to embed 'm' into 'n' in this way, we have to somehow 'freeze'
> the 'monadiness' (you may prefer to use the term 'the warmth and
> fuzziness') of m at the beginning, run the first callback in this
> correct environment, then 'freeze' it again just after the callback
> runs, and restore this for the second 'cb'. Finally we have to somehow
> ensure this 'monadiness' is returned to the caller.
> 
> This procedure is not possible for every pair of Monads m and n. They
> need to have special properties. It is however possible (for example)
> when 'n' is IO, and when 'm' is one of several common custom monads,
> as I will now show.
> 
> Boring imports give a clue as to which monads I'm going to attempt.
> 
>  > {-# OPTIONS -fglasgow-exts #-}
> 
> Although I have -fglasgow-exts on here, it's actually only necessary
> for the MPTC tricks towards the end of the exposition. The initial
> discussion is haskell 98 as far as I know.
> 
>  >
>  > import Control.Monad.State
>  > import Control.Monad.Reader
>  > import Control.Monad.Writer
>  > import Control.Monad.Error
>  > import Control.Exception
>  >
>  > import Data.Typeable
>  >
>  > import Data.IORef
> 
> We begin with a callback which is not in the IO monad, but in StateT
> Int IO (). StateT monads are very common in real programs (or
> hand-rolled equivalents). The simple callback just prints a message so
> we know it has happened, and increments the counter in the state so we
> can prove state is being correctly threaded.
> 
>  > -- example small action in the custom monad
>  > stateioact :: StateT Int IO ()
>  > stateioact = do
>  >   x <- get
>  >   liftIO $ putStrLn ("stateioact called, with state as "++
>  >  show x)
>  >   put (x+1)
>  >
> 
> The main action is just a boostrap to call a 'real' main action with
> some initial state:
> 
>  > -- Main action has type IO () as standard
>  > -- This example main action just defers to another action
>  > -- which is written in a custom monad
>  >
>  > main :: IO ()
>  > main =  do
>  >   putStrLn "main starting"
>  >   evalStateT mainAction 42
>  >   putStrLn "main exiting"
>  >
> 
> The real main action is a StateT Int IO () action. It calls stateioact
> once, then calls a "library function" which is known to use callbacks,
> then it calls stateioact again.
> 
>  > -- mainAction is written in the custom monad
>  > mainAction :: StateT Int IO ()
>  > mainAction = do stateioact
>  > embedIO $ \x -> usesCB (makeCallback stateioact x)
>  > stateioact
>  >
> 
> The library function is "usesCB". makeCallback and embedIO are the
> keys which make it all work.
> 
> Here is the library function. Note that it has plain type IO () -> IO
> (), just like any library function (e.g. a C FFI function) which takes
> a single callback. It prints diagnostic messages and takes care to
> call its callback twice, to demonstrate the monad-threading.
> 
>  > -- a 'library function' in the 

Re: Re[2]: [Haskell-cafe] In-place modification

2007-07-11 Thread ok
On 11 Jul 2007, at 9:56 pm, Bulat Ziganshin wrote:Java comes close to  
being competition, but it's slow and eats memory


never checked it myself, but people say that modern Java
implementations are as fast as C# and close to C++ speeds


People will say anything, but before believing this particular
one you will have to do your own measurements.  Here's mine:

I'm one of two lecturers in a 4th year information retrieval paper.
The main programming exercise is one where the students write their
own simple IR engine.  It's really pretty simple.  My model answer
in C is two separate programs, an index builder and a query engine,
and is 804 SLOC in 1075 total lines.  Each year, despite our advice,
some student does it in Java.  I have one such from last year:
1611 SLOC in 2531 total lines.  (Yes, this does mean programmer X
writing C can be twice as productive as programmer Y writing Java.)
The real killer is performance:  the Java program is 150 times slower
than the C one.  Let me say that slowly:  one hundred and fifty times
slower.  What was that about "close to C++ speeds" again?

The reason I have the program is that the student was distressed by
this and wanted me to help.  The problem was the Java libraries, one
class in particular.  By replacing that class with home brew code (at
the cost of several days coding and experimenting) it was possible to
speed the Java program up by a factor of about 15, at which point it
was *still* slower than AWK (using 'mawk 1.3.3').

I mentioned this in another context, and got a reply from someone who
has worked on large commercial projects in Java, who said that typically
half of their code was application-specific and half of it was rewrites
of Java library facilities to work around serious performance problems.

The lesson here is that productivity and performance are NOT solely
a matter of language; they are also a matter of libraries.  The Haskell
language is wonderful and I enjoy experiencing the reality of "there is
nothing as practical as a good theory".  But if we just had the
Haskell 98 report and libraries, it would NOT be a productive tool for
many real problems.  The growing collection of amazing stuff in the
hackage collection is extremely important.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy Lists and IO

2007-07-11 Thread Derek Elkins
On Wed, 2007-07-11 at 22:33 +0200, Chaddaï Fouché wrote:
> 2007/7/11, Andrew Coppin <[EMAIL PROTECTED]>:
> >
> > Ouch! That's gotta sting...
> >
> > I wasn't aware that this function was so leathal. I use it constantly
> > all the time...
> >
> 
> It isn't that "lethal" usually. It's only because he was using it on
> an infinite stream that it hurt so much... If you use it on a normal
> stdin or a hGetContents on a file it will be fine (though you will
> lose the advantage of its laziness, for example constant memory
> treatment).
> 

Nevertheless, length is a function you should rarely use.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange results when trying to create large Bool arrays.

2007-07-11 Thread Brandon S. Allbery KF8NH


On Jul 11, 2007, at 19:11 , Thomas Conway wrote:


Is there a compelling reason (hysterical raisins is not a compelling
reason) why Data.*.{length,size,take,drop,etc} use Int and not Num n
=>  or similar?


Efficiency, but many of them have generic equivalents (e.g.  
genericLength, genericDrop, etc.) at least in Data.List.


--
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 universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] better error expression in IO function

2007-07-11 Thread Thomas Conway

On 7/12/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:

It's fairly common to use the Either type for this. By convention,
"Right" means "correct", and by elimination "Left" means an error...


Presumably, this is because the world is dominated by dull,
conventional, right handed people. :-)

cheers,
Tom Southpaw Conway
--
Dr Thomas Conway
[EMAIL PROTECTED]

Silence is the perfectest herald of joy:
I were but little happy, if I could say how much.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Number overflow

2007-07-11 Thread Thomas Conway

On 7/12/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:

What, as in the way that simple strings are lists, and you change it to
something less flexible but faster if you actually need it?

I suppose that makes some sense...


Not much. There is a very significant difference between the two.

The differences between Int and Integer operations are mostly constant factors.

The differences between String and ByteString operations are
algorithmic (consider length).

T.
--
Dr Thomas Conway
[EMAIL PROTECTED]

Silence is the perfectest herald of joy:
I were but little happy, if I could say how much.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange results when trying to create large Bool arrays.

2007-07-11 Thread Thomas Conway

On 7/12/07, Stefan O'Rear <[EMAIL PROTECTED]> wrote:

Indeed.  I beleive that Int should be removed from the Prelude.


metoo.

Actually, one of the really annoying things that I am finding in my
code which is a mixture of ByteString, Word16, Word32 and Word64, is
that all the standard libraries use Int everywhere, so I end up having
to get out the fromIntegral spray-gun, which uglifies the code and
makes it much harder to read.

Is there a compelling reason (hysterical raisins is not a compelling
reason) why Data.*.{length,size,take,drop,etc} use Int and not Num n
=>  or similar?

If the answer is efficiency, then cannot they use Int# or similar
internally, and have an optimizable fromIntegral *inside* them?

T.
--
Dr Thomas Conway
[EMAIL PROTECTED]

Silence is the perfectest herald of joy:
I were but little happy, if I could say how much.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] In-place modification

2007-07-11 Thread Claus Reinke

... still talking about "In-place modification" ?


yes. in the time-honoured tradition of demonstrating 
concepts by means of meta-circular arguments.


;-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Toy compression algorithms

2007-07-11 Thread Thomas Conway

On 7/12/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:

Yes - but making it use a non-flat model opens a whole Pandora's Box of
fiddly programming. ;-)


This could just about be Rule No 1 of haskell programming: if it's
fiddly, then you haven't thought about the problem hard enough.

Corollary No 1 is Any Expression requiring more than 80 columns is fiddly.

:-)

I say this in jest, but it is "ha ha, only serious".

cheers,
T.
--
Dr Thomas Conway
[EMAIL PROTECTED]

Silence is the perfectest herald of joy:
I were but little happy, if I could say how much.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type system madness

2007-07-11 Thread Brandon S. Allbery KF8NH


On Jul 11, 2007, at 18:52 , Albert Y. C. Lai wrote:


Brandon S. Allbery KF8NH wrote:
GNOME's gedit, for one, has a tendency to put byte order marks at  
the beginning of every line in UTF8 mode.


Somehow I have never got a single BOM. My http://www.vex.net/ 
~trebla/u.html was written out by GNOME gedit. Version 2.14.4.


Hm. Might be the version (it's been a year or so since I used it) or  
the fact that I was in fact using mixed direction text at the time.


--
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 universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type system madness

2007-07-11 Thread Albert Y. C. Lai

Brandon S. Allbery KF8NH wrote:
GNOME's gedit, for one, has a tendency to put byte order marks at the 
beginning of every line in UTF8 mode.


Somehow I have never got a single BOM. My 
http://www.vex.net/~trebla/u.html was written out by GNOME gedit. 
Version 2.14.4.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type system madness

2007-07-11 Thread Brandon S. Allbery KF8NH


On Jul 11, 2007, at 15:23 , Alex Queiroz wrote:


On 7/11/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:


When I tell the editor to save UTF-8, it inserts some weird "BOM"
character at the start of the file - and thus, any attempt at
programatically processing that file instantly fails. :-(


Are you sure it's not UTF-16?


GNOME's gedit, for one, has a tendency to put byte order marks at the  
beginning of every line in UTF8 mode.


--
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 universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy Lists and IO

2007-07-11 Thread Chaddaï Fouché

Beautiful ! :-)
Could Haskell define this lazy Natural in a more efficient fashion ?
It seems like an useful thing to have in a standard library (or is it
in one of those ?).

--
Jedaï
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Very freaky

2007-07-11 Thread Philippa Cowderoy
On Tue, 10 Jul 2007, Aaron Denney wrote:

> On 2007-07-10, Dan Piponi <[EMAIL PROTECTED]> wrote:
> > On 7/10/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:
> >> But what does, say, "Maybe x -> x" say?
> >
> > Maybe X is the same as "True or X", where True is the statement that
> > is always true. Remember that the definition is
> >
> > data Maybe X = Nothing | Just X
> >
> > You can read | as 'or', 'Just' as nothing but a wrapper around an X
> > and Nothing as an axiom.
> >
> > So Maybe X -> X says that "True or X" implies X. That's a valid proposition.
> 
> It is?  Doesn't look like it.  Unless you just mean "grammatical" by
> valid, rather than "true".
> 

It's true in Haskell - undefined is a valid proof of anything you like, 
which is of course rather unsound.

-- 
[EMAIL PROTECTED]

A problem that's all in your head is still a problem.
Brain damage is but one form of mind damage.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] better error expression in IO function

2007-07-11 Thread Brandon S. Allbery KF8NH


On Jul 11, 2007, at 15:57 , brad clawsie wrote:

i know the Either type can be used in such a case(?), but i've had  
some

problem locating a satisfactory example (if this is indeed
appropriate)


You might want to look at MonadError (Control.Monad.Error), more  
specifically ErrorT layered on top of IO.


--
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 universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Defaulting to Rational [was: Number overflow]

2007-07-11 Thread Donald Bruce Stewart
lennart:
> 
>Yes, I think we want Integer to be the type that is used
>unless you ask for something else.
>It adheres to the principle of getting it right before
>optimizing.

On a similar note, there's been a long discussion in #haskell about the
problems of defaulting to floating point, and should Rational, or
something similar be used instead, given that Doubles and Float are
broken for a lot of basic things (like Eq and Ord), much as we default
to Integer already.

The issues raised regarding Rational was that you can unexpectedly
build up large precision, and performance in general, of course.
It was unknown whether there were suitable replacement types.
Rational also can't be used with Floating functionsl, like sqrt, which
would bring back Double defaulting.

But shouldn't this really work in Haskell, and if you want imprecision
you must ask for Double explicitly:

Prelude> 1.1 + 2.2 - 3.3
4.440892098500626e-16

Prelude> 1.1 + 2.2 - 3.3 :: Rational
0%1

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] xkcd #287 "NP-Complete"

2007-07-11 Thread Albert Y. C. Lai

Henning Thielemann wrote:

On Tue, 10 Jul 2007, Hugh Perkins wrote:


By the way, if you enjoy these problems, there are tons of these at
topcoder.com  I cant help thinking it'd be neat to have topcoder-like
competitions for Haskell, either by pursuading topcoder to integrate support
for Haskell, or hosting our own.


Is this related to
 http://www.haskell.org/haskellwiki/Great_language_shootout ?


No. topcoder is a competition between programmers, a programming 
contest. A question is posed, then 20 minutes later or something, see 
whose code has fewer bugs. It's web site is www.topcoder.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy Lists and IO

2007-07-11 Thread Stefan O'Rear
On Wed, Jul 11, 2007 at 11:46:10PM +0200, Chaddaï Fouché wrote:
> 2007/7/11, Stefan O'Rear <[EMAIL PROTECTED]>:
>>
>> Interestingly, the function is already there; it's called genericLength.
>>
>> However, the lazy natural type isn't.
>
> I'm not sure what you mean there : genericLength is just a length that
> can return any Num (eg. an Integer) and not just Int, it has nothing
> to do with what Andrew wanted, which was a function that checked if a
> list was longer than n without swallowing more of the list than
> necessary.
> Is there something I misunderstood in the exchange ?

[EMAIL PROTECTED]:/tmp$ cat Z.hs
import List

data Nat = Z | S Nat deriving(Eq, Ord, Show)

instance Num Nat where
Z + x = x
S x + y = S (x + y)

Z * x = Z
S x * y = y + (x * y)

fromInteger 0 = Z
fromInteger (n+1) = S (fromInteger n)

main = print $ genericLength (1 : 2 : undefined) > (1 :: Nat)
[EMAIL PROTECTED]:/tmp$ runghc Z.hs 

Z.hs:5:0:
Warning: No explicit method nor default method for `abs'
In the instance declaration for `Num Nat'

Z.hs:5:0:
Warning: No explicit method nor default method for `signum'
In the instance declaration for `Num Nat'
True
[EMAIL PROTECTED]:/tmp$ 

Stefan


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


Re: [Haskell-cafe] Lazy Lists and IO

2007-07-11 Thread Jonathan Cast
On Wednesday 11 July 2007, Chaddaï Fouché wrote:
> 2007/7/11, Stefan O'Rear <[EMAIL PROTECTED]>:
> > Interestingly, the function is already there; it's called genericLength.
> >
> > However, the lazy natural type isn't.
>
> I'm not sure what you mean there : genericLength is just a length that
> can return any Num (eg. an Integer) and not just Int, it has nothing
> to do with what Andrew wanted, which was a function that checked if a
> list was longer than n without swallowing more of the list than
> necessary.
> Is there something I misunderstood in the exchange ?

Yeah.  The reference to the "lazy natural type", which is:

data Nat
  = Zero
  | Succ Nat
  deriving (Eq, Ord, Read, Show)

instance Num Nat where
  fromInteger 0 = Zero
  fromInteger (n + 1) = Succ (fromInteger n)
  etc.

then genericLength xn > n does exactly what Andrew wants, when n :: Nat.

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy Lists and IO

2007-07-11 Thread Chaddaï Fouché

2007/7/11, Stefan O'Rear <[EMAIL PROTECTED]>:


Interestingly, the function is already there; it's called genericLength.

However, the lazy natural type isn't.


I'm not sure what you mean there : genericLength is just a length that
can return any Num (eg. an Integer) and not just Int, it has nothing
to do with what Andrew wanted, which was a function that checked if a
list was longer than n without swallowing more of the list than
necessary.
Is there something I misunderstood in the exchange ?

--
Jedaï
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Monadic tunnelling: the art of threading one monad through another

2007-07-11 Thread Jules Bean

A programming style which is encouraged in haskell is to write your
program using a special monad, rather than the IO monad. Normally some
mixture of reader and state, possibly writer, the point of these
monads is to help the type system to help you; help you be specific
about which parts of your state can be modified by which parts of your
program.

One problem with this approach comes with what an imperative programmer
would call 'callbacks'. It's quite common with C library interfaces to
take as a parameter an IO action (a callback) which the library will
call with certain parameters. It's even more common with haskell
libraries, although the type then is normally more general than IO;
any higher order function can be thought of as using callbacks.

Now, supposing we have a library function which takes a callback. As
an example, suppose we have a library function which reads in a file
and calls our callback once on each line. A typical type might look
like:

forEachLine :: Handle -> (String -> IO ()) -> IO ()

We have to provide a callback in the IO monad. But what if we don't
want to work in the IO monad? What if we are working in, for example,
a custom state monad of our own?

More generally, is there any sensible way to pass callbacks in one
monad, to an action which runs in a different monad?  What does it
mean to want to do this? In general the 'outer' action can call the
callback as many times as it once, something like this (monospace font
needed!):

m: <- cb ->   <- cb ->
   |  |   |  |
n: -- outer --->  <-- outer -->  <-- outer ---

Now, to embed 'm' into 'n' in this way, we have to somehow 'freeze'
the 'monadiness' (you may prefer to use the term 'the warmth and
fuzziness') of m at the beginning, run the first callback in this
correct environment, then 'freeze' it again just after the callback
runs, and restore this for the second 'cb'. Finally we have to somehow
ensure this 'monadiness' is returned to the caller.

This procedure is not possible for every pair of Monads m and n. They
need to have special properties. It is however possible (for example)
when 'n' is IO, and when 'm' is one of several common custom monads,
as I will now show.

Boring imports give a clue as to which monads I'm going to attempt.

> {-# OPTIONS -fglasgow-exts #-}

Although I have -fglasgow-exts on here, it's actually only necessary
for the MPTC tricks towards the end of the exposition. The initial
discussion is haskell 98 as far as I know.

>
> import Control.Monad.State
> import Control.Monad.Reader
> import Control.Monad.Writer
> import Control.Monad.Error
> import Control.Exception
>
> import Data.Typeable
>
> import Data.IORef

We begin with a callback which is not in the IO monad, but in StateT
Int IO (). StateT monads are very common in real programs (or
hand-rolled equivalents). The simple callback just prints a message so
we know it has happened, and increments the counter in the state so we
can prove state is being correctly threaded.

> -- example small action in the custom monad
> stateioact :: StateT Int IO ()
> stateioact = do
>   x <- get
>   liftIO $ putStrLn ("stateioact called, with state as "++
>  show x)
>   put (x+1)
>

The main action is just a boostrap to call a 'real' main action with
some initial state:

> -- Main action has type IO () as standard
> -- This example main action just defers to another action
> -- which is written in a custom monad
>
> main :: IO ()
> main =  do
>   putStrLn "main starting"
>   evalStateT mainAction 42
>   putStrLn "main exiting"
>

The real main action is a StateT Int IO () action. It calls stateioact
once, then calls a "library function" which is known to use callbacks,
then it calls stateioact again.

> -- mainAction is written in the custom monad
> mainAction :: StateT Int IO ()
> mainAction = do stateioact
> embedIO $ \x -> usesCB (makeCallback stateioact x)
> stateioact
>

The library function is "usesCB". makeCallback and embedIO are the
keys which make it all work.

Here is the library function. Note that it has plain type IO () -> IO
(), just like any library function (e.g. a C FFI function) which takes
a single callback. It prints diagnostic messages and takes care to
call its callback twice, to demonstrate the monad-threading.

> -- a 'library function' in the IO monad, which has a callback as one
> -- of its parameters. The library function has no knowledge of the
> -- custom monad being used by the main action here
> usesCB :: IO () -> IO ()
> usesCB f = do putStrLn "usesCB starting"
>   f
>   putStrLn "usesCB middle"
>   f
>   putStrLn "usesCB exiting"
>

The 'threading' of the monad internals is handled by the dual
functions, embedIO and makeCallback. embedIO turns an IO action
(usesCB in the example above) and makes it into a StateT action. In
that sense, it is doing the same job as 'liftIO'.

Re: [Haskell-cafe] function unique

2007-07-11 Thread Stefan O'Rear
On Wed, Jul 11, 2007 at 04:33:19PM -0500, Jonathan Cast wrote:
> On Wednesday 11 July 2007, you wrote:
> > On Wed, Jul 11, 2007 at 03:59:45PM -0500, Jonathan Cast wrote:
> > > One could put up the Haddock doc-comment.  Or, say, one could extend
> > > Haddock to support parameter names:
> > >
> > > testunique' :: Eq a
> > >   => [a] -- ^ $list List of elements to test
> > > -> [a] -- ^ $elementssofar List of elements seen thus far
> > > -> [a] -- ^ List of unique elements in 'list'.
> > >
> > > No patch forthcoming from this corner, though.
> >
> > None necessary!  Haddock already supports that syntax.
> >
> > http://haskell.org/haddock/haddock-html-0.8/ch03s02.html#id289091
> 
> I think you missed my overloading of the section-label syntax to get argument 
> names.

Indeed.

> And it's not even quite supported; trying the example gets you
> 
> $ haddock -h Foo.hs
> Warning: Foo: the following names could not be resolved:
> Eq list

Uhm... that's a *successful* run.  I think you meant to copy the
messages from a failed run?

Stefan


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


Re: [Haskell-cafe] function unique

2007-07-11 Thread Jonathan Cast
On Wednesday 11 July 2007, you wrote:
> On Wed, Jul 11, 2007 at 03:59:45PM -0500, Jonathan Cast wrote:
> > One could put up the Haddock doc-comment.  Or, say, one could extend
> > Haddock to support parameter names:
> >
> > testunique' :: Eq a
> > => [a] -- ^ $list List of elements to test
> > -> [a] -- ^ $elementssofar List of elements seen thus far
> > -> [a] -- ^ List of unique elements in 'list'.
> >
> > No patch forthcoming from this corner, though.
>
> None necessary!  Haddock already supports that syntax.
>
> http://haskell.org/haddock/haddock-html-0.8/ch03s02.html#id289091

I think you missed my overloading of the section-label syntax to get argument 
names.  And it's not even quite supported; trying the example gets you

$ haddock -h Foo.hs
Warning: Foo: the following names could not be resolved:
Eq list

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type system madness

2007-07-11 Thread Jonathan Cast
On Wednesday 11 July 2007, you wrote:
> Yes, that's one way to define IO.  But it's not the only way.

Right.

Aren't we saying the same thing?

I mean, sure, the *one true way* to define IO is

data IO alpha
  = ReturnIO alpha
  | JoinAtomically (STM (IO alpha))
  | HOpenBind String (Handle -> IO alpha)
  | HCloseThen Handle (IO alpha)
  | HPutThen Handle Char (IO alpha)
  | HGetBind Handle (Char -> IO alpha)
  | ForkIOBind (IO ()) (ThreadId -> IO alpha)
  | UnsafeInterleaveIO (IO (IO alpha))
  | ...

but it's still reasonable to explain that GHC doesn't do it that way and that 
*in GHC*

newtype IO alpha = IO (State# RealWorld -> (# alpha, State# RealWorld #))
newtype ST s alpha
  = ST (State# (STState s) -> (# alpha, State# (STState s) #))

no?  I don't see your objection to it.  Especially if it causes light bulbs to 
go off over people's heads.

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] function unique

2007-07-11 Thread Steve Schafer
On Wed, 11 Jul 2007 22:49:27 +0200, you wrote:

>Well, there's a fundamental reason it wont work for Haskell: we dont
>actually define the names of the parameters to the function!

Yes, but you know the type, which is what really counts. And, taking
that a step further, once you've entered something for the first
argument, a real-time compiler might be able to narrow down the set of
allowed types for the second argument, and so on.

Of course, if you're in the habit of creating functions with type
signatures like Int -> Int -> Int -> Int -> Int -> Int, and you can't
remember which Int does what, then you have only yourself to blame

Steve Schafer
Fenestra Technologies Corp.
http://www.fenestra.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy Lists and IO

2007-07-11 Thread Justin Bailey

On 7/10/07, Ronald Guida <[EMAIL PROTECTED]> wrote:

Hi Everyone,

A few weeks ago, I started learning Haskell (and functional
programming) on my own from the wealth if information on the internet.
I recently read the paper "Why Functional Programming Matters" [1] and
it led me to wonder how to input a lazy list.


Another way to do this using my HCL[1] library:

import HCL

main =
 do
   total <- runRequest $ reqLift sum (reqList $ prompt "Please enter
an integer value (or enter to quit): " reqInteger)
   putStrLn $ "Your entries totaled: " ++ (maybe "nothing!" show total)

Justin

[1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/HCL-1.1
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type system madness

2007-07-11 Thread Lennart Augustsson

Yes, that's one way to define IO.  But it's not the only way.

On 7/11/07, Jonathan Cast <[EMAIL PROTECTED]> wrote:


On Wednesday 11 July 2007, Lennart Augustsson wrote:
> Well, Haskell defines the IO type to be abstract, so if IO and ST happen
to
> be the same it's implementation dependent.

And if IO uses a RealWorld type, that's implementation dependent too.  But
it's still useful to understand both RealWorld as used by IO and the same
mechanism as used by ST.

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type system madness

2007-07-11 Thread Albert Y. C. Lai

Andrew Coppin wrote:
When I tell the editor to save UTF-8, it inserts some weird "BOM" 
character at the start of the file - and thus, any attempt at 
programatically processing that file instantly fails. :-(


I know Windows Notepad puts a BOM at the beginning of UTF-8 files. 
http://www.vex.net/~trebla/w.htm is written out by Notepad and has the 
beginning BOM. Firefox and IE display it just fine. Windows Notepad, 
GNOME gedit, Emacs, Vim, and Eclipse are also very graceful about it. If 
you rename it to w.lhs, GHC reads it as a fine Haskell source file, as I 
sneaked in a little Haskell hello-world as an HTML comment, e.g., 
"runghc w.lhs" does wonder. So much for BOM foiling any processing.


Any more FUD to debunk? Wanna hear something about purely functional 
languages incapacitated for I/O? Static typing leading to excessive type 
declarations? Automatic garbage collection irrelevant to the real world?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy Lists and IO

2007-07-11 Thread Stefan O'Rear
On Wed, Jul 11, 2007 at 09:54:10PM +0100, Andrew Coppin wrote:
> Chaddaï Fouché wrote:
>> There is already many thing in standard library. The balance is important.
>
> I agree.
>
> The question is whether we mind lots of people reimplementing this 
> themselves, each using their own different name for it. I believe I read 
> about some plan to add a trivial function named "on" to one of the standard 
> libraries, because having it there makes code more readable. So the 
> question becomes "does putting this thing in the library make people's code 
> clearer, or is the function trivial enough to reimplement that one can 
> readily see what it's for?"
>
> I'd prefer it in the library (probably Data.List), but it's no biggie.

Interestingly, the function is already there; it's called genericLength.

However, the lazy natural type isn't.

Stefan


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


Re: [Haskell-cafe] function unique

2007-07-11 Thread Stefan O'Rear
On Wed, Jul 11, 2007 at 03:59:45PM -0500, Jonathan Cast wrote: 
> One could put up the Haddock doc-comment.  Or, say, one could extend Haddock 
> to support parameter names:
> 
> testunique' :: Eq a
>   => [a] -- ^ $list List of elements to test
> -> [a] -- ^ $elementssofar List of elements seen thus far
> -> [a] -- ^ List of unique elements in 'list'.
> 
> No patch forthcoming from this corner, though.

None necessary!  Haddock already supports that syntax.

http://haskell.org/haddock/haddock-html-0.8/ch03s02.html#id289091

Stefan


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


Re: [Haskell-cafe] function unique

2007-07-11 Thread Jonathan Cast
On Wednesday 11 July 2007, Hugh Perkins wrote:
> Well, there's a fundamental reason it wont work for Haskell: we dont
> actually define the names of the parameters to the function!
>
> Have a look at the function above, the function is defined as:
>
> testunique' :: Eq a => [a] -> [a] -> [a]
> testunique' [] elementssofar = []
> testunique' (x:xs) elementssofar
>
> There's an agreement here that the second parameter is called
> "elementssofar"... but only because I was consistent in my naming in this
> example.  What if we had multiple constructors for a particular type?
>
> The first argument has no obvious naming at all.
>
> We could do things like write it in comments:
>
> testunique' :: Eq a => [a] -> [a] -> [a]
> -- testunique' :: remainingelements -> elementssofar -> uniqueelements
> testunique' [] elementssofar = []
> testunique' (x:xs) elementssofar
>
> ... but we all know that no-one bothers writing comments, and certainly
> never maintaining them, and in any case this is becoming insanely difficult
> to read.
>
> I dont have a solution, apart from using C# for production programming ;-)
> , but things like this are really important to solve in any "mainstream"
> version of Haskell.

One could put up the Haddock doc-comment.  Or, say, one could extend Haddock 
to support parameter names:

testunique' :: Eq a
=> [a] -- ^ $list List of elements to test
-> [a] -- ^ $elementssofar List of elements seen thus far
-> [a] -- ^ List of unique elements in 'list'.

No patch forthcoming from this corner, though.

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy Lists and IO

2007-07-11 Thread Andrew Coppin

Chaddaï Fouché wrote:
There is already many thing in standard library. The balance is 
important.


I agree.

The question is whether we mind lots of people reimplementing this 
themselves, each using their own different name for it. I believe I read 
about some plan to add a trivial function named "on" to one of the 
standard libraries, because having it there makes code more readable. So 
the question becomes "does putting this thing in the library make 
people's code clearer, or is the function trivial enough to reimplement 
that one can readily see what it's for?"


I'd prefer it in the library (probably Data.List), but it's no biggie.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy Lists and IO

2007-07-11 Thread Jonathan Cast
On Wednesday 11 July 2007, Chaddaï Fouché wrote:
> There is already many thing in standard library. The balance is important.
> You can write :
> longerThan n = (> n) . length . take (n+1)
> and it isn't so current a need that you want it into a library that
> already has many functions.

Shorter:

longerThan n = not . null . drop n

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy Lists and IO

2007-07-11 Thread Chaddaï Fouché

2007/7/11, Stefan O'Rear <[EMAIL PROTECTED]>:

It was not infinite.  This has nothing to do with infiniteness.

This has to do with Lazy lists and IO.

Specifically, reading to the end of a list of responses - before sending
all the requests.

Waiting for the second responce before sending the second request caused
a deadlock, even though only a finite number of responces would be
received.


Ah, ok, I read too quickly... Still not the most current case.

--
Jedaï
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] function unique

2007-07-11 Thread Hugh Perkins

Well, there's a fundamental reason it wont work for Haskell: we dont
actually define the names of the parameters to the function!

Have a look at the function above, the function is defined as:

testunique' :: Eq a => [a] -> [a] -> [a]
testunique' [] elementssofar = []
testunique' (x:xs) elementssofar

There's an agreement here that the second parameter is called
"elementssofar"... but only because I was consistent in my naming in this
example.  What if we had multiple constructors for a particular type?

The first argument has no obvious naming at all.

We could do things like write it in comments:

testunique' :: Eq a => [a] -> [a] -> [a]
-- testunique' :: remainingelements -> elementssofar -> uniqueelements
testunique' [] elementssofar = []
testunique' (x:xs) elementssofar

... but we all know that no-one bothers writing comments, and certainly
never maintaining them, and in any case this is becoming insanely difficult
to read.

I dont have a solution, apart from using C# for production programming ;-) ,
but things like this are really important to solve in any "mainstream"
version of Haskell.

On 7/11/07, Steve Schafer <[EMAIL PROTECTED]> wrote:


On Wed, 11 Jul 2007 22:39:27 +0200, you wrote:

>In C#, when you call a function you type "(" and instantly you get a
popup
>box telling you what the name of the first argument is, then when you've
>written the first argument and hit "," you get the name (and type) of the
>second argument.

That's not a feature of C# itself, but rather a feature of the
development environment you're using. You can write C# code in NotePad,
and I will guarantee you that you won't see any such popups. ;)

There do exist various development environments for Haskell, but I don't
think any of them are particularly popular.

Steve Schafer
Fenestra Technologies Corp.
http://www.fenestra.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy Lists and IO

2007-07-11 Thread Chaddaï Fouché

There is already many thing in standard library. The balance is important.
You can write :
longerThan n = (> n) . length . take (n+1)
and it isn't so current a need that you want it into a library that
already has many functions.

--
Jedaï
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy Lists and IO

2007-07-11 Thread Stefan O'Rear
On Wed, Jul 11, 2007 at 10:33:06PM +0200, Chaddaï Fouché wrote:
> 2007/7/11, Andrew Coppin <[EMAIL PROTECTED]>:
>>
>> Ouch! That's gotta sting...
>>
>> I wasn't aware that this function was so leathal. I use it constantly
>> all the time...
>>
>
> It isn't that "lethal" usually. It's only because he was using it on
> an infinite stream that it hurt so much... If you use it on a normal
> stdin or a hGetContents on a file it will be fine (though you will
> lose the advantage of its laziness, for example constant memory
> treatment).

It was not infinite.  This has nothing to do with infiniteness.

This has to do with Lazy lists and IO.

Specifically, reading to the end of a list of responses - before sending
all the requests.

Waiting for the second responce before sending the second request caused
a deadlock, even though only a finite number of responces would be
received.

Stefan


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


Re: [Haskell-cafe] haskell -> db, on Solaris

2007-07-11 Thread Bryan O'Sullivan

Daniil Elovkov wrote:


Yes, thanks. But the emphasis was on Solaris. I don't quite understand
what is the common way to access databases on Solaris. Is it odbc?


ODBC is a standard, fairly portable database interface.  Since HDBC has 
ODBC bindings, it can in principle talk to any database that provides an 
ODBC interface.

http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] function unique

2007-07-11 Thread Steve Schafer
On Wed, 11 Jul 2007 22:39:27 +0200, you wrote:

>In C#, when you call a function you type "(" and instantly you get a popup
>box telling you what the name of the first argument is, then when you've
>written the first argument and hit "," you get the name (and type) of the
>second argument.

That's not a feature of C# itself, but rather a feature of the
development environment you're using. You can write C# code in NotePad,
and I will guarantee you that you won't see any such popups. ;)

There do exist various development environments for Haskell, but I don't
think any of them are particularly popular.

Steve Schafer
Fenestra Technologies Corp.
http://www.fenestra.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] function unique

2007-07-11 Thread Andrew Coppin

Hugh Perkins wrote:

By the way, this is something that is hard in Haskell compared to say C#.

In C#, when you call a function you type "(" and instantly you get a 
popup box telling you what the name of the first argument is, then 
when you've written the first argument and hit "," you get the name 
(and type) of the second argument.


It's pretty hard not to put the right arguments in the right order.

Not so in Haskell where I spend insane amounts of time trying to 
remember what argument is what in a function I wrote 30 seconds ago.


Good point!

Hmm... sounds kind of hard to do in Haskell. I mean, the function might 
be curried. ;-) Still, you'd think it's doable.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy Lists and IO

2007-07-11 Thread Andrew Coppin

Chaddaï Fouché wrote:

2007/7/11, Andrew Coppin <[EMAIL PROTECTED]>:


Ouch! That's gotta sting...

I wasn't aware that this function was so leathal. I use it constantly
all the time...



It isn't that "lethal" usually. It's only because he was using it on
an infinite stream that it hurt so much... If you use it on a normal
stdin or a hGetContents on a file it will be fine (though you will
lose the advantage of its laziness, for example constant memory
treatment).



Loose lazyness?

Oh wait - you mean the inadvertent length thing?



We already have null, but how about a standard function in Data.List for 
testing whether the length is longer than some upper limit?


 lengthUpTo :: Int -> [x] -> Int
 lengthUpTo n = length . take n

 shorterThan :: Int -> Bool
 shorterThan n = (n >) . lengthUpTo (n+1)

 longerThan :: Int -> Bool
 longerThan n = (n <) . lengthUpTo n

 lengthEquals :: Int -> Bool
 lengthEquals n = (n ==) . lengthUpTo (n+1)

(Perhaps need better names...)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] function unique

2007-07-11 Thread Hugh Perkins

By the way, this is something that is hard in Haskell compared to say C#.

In C#, when you call a function you type "(" and instantly you get a popup
box telling you what the name of the first argument is, then when you've
written the first argument and hit "," you get the name (and type) of the
second argument.

It's pretty hard not to put the right arguments in the right order.

Not so in Haskell where I spend insane amounts of time trying to remember
what argument is what in a function I wrote 30 seconds ago.

On 7/11/07, Hugh Perkins <[EMAIL PROTECTED]> wrote:


Oh, lol because I'm stupid and put the arguments the wrong way around in
the first recursive call to testunique' ;-)

On 7/11/07, Hugh Perkins < [EMAIL PROTECTED]> wrote:
>
> Ok so I played with the tweaked problem (Unix 'uniq'), and getting it to
> be lazy.  This seems to work:
>
> testunique :: Eq a => [a] -> [a]
> testunique list = testunique' list []
>where testunique' :: Eq a => [a] -> [a] -> [a]
>  testunique' [] elementssofar = []
>  testunique' (x:xs) elementssofar | x `elem` elementssofar =
> (testunique' elementssofar xs)
>   | otherwise = x : (
> testunique' xs (x:elementssofar))
>
>
> Now, a question, why is this happening:
>
> doesnt block:
>
> take 10 (testunique ([1,3] ++ [7..]))
> take 10 (testunique ([7..] ++ [1,3,7]))
>
> blocks forever:
>
> take 10 (testunique ([1,3,7] ++ [7..]))
>
> The expression ([1,3,7] ++ [7..]) itself doesnt block: things like
> "take 10 ( [1,3,7] ++ [7 ..] )" work just fine, so what is going on?
>
> On 7/11/07, Dan Weston <[EMAIL PROTECTED]> wrote:
> >
> > Alexteslin wrote:
> > > I'v got it - it produces the right output.
> > > Thank you.
> >
> > Now that you've done the exercise, the fun starts! What assumptions
> > did
> > you build in to your solution?
> >
> > 1) You just need uniqueness, so counting the number of copies is not
> > only overkill, but requires you to go through the entire list to count
> > them.
> >
> > 2) The list might be infinite, and your function should work if you
> > make
> > only want to use the first part of it, so the following should return
> > [1,2,3,4,5] in a finite amount of time:
> >
> > take 5 (unique [1..])
> >
> > Your algorithm fails both of these. Consider a *lazy* approach:
> >
> > 1) Keep the head of the list
> > 2) Then filter the tail, keeping only elements different from the head
> >
> > 3) Then put the two together
> >
> > Don't worry in step #2 about having an infinite number of list
> > elements
> > to be filtered out of the list. Think of it like asking a lazy child
> > to
> > clean the house. They're only going to do it just before mom gets home
> >
> > (who knows, with any luck she'll be in a car crash and forget about
> > having asked you to clean!)
> >
> > This works for infinite lists, and puts off the work until you
> > actually
> > need the elements.
> >
> > I won't cheat you out of the fun, but here's the solution to a *very*
> > similar problem using the Sieve of Eratosthenes to find prime numbers:
> >
> > isNotDivisor divisor dividend = dividend `rem` divisor /= 0
> >
> > keepOnlyLowestMultiple (x:xs) =
> >x : keepOnlyLowestMultiple (filter (isNotDivisor x) xs)
> >
> > primes = keepOnlyLowestMultiple [2..]
> >
> > Dan
> >
> > > Brent Yorgey wrote:
> > >> The problem with your second implementation is that elements which
> > occur
> > >> more than once will eventually be included, when the part of the
> > list
> > >> remaining only has one copy. For example:
> > >>
> > >> unique2 [1,1,2,4,1]
> > >> = unique2 [1,2,4,1]
> > >> = unique2 [2,4,1]
> > >> = 2 : unique2 [4,1]
> > >> = 2 : 4 : unique2 [1]
> > >> = 2 : 4 : 1 : unique2 []   -- only a single 1 left, so it gets
> > mistakenly
> > >> included
> > >> = [2,4,1]
> > >>
> > >> When you determine that a certain number should not be included in
> > the
> > >> output, you need to delete all remaining occurrences of it from the
> > list,
> > >> so
> > >> it won't get included later.
> > >>
> > >> unique2 (x:xs)
> > >> |elemNum2 x xs == 1 = x:unique2 xs
> > >> |otherwise = unique2 (deleteElt x xs)
> > >>
> > >> I'll let you figure out how to implement the deleteElt function.
> > >>
> > >> hope this is helpful!
> > >> -Brent
> > >>
> > >> On 7/10/07, Alexteslin <[EMAIL PROTECTED]> wrote:
> > >>>
> > >>> Hi, i am a beginner to Haskell and i have a beginner's question to
> > ask.
> > >>>
> > >>> An exercise asks to define function unique :: [Int] -> [Int],
> > which
> > >>> outputs
> > >>> a list with only elements that are unique to the input list (that
> > appears
> > >>> no
> > >>> more than once).  I defined a function with list comprehension
> > which
> > >>> works
> > >>> but trying to implement with pattern matching and primitive
> > recursion
> > >>> with
> > >>> lists and doesn't work.
> > >>>
> > >>> unique :: [Int] -> [Int]
> > >>> unique xs = [x | x <- xs, elemNum2 x xs == 1]
> > >>>
> > >>>
> > >>> elemNum2 :: I

Re: [Haskell-cafe] In-place modification

2007-07-11 Thread Henning Thielemann

On Tue, 10 Jul 2007, Jon Harrop wrote:

> On Tuesday 10 July 2007 21:19:42 Andrew Coppin wrote:
> > Hugh Perkins wrote:
> > > Yeah I agree with this.  C# totally rocks, but threading is an
> > > unsolved problem.
> >
> > I have repeatedly attempted to discover what C# actually is...
>
> Take Java. Make it Windows only. Fix some mistakes. Tweak performance. Add a
> little functionality (e.g. operator overloading). That is C#.

... still talking about "In-place modification" ?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type system madness

2007-07-11 Thread Jonathan Cast
On Wednesday 11 July 2007, Lennart Augustsson wrote:
> Well, Haskell defines the IO type to be abstract, so if IO and ST happen to
> be the same it's implementation dependent.

And if IO uses a RealWorld type, that's implementation dependent too.  But 
it's still useful to understand both RealWorld as used by IO and the same 
mechanism as used by ST.

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] function unique

2007-07-11 Thread Hugh Perkins

Oh, lol because I'm stupid and put the arguments the wrong way around in the
first recursive call to testunique' ;-)

On 7/11/07, Hugh Perkins <[EMAIL PROTECTED]> wrote:


Ok so I played with the tweaked problem (Unix 'uniq'), and getting it to
be lazy.  This seems to work:

testunique :: Eq a => [a] -> [a]
testunique list = testunique' list []
   where testunique' :: Eq a => [a] -> [a] -> [a]
 testunique' [] elementssofar = []
 testunique' (x:xs) elementssofar | x `elem` elementssofar =
(testunique' elementssofar xs)
  | otherwise = x : ( testunique'
xs (x:elementssofar))


Now, a question, why is this happening:

doesnt block:

take 10 (testunique ([1,3] ++ [7..]))
take 10 (testunique ([7..] ++ [1,3,7]))

blocks forever:

take 10 (testunique ([1,3,7] ++ [7..]))

The expression ([1,3,7] ++ [7..]) itself doesnt block: things like  "take
10 ( [1,3,7] ++ [7 ..] )" work just fine, so what is going on?

On 7/11/07, Dan Weston <[EMAIL PROTECTED]> wrote:
>
> Alexteslin wrote:
> > I'v got it - it produces the right output.
> > Thank you.
>
> Now that you've done the exercise, the fun starts! What assumptions did
> you build in to your solution?
>
> 1) You just need uniqueness, so counting the number of copies is not
> only overkill, but requires you to go through the entire list to count
> them.
>
> 2) The list might be infinite, and your function should work if you make
> only want to use the first part of it, so the following should return
> [1,2,3,4,5] in a finite amount of time:
>
> take 5 (unique [1..])
>
> Your algorithm fails both of these. Consider a *lazy* approach:
>
> 1) Keep the head of the list
> 2) Then filter the tail, keeping only elements different from the head
> 3) Then put the two together
>
> Don't worry in step #2 about having an infinite number of list elements
> to be filtered out of the list. Think of it like asking a lazy child to
> clean the house. They're only going to do it just before mom gets home
> (who knows, with any luck she'll be in a car crash and forget about
> having asked you to clean!)
>
> This works for infinite lists, and puts off the work until you actually
> need the elements.
>
> I won't cheat you out of the fun, but here's the solution to a *very*
> similar problem using the Sieve of Eratosthenes to find prime numbers:
>
> isNotDivisor divisor dividend = dividend `rem` divisor /= 0
>
> keepOnlyLowestMultiple (x:xs) =
>x : keepOnlyLowestMultiple (filter (isNotDivisor x) xs)
>
> primes = keepOnlyLowestMultiple [2..]
>
> Dan
>
> > Brent Yorgey wrote:
> >> The problem with your second implementation is that elements which
> occur
> >> more than once will eventually be included, when the part of the list
>
> >> remaining only has one copy. For example:
> >>
> >> unique2 [1,1,2,4,1]
> >> = unique2 [1,2,4,1]
> >> = unique2 [2,4,1]
> >> = 2 : unique2 [4,1]
> >> = 2 : 4 : unique2 [1]
> >> = 2 : 4 : 1 : unique2 []   -- only a single 1 left, so it gets
> mistakenly
> >> included
> >> = [2,4,1]
> >>
> >> When you determine that a certain number should not be included in
> the
> >> output, you need to delete all remaining occurrences of it from the
> list,
> >> so
> >> it won't get included later.
> >>
> >> unique2 (x:xs)
> >> |elemNum2 x xs == 1 = x:unique2 xs
> >> |otherwise = unique2 (deleteElt x xs)
> >>
> >> I'll let you figure out how to implement the deleteElt function.
> >>
> >> hope this is helpful!
> >> -Brent
> >>
> >> On 7/10/07, Alexteslin <[EMAIL PROTECTED]> wrote:
> >>>
> >>> Hi, i am a beginner to Haskell and i have a beginner's question to
> ask.
> >>>
> >>> An exercise asks to define function unique :: [Int] -> [Int], which
> >>> outputs
> >>> a list with only elements that are unique to the input list (that
> appears
> >>> no
> >>> more than once).  I defined a function with list comprehension which
> >>> works
> >>> but trying to implement with pattern matching and primitive
> recursion
> >>> with
> >>> lists and doesn't work.
> >>>
> >>> unique :: [Int] -> [Int]
> >>> unique xs = [x | x <- xs, elemNum2 x xs == 1]
> >>>
> >>>
> >>> elemNum2 :: Int -> [Int] -> Int
> >>> elemNum2 el xs = length [x| x <- xs, x == el]
> >>>
> >>> //This doesn't work, I know because the list shrinks and produces
> wrong
> >>> result but can not get a right //thinking
> >>>
> >>> unique2 :: [Int] -> [Int]
> >>> unique2 [] = []
> >>> unique2 (x:xs)
> >>> |elemNum2 x xs == 1 = x:unique2 xs
> >>> |otherwise = unique2 xs
> >>>
> >>>
> >>> Any help to a right direction would be very appreciated, thanks.
> >>> --
> >>> View this message in context:
> >>> http://www.nabble.com/function-unique-tf4058328.html#a11528933
> >>> Sent from the Haskell - Haskell-Cafe mailing list archive at
> Nabble.com.
> >>>
> >>> ___
> >>> Haskell-Cafe mailing list
> >>> Haskell-Cafe@haskell.org
> >>> http://www.haskell.org/mailman/listinfo/haskell-cafe
> >>>
> >> 

Re: [Haskell-cafe] Lazy Lists and IO

2007-07-11 Thread Chaddaï Fouché

2007/7/11, Andrew Coppin <[EMAIL PROTECTED]>:


Ouch! That's gotta sting...

I wasn't aware that this function was so leathal. I use it constantly
all the time...



It isn't that "lethal" usually. It's only because he was using it on
an infinite stream that it hurt so much... If you use it on a normal
stdin or a hGetContents on a file it will be fine (though you will
lose the advantage of its laziness, for example constant memory
treatment).

--
Jedaï
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] haskell -> db, on Solaris

2007-07-11 Thread Alistair Bayley

> 
http://www.haskell.org/haskellwiki/Applications_and_libraries/Database_interfaces
>
> If you want to talk to MySQL, you have a few choices.
>
> HDBC has an ODBC interface that lets you use any ODBC provider, so
> you'll be able to talk to both MySQL and Oracle with it.
>
> HaskellDB can bridge to HDBC, I believe, so that will let you do
> type-safe SQL.
>
> There's also Takusen, which can talk to Oracle, but not MySQL.

Yes, thanks. But the emphasis was on Solaris. I don't quite understand
what is the common way to access databases on Solaris. Is it odbc? And
how Haskell libraries connect to that? I mean, Takusen is designed to
use odbc and nothing else (afaik), for example.


Takusen uses OCI to talk to Oracle, so it should work on any Oracle (&
GHC) platform. However, no ODBC or MySQL backend yet (I'm working on
ODBC right now, but it's slow going...).

I imagine that the common way to access databases on Solaris is the
same as on other Unix platforms, which is probably to use the vendor's
API directly. There is also http://www.unixodbc.org/, which appears to
support Solaris, but I can't vouch for it from a usability perspective
i.e. how hard is it to get working, and to get working with HDBC or
HSQL.

I'd recommend giving unixodbc + hsql/hdbc a go, and let us know of any problems.

Alistair
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] xkcd #287 "NP-Complete"

2007-07-11 Thread Henning Thielemann

On Tue, 10 Jul 2007, Hugh Perkins wrote:

> By the way, if you enjoy these problems, there are tons of these at
> topcoder.com  I cant help thinking it'd be neat to have topcoder-like
> competitions for Haskell, either by pursuading topcoder to integrate support
> for Haskell, or hosting our own.

Is this related to
 http://www.haskell.org/haskellwiki/Great_language_shootout ?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] function unique

2007-07-11 Thread Hugh Perkins

Ok so I played with the tweaked problem (Unix 'uniq'), and getting it to be
lazy.  This seems to work:

testunique :: Eq a => [a] -> [a]
testunique list = testunique' list []
  where testunique' :: Eq a => [a] -> [a] -> [a]
testunique' [] elementssofar = []
testunique' (x:xs) elementssofar | x `elem` elementssofar =
(testunique' elementssofar xs)
 | otherwise = x : ( testunique' xs
(x:elementssofar))


Now, a question, why is this happening:

doesnt block:

take 10 (testunique ([1,3] ++ [7..]))
take 10 (testunique ([7..] ++ [1,3,7]))

blocks forever:

take 10 (testunique ([1,3,7] ++ [7..]))

The expression ([1,3,7] ++ [7..]) itself doesnt block: things like  "take 10
( [1,3,7] ++ [7 ..] )" work just fine, so what is going on?

On 7/11/07, Dan Weston <[EMAIL PROTECTED]> wrote:


Alexteslin wrote:
> I'v got it - it produces the right output.
> Thank you.

Now that you've done the exercise, the fun starts! What assumptions did
you build in to your solution?

1) You just need uniqueness, so counting the number of copies is not
only overkill, but requires you to go through the entire list to count
them.

2) The list might be infinite, and your function should work if you make
only want to use the first part of it, so the following should return
[1,2,3,4,5] in a finite amount of time:

take 5 (unique [1..])

Your algorithm fails both of these. Consider a *lazy* approach:

1) Keep the head of the list
2) Then filter the tail, keeping only elements different from the head
3) Then put the two together

Don't worry in step #2 about having an infinite number of list elements
to be filtered out of the list. Think of it like asking a lazy child to
clean the house. They're only going to do it just before mom gets home
(who knows, with any luck she'll be in a car crash and forget about
having asked you to clean!)

This works for infinite lists, and puts off the work until you actually
need the elements.

I won't cheat you out of the fun, but here's the solution to a *very*
similar problem using the Sieve of Eratosthenes to find prime numbers:

isNotDivisor divisor dividend = dividend `rem` divisor /= 0

keepOnlyLowestMultiple (x:xs) =
   x : keepOnlyLowestMultiple (filter (isNotDivisor x) xs)

primes = keepOnlyLowestMultiple [2..]

Dan

> Brent Yorgey wrote:
>> The problem with your second implementation is that elements which
occur
>> more than once will eventually be included, when the part of the list
>> remaining only has one copy. For example:
>>
>> unique2 [1,1,2,4,1]
>> = unique2 [1,2,4,1]
>> = unique2 [2,4,1]
>> = 2 : unique2 [4,1]
>> = 2 : 4 : unique2 [1]
>> = 2 : 4 : 1 : unique2 []   -- only a single 1 left, so it gets
mistakenly
>> included
>> = [2,4,1]
>>
>> When you determine that a certain number should not be included in the
>> output, you need to delete all remaining occurrences of it from the
list,
>> so
>> it won't get included later.
>>
>> unique2 (x:xs)
>> |elemNum2 x xs == 1 = x:unique2 xs
>> |otherwise = unique2 (deleteElt x xs)
>>
>> I'll let you figure out how to implement the deleteElt function.
>>
>> hope this is helpful!
>> -Brent
>>
>> On 7/10/07, Alexteslin <[EMAIL PROTECTED]> wrote:
>>>
>>> Hi, i am a beginner to Haskell and i have a beginner's question to
ask.
>>>
>>> An exercise asks to define function unique :: [Int] -> [Int], which
>>> outputs
>>> a list with only elements that are unique to the input list (that
appears
>>> no
>>> more than once).  I defined a function with list comprehension which
>>> works
>>> but trying to implement with pattern matching and primitive recursion
>>> with
>>> lists and doesn't work.
>>>
>>> unique :: [Int] -> [Int]
>>> unique xs = [x | x <- xs, elemNum2 x xs == 1]
>>>
>>>
>>> elemNum2 :: Int -> [Int] -> Int
>>> elemNum2 el xs = length [x| x <- xs, x == el]
>>>
>>> //This doesn't work, I know because the list shrinks and produces
wrong
>>> result but can not get a right //thinking
>>>
>>> unique2 :: [Int] -> [Int]
>>> unique2 [] = []
>>> unique2 (x:xs)
>>> |elemNum2 x xs == 1 = x:unique2 xs
>>> |otherwise = unique2 xs
>>>
>>>
>>> Any help to a right direction would be very appreciated, thanks.
>>> --
>>> View this message in context:
>>> http://www.nabble.com/function-unique-tf4058328.html#a11528933
>>> Sent from the Haskell - Haskell-Cafe mailing list archive at
Nabble.com.
>>>
>>> ___
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe@haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
>


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
h

Re: [Haskell-cafe] better error expression in IO function

2007-07-11 Thread Andrew Coppin

brad clawsie wrote:

i am working on improving a module for getting Yahoo Finance quote
data, hopefully getting it to a point that i can put it on hackage

in the quote retrieval function, there are a few places i would like
to call out errors. in a trivial case i could return 

IO (Maybe String) 


with Nothing signifying any error state, or Just expressing the data

but i would like to be able to express some of these error cases in a
more structured manner

i know the Either type can be used in such a case(?), but i've had some
problem locating a satisfactory example (if this is indeed
appropriate)

could one of the vets here provide a simplistic example expressing
error cases, preferrably in the IO Monad (in case there are any
gotchas there)?
  


It's fairly common to use the Either type for this. By convention, 
"Right" means "correct", and by elimination "Left" means an error...


 foo x = case x of
    return (Right y)
    return (Left "Some error happened")

Instead of just returning a text string indicating the error condition, 
you could devize your own special type for representing the possible 
errors that can happen.


You could also make a kind of a "Result" type that represents both 
successful *and* failed results, if you prefer.


In addition, in the IO monad, I believe you can do fun stuff with 
exceptions. Specifically, you can *catch* them. However, beware: Haskell 
has something of a habit of executing stuff at unpredictable times, 
which means that if you're throwing errors in pure code, it can be hard 
to register the exception handler(s) at the right time! Probably simpler 
and clearer to go with Either or something OTOH, if you're throwing 
errors from within the IO monad itself, timing should be less of an issue.


Just my few cents...

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] function unique

2007-07-11 Thread Hugh Perkins

Simple answer: you always have to have the single element first, then the
list bit second.  It's just the way it is.  You can learn why later on ;-)

On 7/11/07, Alexteslin <[EMAIL PROTECTED]> wrote:



Oh, I am lost now - for now anyway.
I am attempting to do next exercise in the book to define reverse function
using primitive recursion and pattern matching on lists.  But getting
stack
because when i con in front of xs (xs:x) i get en error, which i thought i
would be getting anyway.  I tried to define a helper function and cons
there
in front of xs and i get type errors again.

I know these are easy and boring questions but i would appreciate a hint.

Thank you


Neil Mitchell wrote:
>
> Hi
>
>> unique = unique' []
>>
>> unique' _ [] = []
>> unique' history (x:xs) = if x `elem` history
>>   then next
>>   else (x:next) where next = (uniq' (x:hist) xs)
>
> You can express this more neatly:
>
> unique' _ [] = []
> unique' history (x:xs) = [x | x `notElem` history] ++ unique'
(x:history)
> xs
>
> Thanks
>
> Neil
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>

--
View this message in context:
http://www.nabble.com/function-unique-tf4058328.html#a11547781
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Number overflow [was: Strange results when trying to create large Bool arrays.]

2007-07-11 Thread Andrew Coppin

Stefan O'Rear wrote:

On Wed, Jul 11, 2007 at 08:16:50PM +0100, Andrew Coppin wrote:
  
Of course, sometimes you purposely write code which you know is going to 
overflow and wrap round in a specific way. But frequently you *don't* want 
this behaviour - and I wish there were some pragma or something to make 
this be checked. AFAIK, most CPU types give you an efficient way to testing 
for such conditions...



Indeed.  I beleive that Int should be removed from the Prelude.  People
who need the algebraic properties of rings modulo 2^(2^n) can use the
sized integral types from Data.Int and Data.Word; people who want speed
and can satisfy the proof obligations can use Int and Word from the same
modules.  Everyone else can use Integer, which should be made shorter than
Int for obvious psychological reasons.
  


Do we really want to do that?

I mean, make Haskell in general 2 orders of magnitude slower (and heaven 
knows how many orders of magnitude more RAM hungry) for any program 
using more than a handful of integers?


Personally, I'd prefer a way to just throw an exception when a numeric 
overflow happens. (Probably only for test purposes - so maybe a compiler 
flag?)


How about the floating-point types? What do they currently do?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Number overflow

2007-07-11 Thread Andrew Coppin

Lennart Augustsson wrote:
Yes, I think we want Integer to be the type that is used unless you 
ask for something else.

It adheres to the principle of getting it right before optimizing.


What, as in the way that simple strings are lists, and you change it to 
something less flexible but faster if you actually need it?


I suppose that makes some sense...

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Number overflow [was: Strange results when trying to create large Bool arrays.]

2007-07-11 Thread Lennart Augustsson

Yes, I think we want Integer to be the type that is used unless you ask for
something else.
It adheres to the principle of getting it right before optimizing.

On 7/11/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:


Stefan O'Rear wrote:
> On Wed, Jul 11, 2007 at 08:16:50PM +0100, Andrew Coppin wrote:
>
>> Of course, sometimes you purposely write code which you know is going
to
>> overflow and wrap round in a specific way. But frequently you *don't*
want
>> this behaviour - and I wish there were some pragma or something to make
>> this be checked. AFAIK, most CPU types give you an efficient way to
testing
>> for such conditions...
>>
>
> Indeed.  I beleive that Int should be removed from the Prelude.  People
> who need the algebraic properties of rings modulo 2^(2^n) can use the
> sized integral types from Data.Int and Data.Word; people who want speed
> and can satisfy the proof obligations can use Int and Word from the same
> modules.  Everyone else can use Integer, which should be made shorter
than
> Int for obvious psychological reasons.
>

Do we really want to do that?

I mean, make Haskell in general 2 orders of magnitude slower (and heaven
knows how many orders of magnitude more RAM hungry) for any program
using more than a handful of integers?

Personally, I'd prefer a way to just throw an exception when a numeric
overflow happens. (Probably only for test purposes - so maybe a compiler
flag?)

How about the floating-point types? What do they currently do?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] Type system madness

2007-07-11 Thread Lennart Augustsson

Well, Haskell defines the IO type to be abstract, so if IO and ST happen to
be the same it's implementation dependent.

 -- Lennart

On 7/11/07, Bulat Ziganshin <[EMAIL PROTECTED]> wrote:


Hello Andrew,

Tuesday, July 10, 2007, 11:49:37 PM, you wrote:

>>> ...so the 's' doesn't really "exist", it's just random hackery of the
>>> type system to implement uniqueness?
>>>
>>
>> Exactly.
>>

> Hmm. Like the IO monad's RealWorld object, which isn't really there?

ST and IO monads are the same beast. in ST, s is free to allow to
create endless amount of independent threads while in IO it fixed to
one type and describes evolution of one thread, synchronized with real
world. look at http://haskell.org/haskellwiki/IO_inside for info about
IO monad trickery


--
Best regards,
Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type system madness

2007-07-11 Thread Jonathan Cast
On Wednesday 11 July 2007, Martin Percossi wrote:
> Jonathan Cast wrote:
> > toUpper :: exists x. x -> x works for only one choice of x.
>
> Are you sure that's not:
>
> "toUpper :: exists x. x -> x works for *at least one* choice of x"

Not quite.  When you give a constructive proof of exists x. x -> x, you only 
prove it at one value of x, and a value of type exists x. x -> x is just such 
a proof.  When you go and use that proof, you can thus only use it at one 
type.  Thus, properly speaking, a value of type exists x. x -> x should be 
thought of as a pair of a type x and a (monomorphic) function of type x -> x.  
So when you eliminate the existential quantifier, you get a function of type 
x -> x for precisely one (unknown) type.  That type is the same every time, 
in fact, although the compiler won't let you use this fact (doing so would 
turn the existential quantifier into a dependent sum).



Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] function unique

2007-07-11 Thread Brent Yorgey

On 7/11/07, Alexteslin <[EMAIL PROTECTED]> wrote:



Oh, I am lost now - for now anyway.
I am attempting to do next exercise in the book to define reverse function
using primitive recursion and pattern matching on lists.  But getting
stack
because when i con in front of xs (xs:x) i get en error, which i thought i
would be getting anyway.  I tried to define a helper function and cons
there
in front of xs and i get type errors again.

I know these are easy and boring questions but i would appreciate a hint.

Thank you



Let's look at the type of the cons operator:

Prelude> :t (:)
(:) :: a -> [a] -> [a]

That is, it takes an element of any type (here represented by 'a'), and a
list of the same type, and produces a list.  So (xs:x) does not make sense,
assuming that xs is a list and x has the same type as an element of xs; cons
expects an element followed by a list, and you are giving it a list followed
by an element.  If you want to append an element onto the end of a list you
can do

xs ++ [x]

++ is the list append operator, so this says "make x into a list with one
element, and append it onto the end of the list xs".

Does that help?  It's hard to help without seeing any code or the specific
errors you are seeing, but hopefully that should give you a push in the
right direction.

-Brent
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Very freaky

2007-07-11 Thread Andrew Coppin

Jim Burton wrote:

Andrew Coppin wrote:
  
The other downside is that you end up with a world where most of the 
"tools" are in fact one-man research projects or small toys.


There are a few good, powerful, useful things out there. (GHC and Parsec 
immediately spring to mind.) But there's also a vast number of really 
tiny projects which don't seem to be terrifically well supported. Kind 
of makes me sad; Haskell seems almost doomed to be a language with 
fantastic potential, but little real-world traction.


AFAIK Haskell wasn't designed for real-world traction in the first place,
but as a way of consolidating FP research efforts onto one platform, so in
that sense it's a resounding success rather than "doomed". It also seems to
have gained some traction, and we know that FP can be an eminently practical
real-world secret weapon, so the tools you're waiting for someone else to
write could well be on their way. At the same time, the only evidence for
this at the moment is a lot of blogs, O'Reilly investing in a book and
Eternal September on haskell-cafe. If you want a language with a bigger user
base or that is less confusing, there are plenty to choose from.
  


The *language* I love. Haskell is usually a joy to program with.

The lack of real-world traction can be very frustrating though. It's 
like I just found the perfect programming language, and I can't really 
use it for very much... :-(


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] function unique

2007-07-11 Thread Brent Yorgey


> I don't think this is possible.  Perhaps you misread the original
problem
> description?  The unique function is supposed to return a list of those
> elements which occur exactly once in the input list, which is impossible
to
> determine for an infinite input list (the only way to prove that a given
> element occurs only once in a list, in the absence of any other
information,
> is to examine every element of the list).  Of course, a function that
> behaves like the unix utility "uniq" ( i.e. returning only one copy of
every
> list element) is possible to implement lazily in the manner you
describe.

Why wouldn't this work?  (I haven't tested it, sorry)

unique = unique' []

unique' _ [] = []
unique' history (x:xs) = if x `elem` history
  then next
  else (x:next) where next = (uniq' (x:hist) xs)



Again, this is solving a different problem than  what the OP stated. Using
your definition:

Prelude> :l unique
[1 of 1] Compiling Main ( unique.hs, interpreted )
Ok, modules loaded: Main.
*Main> unique [1,2,3,1]
[1,2,3]
*Main>

...which behaves like the Unix utility 'uniq'.  But the problem described
originally is to write a function which produces [2,3] when given the same
input; 1 is not included in the output since it occurs more than once.

-Brent
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] function unique

2007-07-11 Thread Alexteslin

Oh, I am lost now - for now anyway.  
I am attempting to do next exercise in the book to define reverse function
using primitive recursion and pattern matching on lists.  But getting stack
because when i con in front of xs (xs:x) i get en error, which i thought i
would be getting anyway.  I tried to define a helper function and cons there
in front of xs and i get type errors again.

I know these are easy and boring questions but i would appreciate a hint.

Thank you


Neil Mitchell wrote:
> 
> Hi
> 
>> unique = unique' []
>>
>> unique' _ [] = []
>> unique' history (x:xs) = if x `elem` history
>>   then next
>>   else (x:next) where next = (uniq' (x:hist) xs)
> 
> You can express this more neatly:
> 
> unique' _ [] = []
> unique' history (x:xs) = [x | x `notElem` history] ++ unique' (x:history)
> xs
> 
> Thanks
> 
> Neil
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 

-- 
View this message in context: 
http://www.nabble.com/function-unique-tf4058328.html#a11547781
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] better error expression in IO function

2007-07-11 Thread brad clawsie
i am working on improving a module for getting Yahoo Finance quote
data, hopefully getting it to a point that i can put it on hackage

in the quote retrieval function, there are a few places i would like
to call out errors. in a trivial case i could return 

IO (Maybe String) 

with Nothing signifying any error state, or Just expressing the data

but i would like to be able to express some of these error cases in a
more structured manner

i know the Either type can be used in such a case(?), but i've had some
problem locating a satisfactory example (if this is indeed
appropriate)

could one of the vets here provide a simplistic example expressing
error cases, preferrably in the IO Monad (in case there are any
gotchas there)?

thanks so much!
brad
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] CGI test

2007-07-11 Thread Hugh Perkins

Here you go:

module SimpleCgiServer
  where

import IO
import Char
import Network
import Control.Monad
import System.Process

listensocket = 2000

main = withSocketsDo $ do socket <- listenOn (PortNumber listensocket)
 mapM_ (\_ -> handleconnection socket) (iterate
(id) ())
 sClose socket

handleconnection socket = do (handle,hostname,portnumber) <- accept socket
putStrLn (show(hostname) ++ " " ++
show(portnumber))
hSetBuffering handle LineBuffering
line <- hGetLine handle
let filename = drop( length("GET /") ) line
htmltoreturn <- runprocess filename
hPutStr handle htmltoreturn

runprocess filename = do (stdin,stdout,stderr,processhandle) <-
runInteractiveCommand filename
waitForProcess processhandle
contents <- hGetContents stdout
return contents


You can change the portnumber by changing the value of the function
"listensocket".

This expects you to send it something like "GET /test.bat".  It will run
test.bat - or whatever filename you sent it - and send the results back down
the socket.

It's obviously not at all secure, eg we're not filtering things like ".."
from the input, so make sure to not publish the port to anywhere insecure
(like the Internet).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Constraints on data-types, mis-feature?

2007-07-11 Thread Jonathan Cast
On Tuesday 10 July 2007, Jim Apple wrote:
> On 7/9/07, Jonathan Cast <[EMAIL PROTECTED]> wrote:
> > GADTs don't change anything (at least, not the last time I checked).
>
> GHC (in HEAD, at least) eliminates this wart for any datatype declared
> with GADT syntax.
>
> http://www.haskell.org/ghc/dist/current/docs/users_guide/data-type-extensio
>ns.html#gadt-style
>
> "Any data type that can be declared in standard Haskell-98 syntax can
> also be declared using GADT-style syntax. The choice is largely
> stylistic, but GADT-style declarations differ in one important
> respect: they treat class constraints on the data constructors
> differently. Specifically, if the constructor is given a type-class
> context, that context is made available by pattern matching."

Cool!  Looks like it does work in HEAD (although it does /not/ in 6.6.1).

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] function unique

2007-07-11 Thread Neil Mitchell

Hi


unique = unique' []

unique' _ [] = []
unique' history (x:xs) = if x `elem` history
  then next
  else (x:next) where next = (uniq' (x:hist) xs)


You can express this more neatly:

unique' _ [] = []
unique' history (x:xs) = [x | x `notElem` history] ++ unique' (x:history) xs

Thanks

Neil
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type system madness

2007-07-11 Thread Steve Schafer
On Wed, 11 Jul 2007 20:10:00 +0100, you wrote:

>When I tell the editor to save UTF-8, it inserts some weird "BOM" 
>character at the start of the file - and thus, any attempt at 
>programatically processing that file instantly fails. :-(

Which means that your processor doesn't properly understand UTF-8. A BOM
character isn't required for UTF-8 (it really only makes sense with
UTF-16), but a UTF-8-aware processor should skip right over it if it's
there.

Steve Schafer
Fenestra Technologies Corp.
http://www.fenestra.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange results when trying to create large Bool arrays.

2007-07-11 Thread Stefan O'Rear
On Wed, Jul 11, 2007 at 08:16:50PM +0100, Andrew Coppin wrote:
> Bryan O'Sullivan wrote:
>> Richard Kelsall wrote:
>>
>>> I guess there must be a switch to make it produce a nice
>>> error message rather than overflowing without warning.
>>
>> Actually, there isn't.
>
> I for one sometimes wish there was...
>
> Of course, sometimes you purposely write code which you know is going to 
> overflow and wrap round in a specific way. But frequently you *don't* want 
> this behaviour - and I wish there were some pragma or something to make 
> this be checked. AFAIK, most CPU types give you an efficient way to testing 
> for such conditions...

Indeed.  I beleive that Int should be removed from the Prelude.  People
who need the algebraic properties of rings modulo 2^(2^n) can use the
sized integral types from Data.Int and Data.Word; people who want speed
and can satisfy the proof obligations can use Int and Word from the same
modules.  Everyone else can use Integer, which should be made shorter than
Int for obvious psychological reasons.

Stefan


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


Re: [Haskell-cafe] function unique

2007-07-11 Thread Antoine Latter

On 7/11/07, Brent Yorgey <[EMAIL PROTECTED]> wrote:

> take 5 (unique [1..])

I don't think this is possible.  Perhaps you misread the original problem
description?  The unique function is supposed to return a list of those
elements which occur exactly once in the input list, which is impossible to
determine for an infinite input list (the only way to prove that a given
element occurs only once in a list, in the absence of any other information,
is to examine every element of the list).  Of course, a function that
behaves like the unix utility "uniq" ( i.e. returning only one copy of every
list element) is possible to implement lazily in the manner you describe.


Why wouldn't this work?  (I haven't tested it, sorry)

unique = unique' []

unique' _ [] = []
unique' history (x:xs) = if x `elem` history
 then next
 else (x:next) where next = (uniq' (x:hist) xs)

Whether or not it's a good idea is a separate issue.

Antoine
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Very freaky

2007-07-11 Thread Jim Burton


Andrew Coppin wrote:
> 
> Jim Burton wrote:
>> Andrew Coppin wrote:
>>   
>>> On the one hand, it feels exciting to be around a programming language 
>>> where there are deep theoretical discoveries and new design territories 
>>> to be explored. (Compared to Haskell, the whole C / C++ / Java / 
>>> JavaScript / Delphi / VisualBasic / Perl / Python thing seems so
>>> boring.)
>>>
>>> On the other hand... WHAT THE HECK DOES ALL THAT TEXT *MEAN*?! >_<
>>>
>>>
>>> 
>> I agree, it's exciting to use Haskell because of its theoretical
>> underpinning and the sense of it as a lab for PL ideas.
> 
> The other downside is that you end up with a world where most of the 
> "tools" are in fact one-man research projects or small toys.
> 
> There are a few good, powerful, useful things out there. (GHC and Parsec 
> immediately spring to mind.) But there's also a vast number of really 
> tiny projects which don't seem to be terrifically well supported. Kind 
> of makes me sad; Haskell seems almost doomed to be a language with 
> fantastic potential, but little real-world traction.
> 
AFAIK Haskell wasn't designed for real-world traction in the first place,
but as a way of consolidating FP research efforts onto one platform, so in
that sense it's a resounding success rather than "doomed". It also seems to
have gained some traction, and we know that FP can be an eminently practical
real-world secret weapon, so the tools you're waiting for someone else to
write could well be on their way. At the same time, the only evidence for
this at the moment is a lot of blogs, O'Reilly investing in a book and
Eternal September on haskell-cafe. If you want a language with a bigger user
base or that is less confusing, there are plenty to choose from.

-- 
View this message in context: 
http://www.nabble.com/Very-freaky-tf4057907.html#a11547225
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type system madness

2007-07-11 Thread Alex Queiroz

Hallo,

On 7/11/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:


When I tell the editor to save UTF-8, it inserts some weird "BOM"
character at the start of the file - and thus, any attempt at
programatically processing that file instantly fails. :-(



Are you sure it's not UTF-16?

Cheers,
--
-alex
http://www.ventonegro.org/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] haskell -> db, on Solaris

2007-07-11 Thread Daniil Elovkov

2007/7/11, Bryan O'Sullivan <[EMAIL PROTECTED]>:

Daniil Elovkov wrote:

> Would you please tell me, what would be my choice if I wanted to
> interact with MySql and Oracle from a Haskell program on Solaris?

http://www.haskell.org/haskellwiki/Applications_and_libraries/Database_interfaces

If you want to talk to MySQL, you have a few choices.

HDBC has an ODBC interface that lets you use any ODBC provider, so
you'll be able to talk to both MySQL and Oracle with it.

HaskellDB can bridge to HDBC, I believe, so that will let you do
type-safe SQL.

There's also Takusen, which can talk to Oracle, but not MySQL.


Yes, thanks. But the emphasis was on Solaris. I don't quite understand
what is the common way to access databases on Solaris. Is it odbc? And
how Haskell libraries connect to that? I mean, Takusen is designed to
use odbc and nothing else (afaik), for example.

Maybe somebody has a successful exprerience of that?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Very freaky

2007-07-11 Thread Fritz Ruehr
Once during a talk I noticed I was getting strange looks and realized  
I was using the term "string" too freely with an audience of non- 
technical people. About half of them were in a beginning linguistics  
class and could at least handle "trees" later on (which terminology I  
had thought in advance to explain), but the other half were from  
humanities, social sciences, etc., with no special training in  
computing (or linguistics). I had to back-pedal quickly to find a  
good alternative to "string" (Sequence of characters? Piece of text?  
"Text" is pretty loaded for some humanities people and would have  
connotations I wouldn't want.) I'd never before realized how  
convenient (but obscure!) the term "string" was. Here these poor  
people were trying to figure out how some thin piece of rope was  
involved in programming languages ... .


  --  Fritz

On Wed 11 Jul 07, at 11:54 am, Andrew Coppin wrote:

I see this *a lot* with computers. People who know lots about  
computers forget that some people don't know that a "megabyte" is  
(considerably) bigger than a "kilobyte". Or that having a faster  
CPU doesn't make Windows load faster. The number of technical  
documents I've seen that make perfect sense to a knowledgable  
person, but would be utter gibberish to most normal folk...


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange results when trying to create large Bool arrays.

2007-07-11 Thread Andrew Coppin

Bryan O'Sullivan wrote:

Richard Kelsall wrote:


I guess there must be a switch to make it produce a nice
error message rather than overflowing without warning.


Actually, there isn't.


I for one sometimes wish there was...

Of course, sometimes you purposely write code which you know is going to 
overflow and wrap round in a specific way. But frequently you *don't* 
want this behaviour - and I wish there were some pragma or something to 
make this be checked. AFAIK, most CPU types give you an efficient way to 
testing for such conditions...


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange results when trying to create large Bool arrays.

2007-07-11 Thread Bryan O'Sullivan

Albert Y. C. Lai wrote:

I'm just being picky here: where the underlying machine's behaviour is 
2's complement binary, it (Int, +, *) is actually a tidy, well-behaved 
mathematical ring, isomorphic to Z / 2^n Z.


Yes, naturally it wasn't until a few moments after I had sent the 
message that I noticed my error.


http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type system madness

2007-07-11 Thread Andrew Coppin

Albert Y. C. Lai wrote:
Lest I am painted as unhelpful(*), http://www.vex.net/~trebla/u.html 
exemplifies what can be done and how to do it. In particular, you must 
always specify a content encoding in the HTML header, and you must 
always order your editor to write out UTF-8.


When I tell the editor to save UTF-8, it inserts some weird "BOM" 
character at the start of the file - and thus, any attempt at 
programatically processing that file instantly fails. :-(


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type system madness

2007-07-11 Thread Andrew Coppin

Bulat Ziganshin wrote:

Hello Andrew,

  

Hmm. Like the IO monad's RealWorld object, which isn't really there?



ST and IO monads are the same beast. in ST, s is free to allow to
create endless amount of independent threads while in IO it fixed to
one type and describes evolution of one thread, synchronized with real
world. look at http://haskell.org/haskellwiki/IO_inside for info about
IO monad trickery
  


OMG! stToIO exists...!

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Toy compression algorithms [was: A very edgy language]

2007-07-11 Thread Andrew Coppin

Bulat Ziganshin wrote:

Hello ajb,

Wednesday, July 11, 2007, 7:55:22 AM, you wrote:
  

Not really.  LZW is basically PPM with a static (and flat!) frequency
prediction model.  The contexts are build in a very similar way.



what you mean by "flat" and "static" applied to PPM? static PPM models
exist - they carry probabilities as separate table very like static
Huffman encoding. is "flat" the same as order-0?
  


I think he meant "flat" as in "pr(z) = 0 | 1"...

As for "static", I'm not so sure that's actually correct.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type system madness

2007-07-11 Thread Andrew Coppin

Paul Moore wrote:

On 10/07/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:

Interesting... I tried to put a pound sign on my web page, and it came
out garbled, so I had to replace it with "£"...


You may need to specify a "content encoding" in the HTML header. For
that, you need to know the encoding your HTML file is saved in.
Unicode works fine, but encodings can be a bit of a minefield...


Indeed.

I thought it was just saved as "ASCII"...

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy Lists and IO

2007-07-11 Thread Andrew Coppin

Stefan O'Rear wrote:

Unfortunately, ignoring purity is fraught with peril.  One notable
example recently is in HAppS, a Haskell web framework.  Alex Jacobson (a
haskeller of significant note, not some "clueless newbie") accidentally
wrote { length xs > 0 } instead of { not (null xs) } in some parsing
code.  Which would just be inefficient, normally, but it demanded the
whole thing, which as it happened was a lazy stream coming of a socket.
Bad data dependencies, bang, deadlock.
  


Ouch! That's gotta sting...

I wasn't aware that this function was so leathal. I use it constantly 
all the time...



Option 2. Ignore lists

It's possible to describe lists threaded with something else.

data ListT m a = m (ListT' m a)
data ListT' m a = NilT | ConsT a (ListT m a)

You get your safety back ... and lose the standard list functions, list
syntax, list comprehensions, list instances, strings-as-lists, et
cetera.
  


That's... interesting...

(I feel yet another "I'm going to have to sit down and think about that 
one" comming on.)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] embedding Haskell: problematic polymorphism

2007-07-11 Thread Stefan O'Rear
On Wed, Jul 11, 2007 at 05:45:40PM +, Claude Heiland-Allen wrote:
> Hi people,
>
> I'm embedding Haskell into a C program with a "stateful objects with 
> message passing" paradigm [0].  I want to make "boxes" with useful 
> functions, then connect them together within the C program.  I know how to 
> build a working version using Data.Dynamic, but that loses polymorphism 
> [1].
>
> Say I have 3 boxes:
>
> Box 1:  [1,2,5,3]:: [Float]
> Box 2:  reverse  :: [a] -> [a]
> Box 3:  putStrLn . show  :: (Show b) => b -> IO ()
>
> I wonder, is it possible to create these boxes separately at runtime (each 
> box being compiled/loaded separately with hsplugins), then connect them 
> together like {Box 1}=>{Box 2}=>{Box 3} (with a wrapping layer doing 
> appropriate type checking/error reporting), or does the whole thing need to 
> be compiled statically to generate specialized variants of the polymorphic 
> functions?  As hinted in #haskell :
>
>  ClaudiusMaximus: I don't think anything will allow you to 
> pass around polymorphic values. They're an illusion of the type-checker, in 
> a sense.

There is nothing intrinsically impossible with a Data.Dynamic like
interface for polytypic values.  Good luck writing toDyn and fromDyn
without compiler support, however.

Stefan


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


Re: [Haskell-cafe] Toy compression algorithms

2007-07-11 Thread Andrew Coppin

[EMAIL PROTECTED] wrote:

G'day all.

Andrew Coppin wrote:

  

Actually, LZW works surprisingly well for such a trivial little
algorithm... When you compare it to the complexity of an arithmetic
coder driven by a high-order adaptive PPM model (theoretically the best
general-purpose algorithm that exists), it's amazing that anything so
simple as LZW should work at all!
  


Not really.  LZW is basically PPM with a static (and flat!) frequency
prediction model.  The contexts are build in a very similar way.
  


Yes - but making it use a non-flat model opens a whole Pandora's Box of 
fiddly programming. ;-)


(It's not "hard" as such - just frustratingly fiddly to get correct...)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Very freaky

2007-07-11 Thread Andrew Coppin

Michael T. Richter wrote:

On Tue, 2007-10-07 at 20:59 +0100, Andrew Coppin wrote:
But it rambled on for, like, 3 pagefulls of completely opaque 
set-theoretic gibberish before I arrived at the (cryptically phrased) 
statements I presented above. Why it didn't just *say* that in the first 
place I have no idea...



Because the overwhelming majority of people who teach math know math 
well, but do not know teaching well.  Sadly it would be better for all 
but the highest levels of education to have that reversed.  My own 
long-standing, deep distaste for the "chicken scratchings" of the pure 
maths stems from incredibly smart teachers who had no idea how to 
communicate what they knew to those not already there.


At the risk of becoming tangental... When you are really *deeply* 
knowledgable about something, it can become seriously hard to even 
realise all the things you're constantly assuming your audience knows. 
It's so obvious *to you* that it never even crosses your mind that you 
might need to explain it. Heck, you don't even realise that what you're 
talking about relies on this concept, since it is so deeply embedded in 
your mind.


I see this *a lot* with computers. People who know lots about computers 
forget that some people don't know that a "megabyte" is (considerably) 
bigger than a "kilobyte". Or that having a faster CPU doesn't make 
Windows load faster. The number of technical documents I've seen that 
make perfect sense to a knowledgable person, but would be utter 
gibberish to most normal folk...


I've also come across no end of product websites where the authors are 
so keen to tell you how brilliant their product is and all the cool 
features it has that they completely forget to explain WHAT THE PRODUCT 
DOES! For example, FreeNX. I spent *hours* trying to figure out what 
that actually does...! (In the end, I had to ask somebody. Turns out it 
does nothing of any interest to me, but still...)


I like to think that I'm quite good at explaining technical things using 
non-technical (but not patronising) language. But I'm probably just 
kidding myself...


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange results when trying to create large Bool arrays.

2007-07-11 Thread Albert Y. C. Lai

Bryan O'Sullivan wrote:
Int is a bit of an odd fish that way; it's a 
window onto the underlying machine's behaviour, not a tidy, well-behaved 
mathematical ring.


I'm just being picky here: where the underlying machine's behaviour is 
2's complement binary, it (Int, +, *) is actually a tidy, well-behaved 
mathematical ring, isomorphic to Z / 2^n Z. Furthermore, if there were 
overflow errors, the result would not be a ring, but an error monad over 
a ring or a CPO lifting a ring. (Not to say that they are not tidy, 
well-behaved, mathematical.)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] In-place modification

2007-07-11 Thread Andrew Coppin

Donald Bruce Stewart wrote:

allbery:
  

Doesn't nhc98 target embedded devices?



It's been used on embedded arm devices the size of a credit card. 
  


1. Where on earth do you find such a device?

2. How do you run code on one?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] function unique

2007-07-11 Thread Brent Yorgey

2) The list might be infinite, and your function should work if you make
only want to use the first part of it, so the following should return
[1,2,3,4,5] in a finite amount of time:

take 5 (unique [1..])



I don't think this is possible.  Perhaps you misread the original problem
description?  The unique function is supposed to return a list of those
elements which occur exactly once in the input list, which is impossible to
determine for an infinite input list (the only way to prove that a given
element occurs only once in a list, in the absence of any other information,
is to examine every element of the list).  Of course, a function that
behaves like the unix utility "uniq" (i.e. returning only one copy of every
list element) is possible to implement lazily in the manner you describe.

@Alexteslin: It probably would still be a useful exercise for you, though,
to get rid of the redundancy Dan describes in determining whether to keep
each element.  A function to count the occurrences of a given element
(although useful in its own right) is overkill here, since you only care
whether the element occurs once, or more than once.  You could implement a
function isUnique :: Int -> [Int] -> Bool which tells you whether the given
element occurs only once (True) or more than once (False), and doesn't
evaluate more of the list than necessary to determine this.  I doubt you'd
have much trouble implementing this function.

-Brent
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Very freaky

2007-07-11 Thread Andrew Coppin

Tony Morris wrote:

I'd like throw in another vote for TAPL.  I've been reading it lately
and it
honestly makes type theory feel fairly simple and natural.  I think
Pierce's
writing is very clear, but occasionally the exercises make the problem
sound
harder than it is and it gets a little confusing.  A friend of mine has the
same problem with his category theory book.



Same here!
I found his Category Theory book quite difficult and I will have to
revisit it. I have only just started TaPL, but I am enjoying it thoroughly.
  


I once sat down and tried to read about Category Theory. I got almost 
nowhere though; I cannot for the life of my figure out how the 
definition of "category" is actually different from the definition of 
"set". Or how a "functor" is any different than a "function". Or... 
actually, none of it made sense.


It didn't sound terribly interesting anyway. I'll stick to group theory...

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] CPS versus Pattern Matching performance

2007-07-11 Thread Stefan O'Rear
On Wed, Jul 11, 2007 at 11:14:20AM +0100, Tony Finch wrote:
> registers or on the stack) and a case analysis branch, but a normal
> function return (predictable by the CPU) is replaced by a less-predictable
> indirect jump. Does anyone have references to a paper that discusses an

GHC does not use calls and returns.  To quote a recent paper on this
subject:

7.1   Using call/return instructions

As we mentioned in Section 2, GHC generates code that manages the
Haskell stack entirely separately from the system-supported C stack. As
a result, a case expression must explicitly push a return address, or
continuation, onto the Haskell stack; and the "return" takes the form of
an indirect jump to this address. There is a lost op- portunity here,
because every processor has built-in CALL and RET instructions that help
the branch-prediction hardware make good predictions: a RET instruction
conveys much more information than an arbitrary indirect jump.

Nevertheless, for several tiresome reasons, GHC cannot readily make use
of these instructions:

* The Haskell stack is allocated in the heap. GHC generates code
  to check for stack overflow, and relocates the stack if necessary.  In
  this way GHC can support zillions of little stacks (one per thread),
  each of which may be only a few hundred bytes long.  However,
  operating systems typically take signals on the user stack, and do no
  limit checking. It is often possible to arrange that signals are
  executed on a separate stack, however.

* The code for a case continuation is normally preceded by an
  info table that describes its stack frame layout. This arrangement
  is convenient because the stack frame looks just like a heap closure,
  which we described in Section 2. The garbage collector can now use the
  info table to distinguish the point- ers from non-pointers in the
  stack frame closure. This changes if the scrutinee is evaluated using
  a CALL instruction: when the called procedure is done, it RETurns to
  the instruction right after the call. This means that the info table
  can no longer be placed before a continuation. Thus the possible
  benefits of a CALL/RET scheme must outweigh the performance penalty of
  abandoning the current (efficient) info table layout.

Stefan


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


Re: [Haskell-cafe] Very freaky

2007-07-11 Thread Andrew Coppin

Jim Burton wrote:

Andrew Coppin wrote:
  
On the one hand, it feels exciting to be around a programming language 
where there are deep theoretical discoveries and new design territories 
to be explored. (Compared to Haskell, the whole C / C++ / Java / 
JavaScript / Delphi / VisualBasic / Perl / Python thing seems so boring.)


On the other hand... WHAT THE HECK DOES ALL THAT TEXT *MEAN*?! >_<




I agree, it's exciting to use Haskell because of its theoretical
underpinning and the sense of it as a lab for PL ideas.


The other downside is that you end up with a world where most of the 
"tools" are in fact one-man research projects or small toys.


There are a few good, powerful, useful things out there. (GHC and Parsec 
immediately spring to mind.) But there's also a vast number of really 
tiny projects which don't seem to be terrifically well supported. Kind 
of makes me sad; Haskell seems almost doomed to be a language with 
fantastic potential, but little real-world traction.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange results when trying to create large Bool arrays.

2007-07-11 Thread Stefan O'Rear
On Wed, Jul 11, 2007 at 10:55:28AM -0700, Bryan O'Sullivan wrote:
> Richard Kelsall wrote:
>> It seems to randomly claim to have successfully created huge sizes
>> of array.
>
> This may be outside of Haskell's control, as you're not actually touching 
> the memory you allocate.  I wouldn't be surprised if the underlying page 
> allocation is succeeding by virtue of the OS being willing to overcommit 
> resources that may not actually be used.  (This would be normal behaviour 
> on Linux, for example.)  In such a case, the Haskell runtime may not 
> receive an error until you try to actually touch the data.

Not a sufficient explanation - you can only allocate addrssable memory,
even on Linux I can't allocate more than 3GB of storage.

> You can get GHC to fix an upper limit on the heap size it will try to use, 
> by passing "+RTS -M768m -RTS" to your compiled program on the command line. 
>  That should cause your program to crash more reliably.

That still won't work because GHC trims the array size to an Int
interally, and trims the byte count to an Int again before passing it to
the OS.

[EMAIL PROTECTED]:~$ ghci
Loading package base ... linking ... done.
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |GHC Interactive, version 6.7.20070612, for Haskell 98.
/ /_\\/ __  / /___| |http://www.haskell.org/ghc/
\/\/ /_/\/|_|Type :? for help.

Prelude> :m + Data.Array.Unboxed 
Prelude Data.Array.Unboxed> array (0,maxBound :: Int) [(-2, 42::Int)] :: UArray 
Int Int
array Segmentation fault
[EMAIL PROTECTED]:~$ 

http://hackage.haskell.org/trac/ghc/ticket/229

(yes, that's a 3 digit bug number)

Stefan


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


Re: [Haskell-cafe] In-place modification

2007-07-11 Thread Brandon S. Allbery KF8NH


On Jul 11, 2007, at 13:37 , Andrew Coppin wrote:

(Windoze-only, you say? Perhaps I misunderstood - I thought this is  
what Mono is all about...)


As someone else pointed out earlier, the real power is the libraries,  
which provide a complete and powerful GUI environment.  Mono provides  
the VM and C# but duplicating the libraries is a much bigger and  
harder job.


--
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 universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Very freaky

2007-07-11 Thread Andrew Coppin

Tim Chevalier wrote:

On 7/10/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:

On the one hand, it feels exciting to be around a programming language
where there are deep theoretical discoveries and new design territories
to be explored. (Compared to Haskell, the whole C / C++ / Java /
JavaScript / Delphi / VisualBasic / Perl / Python thing seems so 
boring.)


On the other hand... WHAT THE HECK DOES ALL THAT TEXT *MEAN*?! >_<



If you're interested in a concept, why not read about it (it's easy to
find a quick definition for most terms on Google, and more details in
research papers), then ask *specific* questions on the list? Posting
to the list about how you don't understand something, without any
suggestion as to how anyone else could help, doesn't accomplish a lot.


I wasn't being entirely serious. ;-)

We've got a whole other thread going about trying to understand the 
difference between existential and universal quantification. Suffice it 
to say I'm still confused. I guess this is going to be one of those 
concepts I'll just never understand.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


  1   2   >