On Sat, Feb 6, 2010 at 1:42 PM, Mark Spezzano
wrote:
> Just wondering whether I can use ShowS or tupling or Difference Lists to
> speed up the following code?...
In case you do want to use a difference list, you could also use a
DString[1]. A DString is just a newtype wrapper around a difference
write something more detailed about this project some
time from now.
regards,
Roel and Bas van Dijk
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On Wed, Feb 10, 2010 at 9:50 PM, Don Stewart wrote:
> ... Perhaps more users could add their details to
> http://haskell.org/haskellwiki/Haskell_in_industry ...
done
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/l
On Wed, Feb 17, 2010 at 10:23 PM, Sean Leather wrote:
>> -- oo :: (c -> d) -> (a -> b -> c) -> a -> b -> d
>> oo :: (Category cat) => cat c d -> (a -> cat b c) -> a -> cat b d
>> oo = (.) . (.)
I think at NL-FP day 2008 at Utrecht somebody called '(.) . (.)' the
'boob' operator... it was late an
mance (no lookup required).
>
> Every exported symbol is now documented.
>
>
> Regards,
> Roel & Bas van Dijk
>
> [1] http://hackage.haskell.org/package/concurrent-extra-0.2
> [2] http://hackage.haskell.org/package/threadmanager-0.1.3
> ___
Hello,
I discovered a bug in our: Control.Concurrent.Thread
In the documentation of 'forkIO' we specify that the forked thread
inherits the blocked state of its parent. However our implementation
did not ensure this.
The newly released concurrent-extra-0.3.1 fixes this.
This release also adds t
On Sun, Mar 14, 2010 at 3:49 PM, David Waern wrote:
> ...
> -- Changes in version 2.7.0
> ...
> * Bug fixes (most importantly #128)
> ...
Nice!
Ross, can this be installed on hackage? Because the documentation of
the base library is suffering from bug #128:
http://trac.haskell.org/haddock/tick
On Wed, Mar 17, 2010 at 5:55 PM, Vasyl Pasternak
wrote:
> BTW, I think it is more useful to let user set the chunk size for
> reading, so I'd like to see this possibility in the iteratee package.
Indeed, this is also the way I designed my enumerator for usb bulk and
interrupt reads:
http://code.
Hello,
I've written a tiny package for restricting access to mutable
variables to be read-only or write-only:
http://code.haskell.org/~basvandijk/code/only-read-or-write-vars/
This is a Request For Comments, so any comments / patches / +1s / -1s
about anything are more than welcome before I uplo
On Fri, Mar 19, 2010 at 4:03 AM, Nicolas Frisby
wrote:
> Alternatively:
>
> let f ::
> f = ...
>
> f' :: a ->
> f' _ = f
> in f' (undefined :: Int)
Or use Edward Kmett's tagged library:
http://hackage.haskell.org/packages/archive/tagged/0.0/doc/html/Data-Tagged.html
so you don't hav
On Fri, Mar 19, 2010 at 5:49 PM, vlado wrote:
> +1 - I like it, I've used this technique in some private projects
Nice, I hope you can use this package.
> I wonder if this would be a place to add a function returning the pair
> of the read and write capabilities (for the lack of a better word) o
On Sun, Mar 21, 2010 at 5:05 PM, Sebastiaan Visser wrote:
> Straight from Zurihac: I'm very pleased to announce the 1.0.0 release of the
> Salvia web server.
Hoi Sebastiaan,
(switching to English) I discovered a major space-leak in
Network.Salvia.Impl.Server.start due to the use of threadmanage
On Tue, Mar 23, 2010 at 2:13 PM, Sebastiaan Visser wrote:
> Nice! This is certainly worth it.
I'm glad you like it.
Sebastiaan, I made the same mistake as threadmanager does: I forgot to
block before installing the deleteMyPid exception handler in the
forked thread. I added a new patch that adds
On Tue, Mar 23, 2010 at 2:30 PM, Gwern Branwen wrote:
> I use ' git format-patch origin'.
Thanks!
In case you have trouble pulling from my webserver I attached the same
two patches using Gwern's method to this email.
On Tue, Mar 23, 2010 at 2:34 PM, Chris Eidhof wrote:
> The way I like to work
On Tue, Mar 23, 2010 at 8:23 PM, David Leimbach wrote:
> Is this just a problem of spawning too many forkIO resources that never
> produce a result?
It looks like it. Lets look at the implementation of timeout:
timeout :: Int -> IO a -> IO (Maybe a)
timeout n f
| n < 0= fmap Just f
On Tue, Mar 23, 2010 at 10:20 PM, Simon Marlow wrote:
> The leak is caused by the Data.Unique library, and coincidentally it was
> fixed recently. 6.12.2 will have the fix.
Oh yes of course, I've reported that bug myself but didn't realize it
was the problem here :-)
David, to clarify the probl
On Wed, Mar 24, 2010 at 6:31 PM, Ozgur Akgun wrote:
> What was I thinking?
A sensible thought if you asked me.
It's certainly a surprise to me that this isn't allowed. Because in
any other context binders, like lambdas and foralls, may be freely
nested. For example:
{-# LANGUAGE RankNTypes #-}
Dear all, (sorry for this long mail)
When programming in the IO monad you have to be careful about
asynchronous exceptions. These nasty little worms can be thrown to you
at any point in your IO computation. You have to be extra careful when
doing, what must be, an atomic transaction like:
do old
On Thu, Mar 25, 2010 at 5:36 PM, Simon Marlow wrote:
> Nice, I hadn't noticed that you can now code this up in the library since we
> added 'blocked'. Unfortunately this isn't cheap: 'blocked' is currently an
> out-of-line call to the RTS, so if we want to start using it for important
> things li
On Thu, Mar 25, 2010 at 6:07 PM, Jason Dagit wrote:
> What is the next step for getting rid of the obsolete comment? Did you
> already nuke it? If not, I could try to get a copy of the ghc repo and
> see if I can figure out the right protocol for submitting a patch.
Making library patches is no
On Thu, Mar 25, 2010 at 11:23 PM, Simon Marlow wrote:
>> So I'm all for deprecating 'block' in favor of 'mask'. However what do
>> we call 'unblock'? 'unmask' maybe? However when we have:
>>
>> mask $ mask $ unmask x
>>
>> and these operations have the counting nesting levels semantics,
>> asynchr
On Fri, Mar 26, 2010 at 3:43 PM, Gregory Collins
wrote:
> Matthew Brecknell writes:
>
>> And is confirmed by a simple test (with GHC 6.10.4 on Linux):
>>
>> import Prelude hiding(catch)
>> import Control.Concurrent
>> import Control.Exception
>>
>> main = do
>> chan <- newEmptyMVar
>> done <-
On Wed, Mar 31, 2010 at 9:17 AM, Paul Brauner wrote:
> Does anyone have an idea why calling rnf before the bench
> doesn't seem to "cache" the result as calling show does?
> (my instances of NFData follow the scheme described in strictbench
> documentation).
Is it possible you could show us your
On Wed, Mar 31, 2010 at 11:06 AM, Paul Brauner wrote:
> data Term = Lam Term | App Term Term | Var Int
>
> instance NFData where
> rnf (Lam t) = rnf t
> rnf (App t1 t2) = rnf t1 `seq` rnf t2
> rnf (Var x) = rnf x
>
> the actual datatype doesn't have fancy stuff like higher-order
> types
On Wed, Mar 31, 2010 at 12:57 PM, Bas van Dijk wrote:
> main = let !t = genterm in defaultMain [bench "subst" $ nf (subst u) t]
Oops, that should be:
main = let t = genterm in rnf t `seq` defaultMain [bench "subst" $ nf
(subst u) t]
Bas
On Wed, Mar 31, 2010 at 7:42 PM, David Leimbach wrote:
> What I mean is let's say the stream has
> "abcd efg abcd efg"
> and then I run some kind of iteratee computation looking for "abcd"
You could adapt the 'heads' function from the iteratee package to do this:
http://hackage.haskell.org/packa
On Wed, Apr 7, 2010 at 5:12 PM, Simon Marlow wrote:
> Comments?
I really like this design.
One question, are you planning to write the MVar utility functions
using 'mask' or using 'nonInterruptibleMask'? As in:
> withMVar :: MVar a -> (a -> IO b) -> IO b
> withMVar m f = whichMask? $ \restore -
It looks like your timedIterateIO is too lazy.
When you pass it a function like (+1) what will happen is that a large
chunk of the form ...+1+1+1+1+1 is build up on your heap. When you
finally need its value the large chunk will be evaluated causing it to
push the '1' arguments on the stack. When
On Thu, Apr 8, 2010 at 11:00 AM, Sean Leather wrote:
> I created a few tools to help me manage multiple GHC distributions in a Bash
> shell environment. Perhaps it's useful to others.
>
> http://github.com/spl/multi-ghc
>
> Feedback welcome. I'd also like to know if something similar exists.
Do
On Thu, Apr 8, 2010 at 9:15 PM, Isaac Dupree
wrote:
> I still would like to see examples of where it's needed, because I slightly
> suspect that wrapping possibly-blocking operations in an exception handler
> that does something appropriate, along with ordinary 'mask', might be
> sufficient... But
On Thu, Apr 8, 2010 at 11:45 PM, Bas van Dijk wrote:
> On Thu, Apr 8, 2010 at 9:15 PM, Isaac Dupree
> wrote:
>> I still would like to see examples of where it's needed, because I slightly
>> suspect that wrapping possibly-blocking operations in an exception handler
On Thu, Apr 8, 2010 at 8:41 PM, Simon Michael wrote:
> With Christian's blessing, I have taken over maintenance of darcsum and
> would like to announce the 1.2 release:
Nice! I'm a power user of darcsum and I'm definitely going to try out
this release.
Thanks for maintaining this tool,
Bas
On Fri, Apr 9, 2010 at 3:22 AM, Isaac Dupree
wrote:
> OK, thanks for the link! In fact, [tell me if my reasoning is wrong...], in
> that fork-definition, the 'putMVar' will never block, because there is only
> putMVar one for each created MVar.
Yes that's correct.
> I seem to remember that any
On Fri, Apr 9, 2010 at 10:40 AM, Bertram Felgenhauer
wrote:
> How does forkIO fit into the picture? That's one point where reasonable
> code may want to unblock all exceptions unconditionally - for example to
> allow the thread to be killed later.
>
> timeout t io = block $ do
> result <
On Wed, Apr 7, 2010 at 5:12 PM, Simon Marlow wrote:
> Comments? I have a working implementation, just cleaning it up to make a
> patch.
Can you also take a look at these bugs I reported earlier:
http://hackage.haskell.org/trac/ghc/ticket/3944
http://hackage.haskell.org/trac/ghc/ticket/3945
The
On Sat, Apr 17, 2010 at 8:22 AM, Jason Dagit wrote:
> ...
> One place where lazy accumulators is bad are the left folds. There is the
> lazy foldl and the version which is strict in the accumulator, foldl'. Try
> summing big lists of integers, let's use ghci and limit the heap to 1 meg:
> ghci
On Mon, Apr 12, 2010 at 10:27 PM, Mark Snyder wrote:
> So in this line of thought, where we have the operations and the control
> operators, I guess my original question wasn't aware of the distinction, and
> was looking for a name for all of them combined. In Haskell (specifically
> in the mtl),
On Mon, Apr 19, 2010 at 5:54 PM, Simon Marlow wrote:
> So I think I like this variant, even though it adds a little API overhead.
> Anyone else have any thoughts on this?
I do think the RankNTypes version:
mask :: ((forall b. IO b -> IO b) -> IO a) -> IO a
is easier to use and explain because it
2010/4/19 Jonas Almström Duregård :
>> If this is to be used with QuickCheck maybe it should be named that way.
> Certainly worth considering. There seems to be no convenient way of
> renaming packages on Hackage though, is there?
AFAIK hackage has support for deprecating packages in favor of othe
On Tue, Apr 20, 2010 at 8:48 AM, Tom Hawkins wrote:
> I have a bunch of global variables in C I would like to directly read
> and write from Haskell. Is this possible with FFI, or must I write a
> bunch of C wrapper functions for the interface, i.e. a 'get' and a
> 'set' for each variable?
I bel
On Tue, Apr 20, 2010 at 12:56 PM, Simon Marlow wrote:
> On 09/04/2010 12:14, Bertram Felgenhauer wrote:
>>
>> Simon Marlow wrote:
>>>
>>> On 09/04/2010 09:40, Bertram Felgenhauer wrote:
timeout t io = mask $ \restore -> do
result<- newEmptyMVar
tid<- for
On Wed, Apr 21, 2010 at 8:07 PM, Aaron D. Ball
wrote:
> If I have the basic building block, which is the ability to
> serialize a Haskell expression with its dependencies and read them
> into another Haskell instance where I can evaluate them, I can handle
> the other pieces
How I wish we had Cle
On Thu, Apr 22, 2010 at 10:30 AM, Simon Marlow wrote:
> Funnily enough, before posting the above message I followed exactly the line
> of reasoning you detail below to discover that there isn't a way to fix this
> using parametricity. It's useful to have it documented, though - thanks.
In their
I created a ticket about the "asynchronous exception wormholes" so
that we won't forget about them:
http://hackage.haskell.org/trac/ghc/ticket/4035
regards,
Bas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listi
On Thu, May 6, 2010 at 3:24 PM, Michael Snoyman wrote:
>
>
> On Thu, May 6, 2010 at 9:13 AM, Bryan O'Sullivan wrote:
>>
>> On Wed, May 5, 2010 at 10:51 PM, Michael Snoyman
>> wrote:
>>>
>>> * When a connection is released, is goes to the end of the pool, so
>>> connections get used evenly (not s
On Thu, May 6, 2010 at 3:24 PM, Michael Snoyman wrote:
>
>
> On Thu, May 6, 2010 at 9:13 AM, Bryan O'Sullivan wrote:
>>
>> On Wed, May 5, 2010 at 10:51 PM, Michael Snoyman
>> wrote:
>>>
>>> * When a connection is released, is goes to the end of the pool, so
>>> connections get used evenly (not s
On Thu, May 6, 2010 at 7:48 PM, Bas van Dijk wrote:
> On Thu, May 6, 2010 at 3:24 PM, Michael Snoyman wrote:
>>
>>
>> On Thu, May 6, 2010 at 9:13 AM, Bryan O'Sullivan wrote:
>>>
>>> On Wed, May 5, 2010 at 10:51 PM, Michael Snoyman
>>> wrot
On Thu, May 6, 2010 at 11:54 PM, Bas van Dijk wrote:
> On Thu, May 6, 2010 at 7:48 PM, Bas van Dijk wrote:
>> On Thu, May 6, 2010 at 3:24 PM, Michael Snoyman wrote:
>>>
>>>
>>> On Thu, May 6, 2010 at 9:13 AM, Bryan O'Sullivan
>>> wrote:
Hi Stephen,
precis reports parse errors when applied to packages containing Unicode syntax.
Regards,
Bas
On Thu, May 13, 2010 at 2:25 PM, Stephen Tetley
wrote:
> On 5 May 2010 12:14, Henning Thielemann wrote:
>>
>> On Wed, 5 May 2010, Stephen Tetley wrote:
>>
>>> I'm open to suggests for pret
On Mon, May 17, 2010 at 7:12 PM, Don Stewart wrote:
> dpx.infinity:
>> Hi,
>> I'm writing a program which listens to some D-Bus signals using
>> DBus.Client.onSignal function from dbus-client package. This function
>> runs IO action in separate haskell thread when signal is received. My
>> program
Dear all,
I uploaded threads-0.1.0.1 to hackage. Threads is a small package that
lets you fork threads and wait for their result.
The basic interface is simply:
module Control.Concurrent.Thread where
data ThreadId α
forkIO ∷ IO α → IO (ThreadId α)
wait ∷ ThreadId α → IO (Either SomeExcepti
Q14: Do you see any problems with respect to integrating BlazeHtml in
your favourite web-framework/server?
How about also providing an enumerator back-end?
http://hackage.haskell.org/packages/archive/iteratee/0.3.5/doc/html/Data-Iteratee-Base.html#t%3AEnumeratorGM
Then your library can integrate
On Thu, May 27, 2010 at 10:48 AM, Jasper Van der Jeugt
wrote:
>> How about also providing an enumerator back-end?
>> http://hackage.haskell.org/packages/archive/iteratee/0.3.5/doc/html/Data-Iteratee-Base.html#t%3AEnumeratorGM
>>
>> Then your library can integrate more easily with the snap framewor
Thanks for writing this package.
I used those functions myself in my usb package:
http://hackage.haskell.org/packages/archive/usb/0.3.1/doc/html/src/System-USB-IO-Synchronous-Enumerator.html#genAlloca
(set you browser to UTF-8 encoding to correctly view the Unicode symbols)
I've now patched usb t
On Tue, Jun 1, 2010 at 5:55 PM, Stephen Tetley wrote:
> What's the procedure for marking one's own package(s) as deprecated on
> Hackage?
Ask Ross Paterson to deprecate your package.
Once a package is deprecated it won't show up in the package list
anymore but will still be available from the p
On Tue, Jun 1, 2010 at 7:09 PM, Matthias Kilian wrote:
> - "Liveness" of a library, that is: does it still get updates? Does it
> build with recent versions of GHC?
Note that Hackage already shows the upload date and for which versions
of GHC the package does and doesn't build.
> - Reverse depe
On Mon, May 31, 2010 at 12:08 PM, Arie Peterson wrote:
> - I tried using the "regions" package, since it has a very similar
> purpose, but this seems impossible: some resources I could not express in
> the form required for its class 'Resource' (methods 'open' and 'close').
Hi Arie, I would love
Hello,
I just released threads-0.2. The library which lets you fork threads
and wait for their result.
INSTALL:
$ cabal update
$ cabal install threads
API DOCS:
http://hackage.haskell.org/package/threads-0.2
DEVELOPMENT:
darcs get http://code.haskell.org/~basvandijk/code/threads
CHANGES:
* I r
atchIO m => Int -> Memory m a
memory size = Resource $ bracket (liftIO $ mallocBytes size) (liftIO . free)
Regards,
Bas
On Wed, Jun 2, 2010 at 1:11 AM, Arie Peterson wrote:
> On Tue, 1 Jun 2010 21:10:40 +0200, Bas van Dijk
> wrote:
> | [...]
> | Hi Arie, I would love to se
open r) (liftIO . C.close)
Regards,
Bas
On Wed, Jun 2, 2010 at 2:28 PM, Bas van Dijk wrote:
> Before answering your questions I would like to make sure I understand
> your Resource type. When I want to create a memory Resource for
> example is the following what you have in mind?
&
On Wed, Jun 2, 2010 at 2:57 PM, Arie Peterson wrote:
>> On Wed, Jun 2, 2010 at 2:28 PM, Bas van Dijk
> wrote:
>>> Before answering your questions I would like to make sure I understand
>>> your Resource type. When I want to create a memory Resource for
>>> ex
On Wed, Jun 2, 2010 at 2:20 PM, Uwe Schmidt wrote:
> For ranking the results for a package search, a download statistic could be
> very useful and could easily be integrated. If such a statistic would be
> available in machine readable format (csv, xml, plain text, ...), we could
> integrate that.
On Wed, Jun 2, 2010 at 4:35 PM, Uwe Schmidt wrote:
> Bas wrote:
>
>> Ordering by nr of direct/indirect reverse dependencies might also be
>> useful.
>
> this is already done.
Ok nice.
For others who like to have a .csv file version of the reverse
dependency page I quickly hacked something togeth
ttp://code.haskell.org/~basvandijk/code/usb-safe-and-safer-file-handles-examples
Regards,
Bas
On Wed, Jun 2, 2010 at 3:13 PM, Bas van Dijk wrote:
> On Wed, Jun 2, 2010 at 2:57 PM, Arie Peterson wrote:
>>> On Wed, Jun 2, 2010 at 2:28 PM, Bas van Dijk
>> wrote:
>>>
On Mon, Jun 7, 2010 at 9:49 PM, Claus Reinke wrote:
> As others have pointed out, you can't go from operation to representation,
> but you can pair operations and expressions with their representations.
This idea is also implemented in my little 'repr' package:
http://hackage.haskell.org/package
On Sat, Jun 12, 2010 at 1:12 PM, Tilo Wiklund wrote:
> I am probably missing something obvious or something relating to
> optimisation/server software but defining iteratees as "Iteratee s a =
> Cont (s -> Either (s, a) (Iteratee s a))" seems to lead to a more
> natural monad instance, and does no
On Tue, Jun 15, 2010 at 7:23 PM, Martin Drautzburg
wrote:
> When I know my supplies I want to know what I can produce. When I know what I
> want to produce I want to know what supplies I need for that. Both kinds of
> questions should be answered by a singe Process thingy.
Your Process thingy rem
On Mon, Jun 14, 2010 at 7:42 AM, Aran Donohue wrote:
> Hints? Tips?
One thing that isn't mentioned yet is to read other peoples programs.
I'm subscribed to the Hackage RSS feed[1]. I tend to read (at least)
the package page of every package that gets uploaded to hackage.
Whenever an interesting
On Tue, Jun 15, 2010 at 9:26 PM, Bas van Dijk wrote:
> On Tue, Jun 15, 2010 at 7:23 PM, Martin Drautzburg
> wrote:
>> When I know my supplies I want to know what I can produce. When I know what I
>> want to produce I want to know what supplies I need for that. Both kinds of
&
On Wed, Jul 15, 2009 at 3:02 AM, Thomas Hartman wrote:
> Please suggest more of these types of exercises if you have them and
> maybe we can collect the folk wisdom into a wiki page and/or exercise
> page for beginners.
My 'stream' library[1] also has some examples. Look at the following
functions
On Wed, Jul 15, 2009 at 6:35 PM, Ryan Ingram wrote:
> iterate' f x = x `seq` x : iterate' f (f x)
> seems better; it doesn't evaluate list elements you don't visit.
iterate'' f x = x : (iterate'' f $! f x)
...seems the most lazy strict iterate.
(Bas wishes for a type system that can express the
On Thu, Jul 16, 2009 at 7:45 PM, Thomas Hartman wrote:
> the strict functions seem very nice, will they eventually make their way into
> http://hackage.haskell.org/packages/archive/Stream/0.3.2/doc/html/Data-Stream.html
Note that there are two stream packages:
* 'Stream' by Wouter Swierstra (incl
On Thu, Jul 16, 2009 at 8:22 PM, Thomas Hartman wrote:
> I played with this a bit, and ok, it seems the difference between
> iterate' and iterate'' is
>
> h _ = 2
>
> tit' = head . drop 1 . iterate' h $ undefined
> tit'' = head . drop 1 . iterate'' h $ undefined
Exactly, iterate' first evaluates '
On Thu, Jul 16, 2009 at 9:57 PM, Ryan Ingram wrote:
>> On Thu, Jul 16, 2009 at 8:22 PM, Thomas Hartman wrote:
>>> Is this being worked on?
>
> On Thu, Jul 16, 2009 at 12:35 PM, Bas van Dijk wrote:
>> I have no idea.
>
> Yes.
>
> Bolingbroke, Peyton-Jones.
; infixr :*:
Converting a Vector to a list is easy:
> toList :: Vector b n -> [b]
> toList Nil= []
> toList (x :*: xs) = x : toList xs
My single question is: how can I convert a list to a Vector???
> fromList :: [b] -> Vector b n
> fromList = ?
regards,
Roel and Bas van Dijk
[1] http://www.ics.forth.gr/~lourakis/levmar/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On Fri, Aug 21, 2009 at 2:02 PM, Miguel Mitrofanov wrote:
>>> {-# LANGUAGE UndecidableInstances #-}
>
> Ouch!
>
> Don't worry, it's just me not liking UndecidableInstances.
Without it, GHC doesn't like the 'Arg f ~ b' constraint not being
smaller than the instance head in:
instance (ModelFunc f,
Thanks for all the advice.
I have this so far. Unfortunately I have to use unsafeCoerce:
-
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
module LevMar where
On Fri, Aug 21, 2009 at 8:50 PM, Jason Dagit wrote:
>>> toPeano :: Int -> (forall n. Nat n => n -> t) -> t
>
> This looks a bit more promising. For those unfamiliar with this form,
> it is the logical "negation" of the previous type. One description is
> here [1], where it is mentioned that th
On Tue, Aug 25, 2009 at 12:07 AM, Ryan Ingram wrote:
> unsafeCoerce is ugly and I wouldn't count on that working properly.
>
> Here's a real solution:
> ...
Thanks very much! I'm beginning to understand the code.
The only thing I don't understand is why you need:
> newtype Witness x = Witness {
Hello,
In the levmar binding[1][2] me and my brother are working on, I need a
function composition operator that is overloaded to work on functions
of any arity. Basically its type needs to be something like the
following:
(.*) :: (b -> c) -> NFunction n a b -> NFunction n a c
where 'NFunction n
defaultOpts
Nothing
Nothing
noLinearConstraints
Nothing
You get the following fit (using levmar-chart):
http://code.haskell.org/~roelvandijk/code/levmar-chart/cubicFit.png
Note that levmar contains a demo with a lot more examples:
http://code.haskell.org/levmar/De
On Mon, Sep 14, 2009 at 7:36 AM, Paul L wrote:
> It's available on Hackage DB at http://hackage.haskell.org/package/LambdaINet
Nice! Screenshots anywhere?
Bas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinf
Hello,
We like to announce a new release of the high-level
Levenberg-Marquardt library levmar:
http://hackage.haskell.org/package/levmar-0.2
Changes:
* There's one new major feature: automatic calculation of the Jacobian
using automatic differentiation with Conal Elliott's vector-space
library.
by Simon Peyton Jones,
contains some references to papers about transformation to
Continuation-Passing-Style. It also discusses the difference between
CPS and the STG language:
http://research.microsoft.com/users/simonpj/papers/spineless-tagless-gmachine.ps.gz
regard
This would be a lot of fun! Make sure to take the lessons from
http://haskell.org/haskellwiki/Safely_running_untrusted_Haskell_code
into account.
regards,
Bas van Dijk
On 7/15/07, Hugh Perkins <[EMAIL PROTECTED]> wrote:
Had an idea: a real shootout game for Haskell.
The way it would w
On 8/14/07, Peter Verswyvelen <[EMAIL PROTECTED]> wrote:
> I noticed many code snippets on the wiki that have syntax colouring.
>
> How is this done? Can I convert syntax coloured code from Emacs to HTML?
Look at HsColour:
http://www.cs.york.ac.uk/fp/darcs/hscolour/
regards
ist
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
Maybe:
http://www.haskell.org/haskellwiki/Blow_your_mind
and:
http://haskell.org/haskellwiki/Research_papers/Functional_pearls
regards,
Bas van Dijk
On 8/20/07, Stefan O'Rear <[EMAIL PROTECTED]> wrote:
> ...
> (I need to find some way to automate making these trails :) )
> ...
I think you can come a long way with the debugger in GHC HEAD. It
provides a :trace command that, when applied to an expression with
some breakpoint in it, remembers the
x trees are represented using Haskell
datatypes and, at compile time, they can be manipulated by Haskell
code. This allows you to reify (convert from concrete syntax to an
abstract syntax tree) some code, transform it and splice it back in
(convert back again), or even to produce completely new c
On 8/27/07, Derek Elkins <[EMAIL PROTECTED]> wrote:
> ...Really, it's not all that appropriate a name anyway...
Indeed, Meta Haskell would be better I think.
Bas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listi
a and wasn't inclined to find out.
>
> Best regards,
> Esa
> ___________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
Ideally, we would have something like pyserial (
http://pyserial.sourceforge.net ) for Haskell. It provides a nice
portable abstraction over serial communication. See for example the
windows binding:
http://pyserial.cvs.sourceforge.net/pyserial/pyserial/serial/serialwin32.py?view=markup
regards,
Bas van Dijk
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On 9/16/07, Mads Lindstrøm <[EMAIL PROTECTED]> wrote:
> Hi all
>
> If I have this type:
>
> data Foo a b = ...
>
> and this class
>
> class Bar (x :: * -> *) where ...
>
> I can imagine two ways to make Foo an instance of Bar. Either I must
> "apply" the 'a' or the 'b' in (Foo a b). Otherwise i
On 9/17/07, Roberto Zunino <[EMAIL PROTECTED]> wrote:
> I thought this was possible with GADTs (is it?):
>
> data Z
> data S n
> data List a len where
>Nil :: List a Z
>Cons:: a -> List a len -> List a (S len)
>
Slightly related:
The other day I was playing with exactly this GADT. See: ht
On 9/18/07, apfelmus <[EMAIL PROTECTED]> wrote:
> ...in reality, foldr is (almost) the induction principle for natural numbers!
Oh yes, nice observation!
Afpelmus, thanks for your thorough answers!
regards,
Bas
___
Haskell-Cafe mailing list
Haskell-Ca
On 9/19/07, Janis Voigtlaender <[EMAIL PROTECTED]> wrote:
> BTW, what would have been the easiest way for me to find this out on my
> own?
The following is probably not the easiest way:
I keep a copy of the sources of GHC and the libraries [1] on my disk.
When I want to search for something I sim
On 9/19/07, Roberto Zunino <[EMAIL PROTECTED]> wrote:
> Henning Thielemann wrote:
> > Then why are patterns in lambdas not lazy?
>
> Because they should allow for more branches! ;-))
>
> null = \ [] -> True
> _ -> False
See http://hackage.haskell.org/trac/haskell-prime/ticket/114 for a
ract the right method ('fromInteger')
from the dictionary and apply it to a concrete Integer. This is what
happens in the case expression: we extract the method 'tpl9_Ba' and
apply it to 'GHC.Num.S# 1'.
Now that our literal 1 is defined, a lambda abstraction is cre
On 9/24/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:
> Anybody happen to know what the time complexity of "transpose" is?
Looking at the definition of 'transpose' in:
http://darcs.haskell.org/libraries/base/Data/List.hs:
transpose :: [[a]] -> [[a]]
transpose [] = []
tran
ame the recursive 'Expr env'
explicitly. However constructing a 'Expr' is a bit verbose because of
the 'In' newtype constructors.
regards,
Bas van Dijk
[1] http://citeseer.ist.psu.edu/293490.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On 9/28/07, Chuk Goodin <[EMAIL PROTECTED]> wrote:
> I have a list of lists of pairs of numeric Strings (like this:
> [["2","3"],["1","2"],["13","14"]] etc.) I'd like to change
> it into a list of a list of numbers...
Now that you know (map . map) which Jonathan explained you need to
apply that to
1 - 100 of 438 matches
Mail list logo