On Wed, Mar 09, 2011 at 05:50:12PM +0100, Gábor Lehel wrote:
> On Wed, Mar 9, 2011 at 5:26 PM, Remi Turk wrote:
> > Count on it having at least an order of magnitude more overhead.
> > I did some simple test of calling the following three trivial
> > functions (with co
On Tue, Mar 08, 2011 at 01:01:58PM +0100, Gábor Lehel wrote:
> On Sun, Mar 6, 2011 at 2:38 PM, Remi Turk wrote:
> > Where?
> > Hackage: http://hackage.haskell.org/package/cinvoke
> >
> > Cheers, Remi
> >
> > [1] http://www.nongnu.org/cinvoke/
>
> Is
On Tue, Mar 08, 2011 at 01:15:26AM +, Felipe Almeida Lessa wrote:
> On Mon, Mar 7, 2011 at 6:32 PM, Remi Turk wrote:
> > - If you need to pass C structs (by value), you'll have to use
> > libffi: cinvoke doesn't support them at all.
>
> What about CInvStruct
On Mon, Mar 07, 2011 at 10:31:25PM +0100, Daniel Fischer wrote:
> On Monday 07 March 2011 22:14:38, Remi Turk wrote:
> > cinvoke (the C library) is obviously not installed on the testing
> > machine. Does that really mean no library with uncommon C dependencies
> > gets doc
On Mon, Mar 07, 2011 at 10:00:47PM +0100, Daniel Fischer wrote:
> On Monday 07 March 2011 21:42:16, Gábor Lehel wrote:
> >
> > It's reporting a build failure.
> >
>
> Missing C library.
cinvoke (the C library) is obviously not installed on the testing machine.
Does that really mean no library wi
On Mon, Mar 07, 2011 at 09:41:27AM +, Max Bolingbroke wrote:
> Hi Remi,
>
> On 6 March 2011 13:38, Remi Turk wrote:
> > I am happy to finally announce cinvoke 0.1, a binding to the
> > C library cinvoke[1], allowing functions to be loaded and called
> > whose na
I am happy to finally announce cinvoke 0.1, a binding to the
C library cinvoke[1], allowing functions to be loaded and called
whose names and types are not known before run-time.
Why?
Sometimes you can't use the Haskell foreign function interface
because you parse the type of the function from so
I am happy to announce libffi 0.1, binding to the C library
libffi, allowing C functions to be called whose types are not
known before run-time.
Why?
Sometimes you can't use the haskell foreign function interface
because you parse the type of the function from somewhere else,
i.e. you're writing
On Tue, Mar 11, 2008 at 01:43:36AM -0400, Brandon S. Allbery KF8NH wrote:
> On Mar 11, 2008, at 0:20 , Chaddaï Fouché wrote:
>> 2008/3/11, David Menendez <[EMAIL PROTECTED]>:
>>> I think Adrian is just arguing that a == b should imply f a == f b,
>>> for all definable f, in which case it doesn't *
Hi everyone,
HSWM was my attempt at a Haskell Window Manager, mostly written
during the first half of 2006 as a personal research project, and
out of frustration with some not to be named other window
managers. Although I have been running it myself for almost two
years, I never got around to poli
Probably unrelated, but this thread is what triggered it for me.
There is a minor bug in showing impredicative types without
-fglasgow-exts: *hope I got that right*
Prelude> let x = [] :: [forall a. a]
:1:23:
Warning: Accepting non-standard infix type constructor `.'
Use -fglasgo
On Fri, Dec 16, 2005 at 07:55:50AM -0800, Scherrer, Chad wrote:
> From: S Koray Can [mailto:[EMAIL PROTECTED]
> Why not do this: name none of those modules Main.hs, and have an empty
> module Main.hs with only "import MainDeJour" and "main =
> MainDeJour.main" so you can just edit just that file.
On Fri, Sep 16, 2005 at 12:12:50AM +0200, Sebastian Sylvan wrote:
> On 9/14/05, Mark Carter <[EMAIL PROTECTED]> wrote:
> > The problem I was having before was that I was trying to create a
> > separate function onCbEdit, thus:
> >cbEdit <- checkBox p1 [text := "Edit Mode", on command := onCbEd
On Fri, Aug 26, 2005 at 08:27:43PM -0400, ChrisK wrote:
> to figure out since there was no Data.Array.ST.Lazy. Does anyone know
> why it was left out? I'll put a note on the HaskellTwo page about that...
Some time ago when I wanted a lazy hashtable I came up with this,
which, after minimal testi
On Tue, Jul 19, 2005 at 08:16:35PM +1000, Ben Lippmeier wrote:
> Bulat Ziganshin wrote:
>
> >reading GHC sources is always very interesting :)
> >that is from GHC/Base.hs :
>
> >getTag :: a -> Int#
> >getTag x = x `seq` dataToTag# x
>
> ! This is just what I was looking for, thankyou.
>
> My sh
On Mon, Mar 07, 2005 at 12:05:41AM +, Keean Schupke wrote:
> Daniel Fischer wrote:
>
> >The Show instances for tuples aren't automatically derived, they are
> >defined in GHC.Show. So somewhere there must be an end, probably the
> >author(s) thought that larger tuples than quintuples aren't
[WARNING: braindamag(ed|ing) experience following]
Hi all,
a few days ago I decided I desperately needed a set which could
contain (among others) itself. My first idea was
> module Main where
> import List
> import Monad
> data Elem s a = V a | R (s (Elem s a))
Now, a self-containing list can
On Mon, Feb 14, 2005 at 03:55:01PM +0100, Lennart Augustsson wrote:
> Any definition can be made point free if you have a
> complete combinator base at your disposal, e.g., S and K.
>
> Haskell has K (called const), but lacks S. S could be
> defined as
> spread f g x = f x (g x)
>
> Given that
On Sun, Feb 13, 2005 at 10:33:06PM +0100, Tomasz Zielonka wrote:
> On Sun, Feb 13, 2005 at 10:25:49PM +0100, Remi Turk wrote:
> > > BTW, I have an implementation of STM based entirely on old concurrency
> > > primitives, which means that it will work in older GHC and pr
On Sun, Feb 13, 2005 at 09:28:18PM +0100, Tomasz Zielonka wrote:
> On Sun, Feb 13, 2005 at 08:06:36PM +0100, Remi Turk wrote:
> > You might be interested in the recent STM monad then
> > (Control.Concurrent.STM in GHC-6.4): `T' for Transactional.
> > However, though it s
On Sun, Feb 13, 2005 at 01:31:56PM -0500, David Roundy wrote:
> On Sun, Feb 13, 2005 at 04:57:46PM +0100, Remi Turk wrote:
> > According to http://www.haskell.org/hawiki/MonadPlus (see also
> > the recent thread about MonadPlus) a MonadPlus instance
> > should obey m >>
On Sun, Feb 13, 2005 at 08:58:29AM -0500, David Roundy wrote:
> I've been working on a typeclass that derives from MonadPlus which will
> encapsulate certain kinds of IO. With MonadPlus, you can write monadic
> code with exceptions and everything that may not be executed in the IO
> monad. You ju
On Fri, Feb 11, 2005 at 11:14:40AM +0100, Henning Thielemann wrote:
>
> On Fri, 11 Feb 2005, Remi Turk wrote:
>
> > 1) It's talking about the compiler having difficulty with some
> >warnings when using guards.
>
> http://www.haskell.org//pipermail/haske
On Sat, Feb 12, 2005 at 01:47:06PM -0500, Benjamin Pierce wrote:
> > As a start, free access to countless general functions as soon as
> > you define a MonadPlus instance for your datatype. (Errr, `guard'
> > and `msum', as long as one stays within the Haskell98 standard
> > libraries ;)
>
> Yes,
On Sat, Feb 12, 2005 at 01:08:59PM -0500, Benjamin Pierce wrote:
> I have seen lots of examples that show how it's useful to make some type
> constructor into an instance of Monad.
>
> Where can I find examples showing why it's good to take the trouble to show
> that something is also a MonadPlus?
On Wed, Feb 09, 2005 at 02:54:12PM +0100, Henning Thielemann wrote:
>
> On Wed, 9 Feb 2005, Henning Thielemann wrote:
> > Is there also a Wiki page about things you should avoid?
>
> Since I couldn't find one, I started one on my own:
>
> http://www.haskell.org/hawiki/ThingsToAvoid
>
> I consid
On Wed, Feb 09, 2005 at 02:54:12PM +0100, Henning Thielemann wrote:
> On Wed, 9 Feb 2005, Henning Thielemann wrote:
> > Is there also a Wiki page about things you should avoid?
>
> Since I couldn't find one, I started one on my own:
>
> http://www.haskell.org/hawiki/ThingsToAvoid
>
> I consider
Ugh, replying to myself...
Obviously, the following contains a few mistakes...:
On Wed, Nov 10, 2004 at 11:34:32AM +0100, R. Turk wrote:
> {-# OPTIONS -fglasgow-exts #-}
> {- I want a Hashable instance for String ;) -}
> import Data.FiniteMap
> import Data.HashTable (hashInt, hashString)
> import
On Mon, Nov 08, 2004 at 04:40:58PM +, Graham Klyne wrote:
> Is there a module that provides functionality similar to that of
> Data.FiniteMap for keys that do not have a defined ordering relation?
Not as far as I know. (Unless you're content with the standard
List library's lookup/delete/union
On Sat, Nov 06, 2004 at 11:49:45PM +0100, Peter Simons wrote:
> Plus, powerful abstractions that make the code look simple
> and elegant _always_ come at a price. An Arrow-based stream
> processor that performs the same task as my monadic BlockIO
> library does, for instance, results in a module th
On Fri, Nov 05, 2004 at 01:57:53PM +0100, Benjamin Franksen wrote:
> Hello Experts,
>
> I need MVar and Chan to be instances of Typeable. Any hint on how this is most
> easily done would be greatly appreciated. I could change the libraries and
> add 'deriving Typeable' but I hesitate to do so.
>
On Mon, Oct 25, 2004 at 09:28:23PM +0200, Tomasz Zielonka wrote:
> On Mon, Oct 25, 2004 at 08:55:46PM +0200, Remi Turk wrote:
> > P.S. Why do so many people (including me) seem to come to Haskell
> > from Python? It can't be just the indentation, can it? ;)
>
> Ho
On Mon, Oct 25, 2004 at 02:14:28PM +0100, Simon Marlow wrote:
> On 24 October 2004 20:51, Sven Panne wrote:
>
> > IMHO it would be best to use explicit bracketing where possible, and
> > hope for the RTS/GC to try its best when one runs out of a given
> > resource. Admittedly the current Haskell i
On Mon, Oct 25, 2004 at 08:46:41AM +0200, Ketil Malde wrote:
> Remi Turk <[EMAIL PROTECTED]> writes:
>
> > IMO, [bracket] does indeed have those same drawbacks. (Although the
> > traditional "explicit memory management model" is alloc/free,
> > w
On Sun, Oct 24, 2004 at 12:19:59PM -0700, Conal Elliott wrote:
> I'm puzzled why explicit bracketing is seen as an acceptable solution.
> It seems to me that bracketing has the same drawbacks as explicit memory
> management, namely that it sometimes retains the resource (e.g., memory
> or file desc
On Sun, Oct 24, 2004 at 02:16:50PM +0200, Peter Simons wrote:
> Tomasz Zielonka writes:
>
> > AFAIK, Handles have finalisers which close them, but I
> > don't know if GHC triggers garbage collection when file
> > descriptors run out. If not, you will have problems if
> > you manage to run out
On Sun, Oct 17, 2004 at 10:53:37PM +0100, Sam Mason wrote:
> Peter Simons wrote:
> >This version should do it:
> >
> >isSubSeq :: (Eq a) => [a] -> [a] -> Bool
> >isSubSeq [] _= True
> >isSubSeq _ []= False
> >isSubSeq (x:xs) (y:ys)
> > | x == y= isSubSeq xs ys
>
On Sun, Oct 17, 2004 at 10:10:44PM +0200, Ketil Malde wrote:
> Remi Turk <[EMAIL PROTECTED]> writes:
> > Do you mean "subset" with "subsequence"?
>
> No, since a set isn't ordered.
>
> I would say a subset needs to contain some of the elemen
On Sun, Oct 17, 2004 at 11:41:59AM -0700, Peter Stranney wrote:
> Thanks guys for all your help, finally through code, sweat and tears i have found
> the solution;
>
> isSubStrand:: String -> String -> Bool
> isSubStrand [] [] = True
> isSubStrand [] (y:ys) = False
> isSubStrand (x:xs) [] = Fals
On Sun, Oct 17, 2004 at 08:05:09PM +0200, Ketil Malde wrote:
> Remi Turk <[EMAIL PROTECTED]> writes:
>
> > You might also want to look at the earlier `any prefix of tails'
> > suggestion, as it makes the solution a rather simple one-liner.
>
> Wouldn't th
On Sun, Oct 17, 2004 at 07:16:51AM -0700, Peter Stranney wrote:
> equalString :: String -> String -> Bool
> equalString [] [] = True
> equalString [] (c':s') = False
> equalString(c:s) [] = False
> equalString(c:s)(c':s') = equalChar c c'^ equalString s s'
^^^
On Fri, Aug 13, 2004 at 10:23:36AM +0200, Henning Thielemann wrote:
> On Thu, 12 Aug 2004, Remi Turk wrote:
> > On Thu, Aug 12, 2004 at 09:01:03PM +0200, Henning Thielemann wrote:
> > > If I urgently need factors of an integer I check "factor*factor > n"
> &
On Thu, Aug 12, 2004 at 09:01:03PM +0200, Henning Thielemann wrote:
>
> On Thu, 12 Aug 2004, Remi Turk wrote:
> > I usually (each time I urgently need to calculate primes ;)) use
> > a simple intSqrt = floor . sqrt . fromIntegral
> > (which will indeed give wrong answers
On Thu, Aug 12, 2004 at 06:59:26PM +0200, Christian Sievers wrote:
> [EMAIL PROTECTED] wrote:
>
> > -- Here's the discrete version of Newton's method for finding
> > -- the square root. Does it always work? Any literature?
>
> I recently used, without range check,
>
> sqrtInt n = help n where
On Tue, Jul 20, 2004 at 04:42:24PM +0100, Graham Klyne wrote:
> I found myself treading a path which led me to asking the same question as
> [1]. Given the answer [2], I'd like to stand back a little and ask if
> there's another way to tackle my niggle: what I'm interested in is a set
> compre
On Thu, Jul 08, 2004 at 11:44:38PM +0100, Alastair Reid wrote:
[snip]
> We can do better though. Using two functions in System.Random, it's easy to
> get an infinite list of random numbers:
>
> randomRsIO :: IO [Int]
> randomRsIO = do
> g <- getStdGen
> return (randoms g)
[snip]
Exc
On Mon, Aug 18, 2003 at 07:33:47PM +0200, Konrad Hinsen wrote:
> Well, yes, because my original example was cut down to illustrate the problem
> I had. The full version of the class Vect is
>
> class Vect v a where
> (<+>) :: Floating a => v a -> v a -> v a
> (<->) :: Floating a => v a -> v
On Thu, Jul 17, 2003 at 12:03:19PM +0100, Bayley, Alistair wrote:
> This is what I've turned it into to get it to work. It seems a bit clumsy;
> is there a better way to write this?
>
> > test n =
> > case True of
> > _ | n == one -> "one"
> > | n == two -> "two"
> >
On Mon, Dec 23, 2002 at 09:05:00AM +, Glynn Clements wrote:
> Jyrinx wrote:
> > So is this lazy-stream-via-unsafeInterleaveIO not so nasty, then, so
> > long as a few precautions (not reading too far into the stream,
> > accounting for buffering, etc.) are taken? I like the idiom Hudak uses
On Sun, Dec 22, 2002 at 04:00:45AM -0800, Jyrinx wrote:
> As an experiment for a bigger project, I cooked up a simple program: It
> asks for integers interactively, and after each input, it spits out the
> running total. The wrinkle is that the function for calculating the
> total should be a no
On Sun, Oct 06, 2002 at 07:57:18PM +, Zdenek Dvorak wrote:
> Hello,
>
> >How does one debug in haskell? I have a function that I could swear should
> >behave differently than it does, and after tracking down bugs for many
> >hours, I'm wondering if there's any way to step through the evaluati
On Wed, Apr 03, 2002 at 07:13:03AM -0500, Michal Wallace wrote:
>
> Hello everyone,
>
> I just wrote my first haskell program. I started with a
> simple python program and tried to see if I could port it to
> haskell. The program reads text from stdin and prints out a
> histogram of all the let
On Thu, Feb 07, 2002 at 08:00:36AM -0800, Ian Zimmerman wrote:
>
> I am new to the language (coming from ML) and I am sorry if my first
> post turns out to be a flamebait, but I can't help it:
>
> Why in the world did the designers of Haskell permit the ' character
> to be both a prime (part of
ppy Hacking
Remi
--
I have so much
I want to say
but it doesen't matter
anyway
Key fingerprint = CC90 A1BA CF6D 891C 5B88 C543 6C5F C469 8F20 70F4
{-
Read from /dev/random
Copyright (C) 2001 Remi Turk <[EMAIL PROTECTED]>
This program is free software
54 matches
Mail list logo