Thu, haskell/ghc is definitely not for fast execution
really, i was not seeking time performance. i try to have a nice to
read kind of prototype.
but the fact that the program doesn't work with quite small test (but
already too big for it) is a problem.
Best regards,
Bulat
G'day all.
Quoting Mathew Mills <[EMAIL PROTECTED]>:
> How about the closed form ;)
>
> > -- fib x returns the x'th number in the fib sequence
>
> > fib :: Integer -> Integer
>
> > fib x = let phi = ( 1 + sqrt 5 ) / 2
>
> > in truncate( ( 1 / sqrt 5 ) * ( phi ^ x - phi' ^ x ) )
>
>
> Seem
Hello minh,
Friday, June 16, 2006, 10:09:47 AM, you wrote:
> it's not ok (i always think to the array exemple) : it works well for
Thu, haskell/ghc is definitely not for fast execution
--
Best regards,
Bulatmailto:[EMAIL PROTECTED]
___
[...]
import Data.AltBinary
main = putWord32 stdout (1::Int)
Bulatmailto:[EMAIL PROTECTED]
well, you're right, i've a bit to overemphased the learning difficulty..
but, last time i tried to use your lib, i missed some other libraries
(win32 for one ? .. i dont reme
noteed:
>
> i want to process 4k pictures (and not just one pixel fater one)...
> for example. if there is a better solution than array, i'm eager to
> know it!
Try Data.ByteString. 4G can be feasible :)
-- Don
___
Haskell-Cafe mailing list
Haskell-C
Hello minh,
Friday, June 16, 2006, 12:14:00 AM, you wrote:
> yes i know about that, but i was talking about randomIO which breaks that
> view;
> and i find that quite weird for a 'clean' language.
there is also haskell-based language named Clean, look at it too :)
> * another thing i remember
Hello Brian,
Friday, June 16, 2006, 2:18:24 AM, you wrote:
>> but i consider to move back to c/c++.
> There is also OCaml and SML, both of which have freely available compilers
> to generate fast native code (SML has MLton - a whole program optimizing
> compiler), and which use side effects inst
Hello Brian,
Friday, June 16, 2006, 12:13:27 AM, you wrote:
> Seriously though, at the moment my aim is to develop an integrated
> programming environment for a language similar to Haskell, either Haskell
> itself or a non-lazy version of it, also with some syntactic modifications
> to make it ea
thanks, brian, udo and the others for your answers
[...]
I'm led to believe that you just haven't got the hang of the things that
just aren't there in C, such as Monads and higher order functions. So
you cannot yet see what you would miss in C. (And I guess, you're not
feeling at home in C++ e
Mathew Mills <[EMAIL PROTECTED]> writes:
> -- fib x returns the x'th number in the fib sequence
> fib :: Integer -> Integer
> fib x = let phi = ( 1 + sqrt 5 ) / 2
> phi' = ( 1 - sqrt 5 ) / 2
> in truncate( ( 1 / sqrt 5 ) * ( phi ^ x - phi' ^ x ) )
>
> -- Seems pretty quick to m
How about the closed form ;)
> -- fib x returns the x'th number in the fib sequence
> fib :: Integer -> Integer
> fib x = let phi = ( 1 + sqrt 5 ) / 2
> in truncate( ( 1 / sqrt 5 ) * ( phi ^ x - phi' ^ x ) )
Seems pretty quick to me, even with sqrt and arbitrarily large numbers.
On
G'day all.
Quoting Vladimir Portnykh <[EMAIL PROTECTED]>:
> I wrote my own Fibonacci numbers generator:
>
> fib :: Int -> [Int]
> fib 0 = [0,0]
> fib 1 = [1,0]
> fib n = [sum prevFib, head prevFib] where a = fib (n - 1)
>
> To get the k-th number you do the following:
>
> result = head (fib k)
[
On Thursday, June 15, 2006 8:07 PM Clifford Beshers wrote:
On another note, who picked the word `Just' for this type
and how did we end up with Some x | None in
O'Caml and Just x | Nothing in Haskell?
I've always thought this is one of the most charming things about Haskell,
along with the us
minh thu wrote:
> but i consider to move back to c/c++.
I'm led to believe that you just haven't got the hang of the things that
just aren't there in C, such as Monads and higher order functions. So
you cannot yet see what you would miss in C. (And I guess, you're not
feeling at home in C++ eith
minh thu wrote:
hi all folks,
i'm diving into haskell for more than one year now.
the reason for that is just that i like haskell.
(i'm a computer science student)
but i consider to move back to c/c++.
There is also OCaml and SML, both of which have freely available compilers
to generate fas
I did the transition the other way, and even now the real-world keeps me using
more C-like languages (Java, Python).
Unlike the transition from imperative languages to Haskell, I don't think
there's much you have to unlearn or rethink. But I suspect you may feel a
degree of frustration at how inc
Vladimir,
I think you forgot to put Haskell-cafe as a recipient of this email,
so first I'll repost what you wrote.
On 6/15/06, Vladimir Portnykh <[EMAIL PROTECTED]> wrote:
many thanks. i have the follwoing code:
module MyType (DataContainer(..)) where
import Maybe
data DataContainer =
MyT
hi,
yes i know about that, but i was talking about randomIO which breaks that view;
and i find that quite weird for a 'clean' language.
* another thing i remember now :
binary io. there are some libraries but it's not really standard. and
it's weird to learn all (well, or just one) that libraries
minh thu wrote:
hi
in fact, i think that for a while ...
moreover, i thought to translate to some kind of readable c (because
there s so much c libs all around).
i think it's even possible to retain laziness where it's ok ( for data
structure essentially).
Hi Thu -
Someone pointed out (offlist
On Thu, 15 Jun 2006, Vladimir Portnykh wrote:
Fibonacci numbers implementations in Haskell one of the classical examples.
An example I found is the following:
fibs :: [Int]
fibs = 0 : 1 : [ a + b | (a, b) <- zip fibs (tail fibs)]
To get the k-th number you do the following:
Result = fibs !!
On Thu, 15 Jun 2006, minh thu wrote:
* randomIO
side-effect is nicely resolved with monad. and you have to thread your state.
if you're writing your monad or use a transformer, things are quite
explicitly (even if it's implicit in the do notation) threaded.
You know that random generators are
Duncan Coutts wrote:
On Thu, 2006-06-15 at 13:11 +0100, Duncan Coutts wrote:
then you can construct your records using:
foo = default { weight = 3.2 }
Oops, as David House pointed out to me that should of course be
foo = default { weight = Just 3.2 }
I think the c
hi
in fact, i think that for a while ...
moreover, i thought to translate to some kind of readable c (because
there s so much c libs all around).
i think it's even possible to retain laziness where it's ok ( for data
structure essentially).
is-it possible to know what you're doing at metamilk ?
On 6/15/06, Joel Reymont <[EMAIL PROTECTED]> wrote:
On Jun 15, 2006, at 6:18 PM, Sebastian Sylvan wrote:
> This may not be very helpful, but I would say that an Image is neither
> a list nor an array - it's a function! :-)
How exactly do you manipulate the bits and bytes of a function?
Well
right :)
i had to say a discrete image ... or a raster, or an *array* of pixels !
sylvan, it must be nice to talk with you (an funny) about haskell and cg :)
mt
2006/6/15, Sebastian Sylvan <[EMAIL PROTECTED]>:
On 6/15/06, minh thu <[EMAIL PROTECTED]> wrote:
> hi, thanks for your answer.
>
> the
On Jun 15, 2006, at 6:18 PM, Sebastian Sylvan wrote:
This may not be very helpful, but I would say that an Image is neither
a list nor an array - it's a function! :-)
How exactly do you manipulate the bits and bytes of a function?
--
http://wagerlabs.com/
___
On 6/15/06, minh thu <[EMAIL PROTECTED]> wrote:
hi, thanks for your answer.
the kind of thing i want to do : computer graphics programming.
so array is better than list (no ?) to represent images ...
This may not be very helpful, but I would say that an Image is neither
a list nor an array -
hi, thanks for your answer.
the kind of thing i want to do : computer graphics programming.
so array is better than list (no ?) to represent images ...
bye
vo minh thu
(hey, my last name is VO, and my first name is Thu, not Minh :)
2006/6/15, Neil Mitchell <[EMAIL PROTECTED]>:
Hi Minh,
When
Here's some code I wrote a while back for computing the nth Fibonacci
number. It has O(log n) time complexity rather than O(n). It isn't
the most elegant example, but it should be one of the fastest
approaches.
import Data.Bits (shiftR, xor, (.|.), (.&.))
import Data.Word (Word32)
fibo :: W
Hi Minh,
When I write Haskell, its because I want to write the code quickly,
not because I want it to run quickly. GHC is a wonderful compiler and
makes things go fast, but Hugs is faster at compiling, so I always use
Hugs (WinHugs in fact). If your focus is on things going fast, then
with Haskel
Fibonacci numbers implementations in Haskell one of the classical examples.
An example I found is the following:
fibs :: [Int]
fibs = 0 : 1 : [ a + b | (a, b) <- zip fibs (tail fibs)]
To get the k-th number you do the following:
Result = fibs !! k
It is elegant but creates a list of all Fibona
hi all folks,
i'm diving into haskell for more than one year now.
the reason for that is just that i like haskell.
(i'm a computer science student)
but i consider to move back to c/c++.
here are my thoughts.
i've no specific question but i'd like to have your opinion.
here we go:
haskell is re
Hello,
Has anyone figured out a way to receive multicasts in a Haskell
program? It doesn't appear that Network.Socket.setSocketOption
provides enough information to join a multicast address.
Any information would be appreciated.
--
Rich
AIM : rnezzy
ICQ : 174908475
Thomas,
> rotate' :: [[a]] -> [[a]]
> rotate' [] = []
> rotate' xs = (map (head) xs ):(rotate' $ filter (not . null) $
map (tail) xs)
which seems to work just fine. While this solution is adequate (it
seems to work for infinite structures as well, which is good), I
originally set out to
On Thu, 15 Jun 2006, Thomas Sutton wrote:
Today I've been looking at rotating matrices, i.e: taking a column-wise
matrix and making it row-wise and, in the process, swapping the dimensions
(thus a 3*2 matrix becomes a 2*3 matrix).
You mean 'matrix transposition' which is available as Data.Li
Dear list,
I'm currently engaged in an attempt to wrap my head around type
arithmetic. To make sure that I've understood, I plan to write a few
operations on matrices a la Oleg's Number Parameterised Types. Before
I get down to it, I've been making sure I know how to implement the
operati
On Thu, 2006-06-15 at 13:11 +0100, Duncan Coutts wrote:
> then you can construct your records using:
>
> foo = default { weight = 3.2 }
Oops, as David House pointed out to me that should of course be
foo = default { weight = Just 3.2 }
Duncan
___
H
On Thu, 2006-06-15 at 12:43 +0100, Vladimir Portnykh wrote:
> Suppose there is a data definition in Haskell:
> data MyType = MyType { date :: Double,
> weight :: Double,
> height:: Double
> } deriving (Eq, Ord, Show)
>
> Is it possible
On 6/15/06, Vladimir Portnykh <[EMAIL PROTECTED]> wrote:
Suppose there is a data definition in Haskell:
data MyType = MyType { date :: Double,
weight :: Double,
height:: Double
} deriving (Eq, Ord, Show)
Is it possible to che
Suppose there is a data definition in Haskell:
data MyType = MyType { date :: Double,
weight :: Double,
height:: Double
} deriving (Eq, Ord, Show)
Is it possible to check if the field height, for example, is filled
in(defined
40 matches
Mail list logo