> last $ takeWhile (\x -> 1 + x /= 1) (iterate (/2) 1)
2.220446049250313e-16
This works because of the way IEEE floating-point numbers are
represented, so it's good for the majority of machines, but it is
technically a hack, in that it depends on a representation of
floating-point numbers in som
Paul Johnson wrote:
I've done some stuff with maybe 50k rows at a time. A few bits and pieces:
1: I've used HSQL
(http://sourceforge.net/project/showfiles.php?group_id=65248) to talk to
ODBC databases. Works fine, but possibly a bit slowly. I'm not sure
where the delay is: it might just be
jeff p wrote:
Hello,
So before I embark on day 1 of the project, I thought I should check and
see if anyone on this list has used Haskell to munge a ten-million-row
database table, and if there are any particular gotchas I should watch
out for.
One immediate thing to be careful about is how y
Bertram Felgenhauer <[EMAIL PROTECTED]> writes:
(snip)
> I'll venture a guess: The code originally read
>
> | bestSplit width string =
> | let wraps = options string
> | in last (head wraps : takeWhile ((<= width) . length . fst) wraps)
(snip)
Version control agrees with you. Next time I'
"What a beautiful world this could be..." ;-)) (*)
Cheers,
Ben
(*) Donald Fagen (forgot the name of the song)
I think I.G.Y. (International Geophysical Year) is it:
On that train all graphite and glitter
Undersea by rail
Ninety minutes from New York to Paris
(More leisure time for artists ever
Forwarded Message
From: Victor Bandur <[EMAIL PROTECTED]>
Reply-To: [EMAIL PROTECTED]
To: Brandon Moore <[EMAIL PROTECTED]>
Subject: Re: [Haskell-cafe] smallest double eps
Date: Sat, 30 Sep 2006 20:17:05 -0400
Hi all,
I'm new to this mailing list, so my response may be a little
Bryan Burgers wrote:
>>> Hang on, hang on, now I'm getting confused.
>>> First you asked for the smallest (positive) x such that
>>>1+x /= x
>>> which is around x=4.5e15.
>>
>> 1 + 0 /= 0
>>
>> 0 is smaller than 4.5e15
>>
>> So I don't understand this at all...
>
> But then 0 isn't positive.
On Sat, Sep 30, 2006 at 08:51:40PM +0200, Udo Stenzel wrote:
> To: Matthias Fischmann <[EMAIL PROTECTED]>
> Cc: haskell-cafe@haskell.org
> From: Udo Stenzel <[EMAIL PROTECTED]>
> Date: Sat, 30 Sep 2006 20:51:40 +0200
> Subject: Re: [Haskell-cafe] cutting long strings into lines
>
> Matthias Fisch
Matthias Fischmann wrote:
> although this wasn't the original problem, i like it, too :). but now
> i am stuck in finding an optimal implementation for lines.
Isn't the obvious one good enough?
lines [] = []
lines s = go s
where
go [] = [[]]
go ('\n':s) = [] : lines s
go (c:s) = le
On Sat, Sep 30, 2006 at 08:56:24PM +0400, Bulat Ziganshin wrote:
> splitByLen len_f [] = []
> splitByLen len_f xs = y : splitByLen len_f ys
>where (y,ys) = splitAt (len_f xs) xs
...
> so, "splitByLen len_f" should give you that you need, you need only to
> add checks for som
Matthias Fischmann wrote:
>
> On Sat, Sep 30, 2006 at 11:54:19AM -0400, Mark T.B. Carroll wrote:
> > module WordWrap (wrap) where
> > import Data.Maybe
> >
> > options :: String -> [(String, String)]
> >
> > options [] = [("", "")]
> >
> > options (x:xs) =
> > let rest = map (\(ys, zs) -> (
doh, i was just missing "where" after module... in my .chs file, and
some other syntax errors...
On 9/30/06, Anatoly Yakovenko <[EMAIL PROTECTED]> wrote:
I am trying to figure out how to use c2hs, so I wrote a wrapper for
asin from math.h:
$ cat ASin.chs
module MySin (mysin)
import C2HS
#inclu
>>> Hang on, hang on, now I'm getting confused.
>>> First you asked for the smallest (positive) x such that
>>>1+x /= x
>>> which is around x=4.5e15.
>>
>> 1 + 0 /= 0
>>
>> 0 is smaller than 4.5e15
>>
>> So I don't understand this at all...
>
> But then 0 isn't positive.
Why not?
In any case
I am trying to figure out how to use c2hs, so I wrote a wrapper for
asin from math.h:
$ cat ASin.chs
module MySin (mysin)
import C2HS
#include "math.h"
asin::Double -> Double
asin xx =
{#call fun asin#} xx
and this is my main:
$ cat Main.hs
module Main where
import ASin
main = do
putStrL
On Sat, Sep 30, 2006 at 08:56:24PM +0400, Bulat Ziganshin wrote:
> i think that your algorithm is too complex. standard algorithm, imho,
> is to find last space before 80 (or 75) chars margin, split here and
> then repeat this procedure again. so, one line split may look like
>
> splitAt . last .
On Sat, Sep 30, 2006 at 04:36:02PM +0100, Neil Mitchell wrote:
> (if you can't be bothered to do that, the answer is "lines" ;)
although this wasn't the original problem, i like it, too :). but now
i am stuck in finding an optimal implementation for lines. the
following implementation is slight
Hello Andrea,
Saturday, September 30, 2006, 7:02:34 PM, you wrote:
> -- gets the indexes of the spaces within a string
> indx = findIndices (\x -> if x == ' ' then True else False)
indx = findIndices (==' ')
> -- takes the first index of a group of indexes
> takeFirst = map (\(x:xs) -> x)
take
On Sat, Sep 30, 2006 at 11:54:19AM -0400, Mark T.B. Carroll wrote:
> module WordWrap (wrap) where
> import Data.Maybe
>
> options :: String -> [(String, String)]
>
> options [] = [("", "")]
>
> options (x:xs) =
> let rest = map (\(ys, zs) -> (x:ys, zs)) (options xs)
> in if x == ' ' th
Thomas Davie wrote:
On 30 Sep 2006, at 17:19, Brian Hulley wrote:
Lennart Augustsson wrote:
Hang on, hang on, now I'm getting confused.
First you asked for the smallest (positive) x such that
1+x /= x
which is around x=4.5e15.
1 + 0 /= 0
0 is smaller than 4.5e15
So I don't understand th
I've done some stuff with maybe 50k rows at a time. A few bits and pieces:
1: I've used HSQL
(http://sourceforge.net/project/showfiles.php?group_id=65248) to talk to
ODBC databases. Works fine, but possibly a bit slowly. I'm not sure
where the delay is: it might just be the network I was ru
On 30 Sep 2006, at 17:19, Brian Hulley wrote:
Lennart Augustsson wrote:
Hang on, hang on, now I'm getting confused.
First you asked for the smallest (positive) x such that
1+x /= x
which is around x=4.5e15.
1 + 0 /= 0
0 is smaller than 4.5e15
So I don't understand this at all...
But t
Lennart Augustsson wrote:
Hang on, hang on, now I'm getting confused.
First you asked for the smallest (positive) x such that
1+x /= x
which is around x=4.5e15.
1 + 0 /= 0
0 is smaller than 4.5e15
So I don't understand this at all...
Regards, Brian.
--
Logic empowers us and Love gives us
I've been doing it as the enclosed. I wrote it a while ago, though, and
haven't really looked too hard at it since.
-- Mark
module WordWrap (wrap) where
import Data.Maybe
options :: String -> [(String, String)]
options [] = [("", "")]
options (x:xs) =
let rest = map (\(ys, zs) -> (x:ys, zs)
Hi,
You want a function that converts a string into a list of strings,
i.e. with the type signature:
String -> [String]
Go to hoogle (http://haskell.org/hoogle) and search for that:
http://haskell.org/hoogle/?q=String->[String]
(if you can't be bothered to do that, the answer is "lines" ;)
T
On 30/09/2006, at 6:15 AM, Nicolas Frisby wrote:
Software engineering is as of yet misnamed. A professional engineer's
design work should never include figuring out why the first attempt
exploded/collapsed/failed--professionals in mature engineering fields
only debug catastrophes.
That is only
Hang on, hang on, now I'm getting confused.
First you asked for the smallest (positive) x such that
1+x /= x
which is around x=4.5e15.
Then Joachim wondered if you wanted
1+x /= 1
which is around x=2.2e-16.
But not you claim to be looking for the smallest positive number that
a Double ca
Hello!
I've been trying for quite some time to find an elegant solution to
cut long strings into lines, but the only solution I was able to come
up is the following piece of ugly code.
Is there a library function for that? What kind of approach would you
suggest?
Thanks for your kind attention.
On 9/30/06, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote:
data Eq a b where Refl :: Eq a a
coerce :: Eq a b -> a -> b
coerce ~Refl x = x
But this works well with Leibniz-style equality (
http://homepage.mac.com/pasalic/p2/papers/thesis.pdf ), because the
Equality proof/term is actually us
Hi
[EMAIL PROTECTED] wrote:
To summarize, the main problem is to get a lazy/online algorithm (the
problem here falls into the "more haste, less speed" category) while
staying more type safe.
@Conor: how does this issue look like in Epigram?
Thanks for asking!
In the current Epigram prototy
On Sat, Sep 30, 2006 at 04:19:50AM -0400, Lennart Augustsson wrote:
> Hang on, hang on, now I'm getting confused.
>
> First you asked for the smallest (positive) x such that
>1+x /= x
> which is around x=4.5e15.
> Then Joachim wondered if you wanted
>1+x /= 1
> which is around x=2.2e-16.
> But that makes it refutable! For the above, either
>
> coerce _|_ x === x
>
> or the notation is being abused.
Making a pattern irrefutable does not mean that the function in question
will become lazy:
fromJust (~Just x) = x
fromJust _|_ === _|_
The point with coerce is that it looks v
Here is a formulation of what exactly I require from irrefutable pattern
matches for GADTs.
The problem arouse from the "Optimization problem" thread. In short,
here is a GADT-using, type safe version of Bertram's solution (without
balancing)
> -- a binary search tree with witness about its
>> {-# OPTIONS -fglasgow-exts #-}
>>
>> module Main where
>>
>> import Data.IORef
>>
>> data T a where
>> Li:: Int -> T Int
>> Lb:: Bool -> T Bool
>> La:: a -> T a
>>
>> writeInt:: T a -> IORef a -> IO ()
>> writeInt v ref = case v of
>> ~(Li x) -> writeIORef ref (1::Int)
>>
>
Tamas K Papp writes:
Henning Thielemann wrote:
Actually, laziness allows me to formulate algorithms that look more like
the specification of the problem than the solution. E.g., I can formulate
the solution of a differential equation in terms of a power series or time
series in that way. Howe
It seems that irrefutable pattern match with existentials is safe. The
fact that irrefutable pattern match with GADT is unsafe has been
demonstrated back in September 2004.
Let us consider the following regular existential data type
> data TFoo where
>Foo :: Show a => a -> TFoo
>Bar :: I
Hang on, hang on, now I'm getting confused.
First you asked for the smallest (positive) x such that
1+x /= x
which is around x=4.5e15.
Then Joachim wondered if you wanted
1+x /= 1
which is around x=2.2e-16.
But not you claim to be looking for the smallest positive number that
a Double can
I previously wrote:
> The typechecker commits to the instance
> and adds to the current constraints
> TypeCast x Int, Ord Bool, Eq Bool
> The latter two are obviously satisfied and so discharged. The former
> leads to the substitution {x->Int}.
I should have been more precise and said:
I've used Mathematica a lot (and, unfortunately, still using it), and written a program, which uses symbolic computations a lot to deal with simplification of multivariate polynomial systems of inequalities. Now I'm trying to get rid of that Mathematica code and rewrite the program in Haskell becau
38 matches
Mail list logo