On Fri, Feb 13, 2009 at 08:06, Magicloud wrote:
> Hi,
> I am using Text.CSV to read and using gtk2hs to display csv files using
> utf-8 encode. Well, it displays broken strings, seems like it cannot deal
> with utf-8.
> What should I do?
You should try using functions from utf8-string package
Hi,
I am using Text.CSV to read and using gtk2hs to display csv files
using utf-8 encode. Well, it displays broken strings, seems like it
cannot deal with utf-8.
What should I do?
Thanks.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
h
> Can you live with
>infixl |$|
>(|$|) :: [a -> r] -> a -> [r]
>fs |$| x = map ($ x) fs
> and, instead of "broadcast fs a b" use
>fs |$| a |$| b
> ?
map ($ x) fs
= { Applicative Functors satisfy... }
pure ($ x) <*> fs
= { 'interchange' rule from Control.Applicative }
fs <*>
SYB makes very heavy use of Typeable as well, although not, as I
recall dynamics as such.
Cheers,
Sterl.
On Feb 12, 2009, at 3:40 PM, Don Stewart wrote:
Notably, extensible exceptions use dynamics, in conjunction with type
classes and existentials.
A number of solutions to the 'expression p
+1 for some graphical tools for darcs, especially even a graphical
merge tool (and a console/curses based version as well, to be sure).
And +1 for darcs and xmonad applying as mentoring organizations in
their own right.
For that matter, it might be worthwhile for GHC to apply as well!
Tha
John Ky wrote:
> Is there a way to define type r to be all types except functions?
Perhaps the following article
How to write an instance for not-a-function
http://okmij.org/ftp/Haskell/typecast.html#is-function-type
answers your question. It shows several complete examples.
On Thu, Feb 12, 2009 at 6:26 PM, Don Stewart wrote:
> bugfact:
>> Consider the following code
>>
>> stamp v x = do
>> t <- getCurrentTime
>> putMVar v (x,t)
>>
>> Is it possible - with GHC - that a thread switch happens after the t <-
>> getCurrentTime and the putMVar v (x,t)?
>
> Yes. if 't'
So, I was reading a bit about continuations the other day, and, since I've
been thinking about good ways of expressing chess strategies in Haskell, I
thought that I'd play around a bit with something like continuations for
game-playing strategies. The idea is that you have combinators that allow
yo
On Thu, 2009-02-12 at 19:55 -0500, Chung-chieh Shan wrote:
> wren ng thornton wrote in article
> <4993bbee.9070...@freegeek.org> in gmane.comp.lang.haskell.cafe:
> > It's ugly, but one option is to just reify your continuations as an ADT,
> > where there are constructors for each function and fi
Cristiano Paris wrote in article
in
gmane.comp.lang.haskell.cafe:
> In effect, this is a bit different from the syscall service routine
> described by Oleg, as the scheduler function reacts in different ways
> for subsequent calls (the first time feeds "Hello!", the second one
> "World!", in a
My thoughts on type families:
1) Type families are often too open. I causes "rigid variable"
type error messages because when I start writing open type
functions, I often realize that what I really intend is not
truly open type functions. It happens a lot that I had some
assumptions on the argume
> So in general, think hard about missing capabilities in Haskell:
>
>* tools
>* libraries
>* infrastructure
>
> that benefit the broadest number of Haskell users or developers.
>
> Another route is to identify a clear niche where Haskell could leap
> ahead of the competition, with a sm
wren ng thornton wrote in article
<4993bbee.9070...@freegeek.org> in gmane.comp.lang.haskell.cafe:
> It's ugly, but one option is to just reify your continuations as an ADT,
> where there are constructors for each function and fields for each
> variable that needs closing over. Serializing that
On Fri, 2009-02-13 at 11:15 +1100, John Ky wrote:
> Hi Johnaton,
>
> Ah yes. That makes sense. Is there a way to define type r to be all
> types except functions?
Not without overlapping instances. I *think* if you turn on {-#
LANGUAGE OverlappingInstances #-} then
instance Broadcast r wher
If you have ideas for student projects that you think would benefit the
Haskell community, now is the time to start discussing them on mailing
Here is an idea that if done right might bootstrap Haskell real world
applications with the help of greed
and adrenaline:-)
The ignition:
(0) Bind Hask
If you have ideas for student projects that you think would benefit the
Haskell community, now is the time to start discussing them on mailing
Here is an idea that if done right might bootstrap Haskell real world
applications with the help of greed
and adrenaline:-)
The ignition:
(0) Bind Hask
On Fri, 2009-02-13 at 13:30 +1300, Richard O'Keefe wrote:
> Let's take this example from the web.
>x2 +
> 4x +
> 4
NB: This example is *precisely* why I will never adopt MathML as an
authoring format. Bowing and scraping at the alter of W3C is not worth
using such a terrible syntax,
On 12 Feb 2009, at 8:48 pm, Wolfgang Jeltsch wrote:
I don’t understand this. The way which works is conversion from
MathML to TeX.
So your suggestion would be to use MathML as the source language.
But this is
obviously not what you suggest. I’m confused.
It's explicit enough in the origi
oops, I take that back. It only appears to work if you are sloppy:
x :: (Monad m) => m a
x = undefined
y :: (Monad m) => m b
y = undefined
g :: (Monad m) => a -> b -> m c
g = undefined
ex1 :: (Monad m) :: m c
ex1 = (g =<< x) =<< y
But, if you try to pin down the types you find it only works be
Hi Johnaton,
Ah yes. That makes sense. Is there a way to define type r to be all types
except functions?
-John
On Fri, Feb 13, 2009 at 10:44 AM, Jonathan Cast
wrote:
> On Fri, 2009-02-13 at 10:34 +1100, John Ky wrote:
> > Hi Haskell Cafe,
> >
> > I tried using type families over functions, bu
On Thu, 2009-02-12 at 23:36 +, Edsko de Vries wrote:
> Hi,
>
> I can desugar
>
> do x' <- x
> f x'
>
> as
>
> x >>= \x -> f x'
>
> which is clearly the same as
>
> x >>= f
>
> However, now consider
>
> do x' <- x
> y' <- y
> f x' y'
>
> desugared, this is
>
>
Hello,
You could do:
(f =<< x) =<< y
?
- jeremy
At Thu, 12 Feb 2009 23:36:19 +,
Edsko de Vries wrote:
>
> Hi,
>
> I can desugar
>
> do x' <- x
> f x'
>
> as
>
> x >>= \x -> f x'
>
> which is clearly the same as
>
> x >>= f
>
> However, now consider
>
> do x' <- x
Hi Miguel,
That's a nice way of writing it.
Thanks,
-John
On Fri, Feb 13, 2009 at 10:42 AM, Miguel Mitrofanov
wrote:
> What do you need that for?
>
> Can you live with
>
> infixl |$|
> (|$|) :: [a -> r] -> a -> [r]
> fs |$| x = map ($ x) fs
>
> and, instead of "broadcast fs a b" use
>
> fs |$|
On Fri, 2009-02-13 at 10:34 +1100, John Ky wrote:
> Hi Haskell Cafe,
>
> I tried using type families over functions, but when I try it
> complains that the two lines marked conflict with each other.
>
> class Broadcast a where
>type Return a
>broadcast :: a -> Return a
> instance Broadca
What do you need that for?
Can you live with
infixl |$|
(|$|) :: [a -> r] -> a -> [r]
fs |$| x = map ($ x) fs
and, instead of "broadcast fs a b" use
fs |$| a |$| b
?
On 13 Feb 2009, at 02:34, John Ky wrote:
Hi Haskell Cafe,
I tried using type families over functions, but when I try it
c
Check out liftM2. It's almost what you want.
On Thu, Feb 12, 2009 at 6:36 PM, Edsko de Vries wrote:
> Hi,
>
> I can desugar
>
> do x' <- x
> f x'
>
> as
>
> x >>= \x -> f x'
>
> which is clearly the same as
>
> x >>= f
>
> However, now consider
>
> do x' <- x
> y' <- y
> f x' y'
Hi,
I can desugar
do x' <- x
f x'
as
x >>= \x -> f x'
which is clearly the same as
x >>= f
However, now consider
do x' <- x
y' <- y
f x' y'
desugared, this is
x >>= \x -> y >>= \y' -> f x' y'
I can simplify the second half to
x >>= \x -> y >>= f x'
but now w
Hi Haskell Cafe,
I tried using type families over functions, but when I try it complains that
the two lines marked conflict with each other.
class Broadcast a where
type Return a
broadcast :: a -> Return a
instance Broadcast [a -> r] where
type Return [a -> r] = a -> [r] -- Conflict!
bugfact:
> Consider the following code
>
> stamp v x = do
> t <- getCurrentTime
> putMVar v (x,t)
>
> Is it possible - with GHC - that a thread switch happens after the t <-
> getCurrentTime and the putMVar v (x,t)?
Yes. if 't' is heap allocated, there could be a context switch.
> If so
On Mon, 9 Feb 2009, Edsko de Vries wrote:
Hi,
Is there a nice way to write
down :: Focus -> [Focus]
down p = concat [downPar p, downNew p, downTrans p]
down = concat . sequence [downPar, downNew, downTrans]
given the Reader like Monad instance of ((->) a).
_
One clarification. That is, I could write map with the cNull/cCons
implementation already suggested, but I couldn't do:
instance Chunkable Data.StorableVector.Vector el where
...
cMap = Data.StorableVector.map
which is what I really want.
However, I just realized that I should be able to us
Consider the following code
stamp v x = do
t <- getCurrentTime
putMVar v (x,t)
Is it possible - with GHC - that a thread switch happens after the t <-
getCurrentTime and the putMVar v (x,t)?
If so, how would it be possible to make sure that the operation of reading
the current time and writin
Hi Job, thanks for replying.
Thanks for explaining this. I never really thought about the
implications of kinds on type classes, and it's all much more clear
now.
The first version, with only one parameter, almost works, except that
some instances (e.g. uvector, storablevector) have further clas
Notably, extensible exceptions use dynamics, in conjunction with type
classes and existentials.
A number of solutions to the 'expression problem' involve dynamics.
bugfact:
> It would be interesting to see when you HAVE to use dynamics, e.g. when no
> other solution is possible in Haskell...
>
>
It would be interesting to see when you HAVE to use dynamics, e.g. when no
other solution is possible in Haskell...
Right now if I use it, it feels that I'm doing so because I'm too new to
Haskell.
On Thu, Feb 12, 2009 at 7:53 PM, Lennart Augustsson
wrote:
> You're quite right. You should only
Matthew Elder wrote:
> would love to see this.
>
> basic features first i suppose. here are some of my ideas:
>
> 1. browseable change history with preview pane (preview pane shows
> diff and patch message)
Extending this idea, I'd like to see some "3D" visualization of the file
hierarchy and t
You're quite right. You should only be allowed to derive Typeable.
(Which could be arranged by hiding the methods of typeable.)
On Thu, Feb 12, 2009 at 6:24 PM, Jonathan Cast
wrote:
> On Thu, 2009-02-12 at 19:04 +0100, Lennart Augustsson wrote:
>> They are not unsafe in the way unsafePerformIO i
On Thu, 2009-02-12 at 19:04 +0100, Lennart Augustsson wrote:
> They are not unsafe in the way unsafePerformIO is,
I beg permission to demur:
newtype Unsafe alpha = Unsafe { unUnsafe :: alpha }
instance Typeable (Unsafe alpha) where
typeOf _ = typeOf ()
pseudoSafeCoerce :: alpha -> Mayb
On Thu, 12 Feb 2009, Achim Schneider wrote:
Jamie wrote:
For Theora playback we've found that the largest CPU load comes from
colorspace conversion, where the YUV output of the codec needs to be
converted to RGB for some targets (like Firefox). That is some
fairly straightforward array proc
fgl uses pretty much the most beautiful way of abstracting graphs I've seen;
a brief review:
type Context a b -- a collected representation of a vertex's number, label,
and all information on edges going into and out of that vertex
match :: Graph gr => Node -> gr a b -> (Maybe (Context a b), gr a
They are not unsafe in the way unsafePerformIO is, but I regard them
as a last resort in certain situations.
Still, in those situations they are very useful.
-- Lennart
2009/2/12 Peter Verswyvelen :
> Haskell seems to have pretty strong support for dynamic casting using
> Data.Typeable and Data
Peter Verswyvelen wrote:
> Haskell seems to have pretty strong support for dynamic casting using
> Data.Typeable and Data.Dynamic.
> All kinds of funky dynamic programming seems to be possible with these
> "hacks".
>
> Is this considered as being as bad as - say - unsafePerformIO? What
> kind of
bugfact:
> Haskell seems to have pretty strong support for dynamic casting using
> Data.Typeable and Data.Dynamic.
>
> All kinds of funky dynamic programming seems to be possible with these
> "hacks".
>
> Is this considered as being as bad as - say - unsafePerformIO? What kind of
> evil is lurki
Haskell seems to have pretty strong support for dynamic casting using
Data.Typeable and Data.Dynamic.
All kinds of funky dynamic programming seems to be possible with these
"hacks".
Is this considered as being as bad as - say - unsafePerformIO? What kind of
evil is lurking here?
Cheers,
Peter
___
gwern0:
> On Thu, Feb 12, 2009 at 11:49 AM, John Lato wrote:
> > Johan Tibell wrote:
> >> On Thu, Feb 12, 2009 at 2:12 AM, Felipe Lessa
> >> wrote:
> >>> Do we already have enough information to turn
> >>> http://okmij.org/ftp/Haskell/Iteratee/ into a nice, generic, cabalized
> >>> package? I th
On Thu, Feb 12, 2009 at 11:49 AM, John Lato wrote:
> Johan Tibell wrote:
>> On Thu, Feb 12, 2009 at 2:12 AM, Felipe Lessa wrote:
>>> Do we already have enough information to turn
>>> http://okmij.org/ftp/Haskell/Iteratee/ into a nice, generic, cabalized
>>> package? I think Iteratees may prove th
Hi,
I'm experimenting with delimited continuations in the effort to
understand how they work and when it's convenient to use them.
Consider this piece of code (install the CC-delcont before running it):
{-# LANGUAGE NoMonomorphismRestriction #-}
import Control.Monad.CC
import Control.Monad
On Thu, Feb 12, 2009 at 4:12 AM, Duncan Coutts
wrote:
> As Wolfgang mentioned, you may choose to follow the common package
> versioning policy.
>
> http://haskell.org/haskellwiki/Package_versioning_policy
>
> We are planning to develop tool support for this. To let packages
> explicitly opt-in and
Johan Tibell wrote:
> On Thu, Feb 12, 2009 at 2:12 AM, Felipe Lessa wrote:
>> Do we already have enough information to turn
>> http://okmij.org/ftp/Haskell/Iteratee/ into a nice, generic, cabalized
>> package? I think Iteratees may prove themselves as useful as
>> ByteStrings.
>
> I still haven't
Daniel Kraft schrieb:
Benedikt Huber wrote:
I would also like to see a project working on a new graph library.
Currently, there is at least Data.Graph (just one Module, package
containers), based on Array - adjacency lists, and the functional
graph library (package fgl).
I don't know those,
gtener:
> On Thu, Feb 12, 2009 at 11:36, Malcolm Wallace
> wrote:
> > Gwern Branwen wrote:
> >
> >> * A GUI interface to Darcs
> >> (http://hackage.haskell.org/trac/summer-of-code/ticket/17);
> >
> > I wonder whether darcs ought to apply to be a GSoC mentoring
> > organisation in its own right th
Malcolm.Wallace:
> Gwern Branwen wrote:
>
> > * A GUI interface to Darcs
> > (http://hackage.haskell.org/trac/summer-of-code/ticket/17);
>
> I wonder whether darcs ought to apply to be a GSoC mentoring
> organisation in its own right this year? It would be good to attempt to
> get a couple of d
Benedikt Huber wrote:
I would also like to see a project working on a new graph library.
Currently, there is at least Data.Graph (just one Module, package
containers), based on Array - adjacency lists, and the functional graph
library (package fgl).
I don't know those, but "functional graph l
Benedikt writes:
> I think a good general purpose graph library is tricky though:
> - There are lot of variants of graphs (trees, bipartite, acyclic,
> undirected, simple, edge labeled etc.), hard to find adequate and easy to
> use abstraction.
> - There is no single 'best' implementation (mutable
Am Donnerstag, 12. Februar 2009 15:34 schrieb Thomas DuBuisson:
> Daniel Kraft asked:
> > That sounds interesting... What do you mean by "no canonical" library?
> > Are there already ones but just no "standard" one? But in this case, I
> > don't think adding yet another one will help :D Or isn'
Am Donnerstag, 12. Februar 2009 10:49 schrieb Luke Palmer:
> Something like AnnoCPAN would be a good middle-ground here; i.e.
> differentiate between "official" package documentation and user
> annotations, but make them both visible.
And give visitors of the Hackage website the choice to not see
Am Donnerstag, 12. Februar 2009 09:15 schrieben Sie:
> g9ks157k:
> > Am Mittwoch, 11. Februar 2009 18:51 schrieb Don Stewart:
> > > For example, if all the haddocks on hackage.org were a wiki, and
> > > interlinked, every single package author would benefit, as would all
> > > users.
> >
> > You me
Benedikt Huber writes:
> I would also like to see a project working on a new graph library.
[...]
> I think a good general purpose graph library is tricky though:
And please, let us have a library that is scalable! This means there
should be one (or several) benchmark application(s) that do
n
Call for participation:
~~
The 5th Haskell Hackathon
April 17 - 19, 2009
Utrecht, The Netherlands
Daniel Kraft schrieb:
Don Stewart wrote:
- Graphs.
True graphs (the data structure) are still a weak point! There's no
canonical graph library for Haskell.
That sounds interesting... What do you mean by "no canonical" library?
Are there already ones but just no "standard" one? But in th
Daniel Kraft wrote:
> Don Stewart wrote:
> >> - Graphs.
> >>
> > True graphs (the data structure) are still a weak point! There's no
> > canonical graph library for Haskell.
>
> That sounds interesting... What do you mean by "no canonical"
> library? Are there already ones but just no "standar
Daniel Kraft asked:
> That sounds interesting... What do you mean by "no canonical" library? Are
> there already ones but just no "standard" one? But in this case, I don't
> think adding yet another one will help :D Or isn't there a "real" general
> graph library?
My impression is that there is
Jamie wrote:
>
> On Thu, 12 Feb 2009, Conrad Parker wrote:
>
> > 2009/2/12 Don Stewart :
> >> Thanks for the analysis, this clarifies things greatly.
> >> Feasibility and scope is a big part of how we determine what
> >> projects to work on.
> >
> > I agree that it's beyond the scope of a SoC p
TASE 2009 - Final CALL FOR PAPERS
**
* 3rd IEEE International Symposium on
* Theoretical Aspects of Software Engineering
* (TASE 2009)
* 29-31 July 2009, Tianjin, China
* http://www.dur.ac.uk/ieee.tase2009
*
* For more information email: ieee.tase2...@durham
Don Stewart wrote:
- Graphs.
True graphs (the data structure) are still a weak point! There's no
canonical graph library for Haskell.
That sounds interesting... What do you mean by "no canonical" library?
Are there already ones but just no "standard" one? But in this case,
I don't think
Hi all,
I'm trying to parse some XML files using HXT. However, even the examples
available on the twiki fail. I guess that the problem is related to some
library version, but I'm not sure.
The error reported is: "Segmentation fault".
Thanks in advance.
Compiling with GHC-6.8.3 running on MAC
> > without removing all all setLevel calls to subloggers?
> > Is this desirable?
>
> I don't understand the problem. If you told hslogger that you didn't
> want to hear about stuff about "A", why do you not like that it is
> following your instructions?
Because taht >>don't want to hear abuot "
> Check out what GHC is doing these days, and come back with an analysis
> of what still needs to be improved. We can't wait to hear!
can you point me to any haskell code that is as fast as it's C
equivalent?
You should do your own benchmarking!
Please, folks! This is hardly helpful.
It isn't
On Thu, 12 Feb 2009, Conrad Parker wrote:
2009/2/12 Don Stewart :
Thanks for the analysis, this clarifies things greatly.
Feasibility and scope is a big part of how we determine what projects to
work on.
I agree that it's beyond the scope of a SoC project.
Rather than H.263 or H.264 I was g
On Tue, 2009-02-10 at 12:39 +0100, Henning Thielemann wrote:
> Heinrich Apfelmus schrieb:
> > Henning Thielemann wrote:
> >> I want for long to write math formulas in a paper in Haskell. Actually,
> >> lhs2TeX can do such transformations but it is quite limited in handling
> >> of parentheses and d
On Wed, 2009-02-11 at 14:02 -0800, Corey O'Connor wrote:
> On Wed, Feb 11, 2009 at 2:48 AM, Duncan Coutts
> wrote:
> > On Tue, 2009-02-10 at 10:21 -0800, Corey O'Connor wrote:
> >> I released a new version of data-spacepart that resolved some of the
> >> issues with the previous release. One issue
On Thu, Feb 12, 2009 at 11:36, Malcolm Wallace
wrote:
> Gwern Branwen wrote:
>
>> * A GUI interface to Darcs
>> (http://hackage.haskell.org/trac/summer-of-code/ticket/17);
>
> I wonder whether darcs ought to apply to be a GSoC mentoring
> organisation in its own right this year? It would be good
On Thu, 2009-02-12 at 10:11 +0100, Christian Maeder wrote:
> Duncan Coutts wrote:
> > On Wed, 2009-02-11 at 15:49 +0100, Lennart Augustsson wrote:
> >> Does this version work from ghci?
> >>
> >> -- Lennart
> >
> > Specifically I believe Lennart is asking about Windows. It's worked in
> > ghci i
0.10.0 works on Windows for me even when using GHCi. Great work, I love it.
On Thu, Feb 12, 2009 at 1:11 AM, Duncan Coutts
wrote:
> On Wed, 2009-02-11 at 15:49 +0100, Lennart Augustsson wrote:
> > Does this version work from ghci?
> >
> > -- Lennart
>
> Specifically I believe Lennart is asking a
On Thu, 2009-02-12 at 11:08 +0100, Heinrich Apfelmus wrote:
> Benja Fallenstein wrote:
> > Kim-Ee Yeoh wrote:
> >>
> >> On the same note, does anyone have ideas for the following snippet? Tried
> >> the
> >> pointfree package but the output was useless.
> >>
> >> pointwise op (x0,y0) (x1,y1) = (x0
Wolfgang Jeltsch wrote:
> Am Donnerstag, 12. Februar 2009 09:20 schrieb Achim Schneider:
> > Wolfgang Jeltsch wrote:
> > > Am Mittwoch, 11. Februar 2009 18:51 schrieb Don Stewart:
> > > > For example, if all the haddocks on hackage.org were a wiki, and
> > > > interlinked, every single package a
2009/2/12 Peter Verswyvelen :
> It is funny that recently I had a strange problem in C# (I tried to write
> parts of Reactive in C#) where the garbage collector freed data that was
> actually needed by my program! I had to fix that by putting a local variable
> on the stack, passing the constructed
On Wed, Feb 11, 2009 at 6:41 PM, Achim Schneider wrote:
> ...
> I got curious and made two pages point to each other, resulting in as
> many stale continuations as your left mouse button would permit. While
> the model certainly is cool, I'm not aware of any implementation that
> even comes close
Gwern Branwen wrote:
> * A GUI interface to Darcs
> (http://hackage.haskell.org/trac/summer-of-code/ticket/17);
I wonder whether darcs ought to apply to be a GSoC mentoring
organisation in its own right this year? It would be good to attempt to
get a couple of dedicated slots for darcs only (in
Am Donnerstag, 12. Februar 2009 09:20 schrieb Achim Schneider:
> Wolfgang Jeltsch wrote:
> > Am Mittwoch, 11. Februar 2009 18:51 schrieb Don Stewart:
> > > For example, if all the haddocks on hackage.org were a wiki, and
> > > interlinked, every single package author would benefit, as would all
>
On Thu, Feb 12, 2009 at 10:48 AM, Svein Ove Aas wrote:
> Using this as a guide, I tested these two programs:
>
>
> str = concat $ repeat "foo "
>
> main1 = print foo
> main2 = print foo >> print foo
> =
>
> As I'm sure you realize, the first ran in constant memory; the second,
> not so m
Benja Fallenstein wrote:
> Kim-Ee Yeoh wrote:
>>
>> On the same note, does anyone have ideas for the following snippet? Tried the
>> pointfree package but the output was useless.
>>
>> pointwise op (x0,y0) (x1,y1) = (x0 `op` x1, y0 `op` y1)
>
> import Control.Monad.Reader -- for the (Monad (a ->)
Don Stewart wrote:
>
> No one said anything about unrestricted commit rights ... we're not
> crazy ... what if it were more like, say, RWH's wiki .. where comments
> go to editors to encorporate ...
By the way, the PHP documentation has such a comment feature, see for
example
http://www.php.
> From: haskell-cafe-boun...@haskell.org
> [mailto:haskell-cafe-boun...@haskell.org] On Behalf Of Don Stewart
> >
> > You mean, everyone should be able to mess about with my
> documentation? This
> > would be similar to give everyone commit rights to my
> repositories or allow
> > everyone to
On Thu, Feb 12, 2009 at 2:42 AM, Heinrich Apfelmus <
apfel...@quantentunnel.de> wrote:
> Wolfgang Jeltsch wrote:
> > Don Stewart wrote:
> >> For example, if all the haddocks on hackage.org were a wiki, and
> >> interlinked, every single package author would benefit, as would all
> >> users.
> >
>
On Thu, Feb 12, 2009 at 10:36 AM, Simon Marlow wrote:
> Peter Verswyvelen wrote:
>>
>> Yes, I was really surprised that this was the case. I while ago I did a
>> little FRP experiment. I made a top level binding to a list of timer event
>> occurrences. The list was generated on another thread. To
Wolfgang Jeltsch wrote:
> Don Stewart wrote:
>> For example, if all the haddocks on hackage.org were a wiki, and
>> interlinked, every single package author would benefit, as would all
>> users.
>
> You mean, everyone should be able to mess about with my documentation? This
> would be similar to
Friends
Writing papers is fun, we mostly only get to write one *kind* of paper. Here
is an opportunity to write something in a totally different style:
Submit an essay to Onward! Essays
Deadline: 20 April 2009
http://onward-conference.org/calls/foressays
An Onward! essa
Peter Verswyvelen wrote:
Yes, I was really surprised that this was the case. I while ago I did a
little FRP experiment. I made a top level binding to a list of timer
event occurrences. The list was generated on another thread. To my
surprise, I did not have space leak, which is amazingly cool,
2009/2/12 Matthew Elder :
> would love to see this.
>
> basic features first i suppose. here are some of my ideas:
meld-like diff view would be great too.
http://meld.sourceforge.net/
--
Felipe.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
ht
Duncan Coutts wrote:
> On Wed, 2009-02-11 at 15:49 +0100, Lennart Augustsson wrote:
>> Does this version work from ghci?
>>
>> -- Lennart
>
> Specifically I believe Lennart is asking about Windows. It's worked in
> ghci in Linux for ages and it worked in ghci in Windows prior to the
> 0.9.13 rel
On Thu, Feb 12, 2009 at 6:46 PM, Kim-Ee Yeoh wrote:
>
> On the same note, does anyone have ideas for the following snippet? Tried the
> pointfree package but the output was useless.
>
> pointwise op (x0,y0) (x1,y1) = (x0 `op` x1, y0 `op` y1)
$ pointfree '(\op (a, b) (c, d) -> (a `op` c, b `op` d)
Wolfgang Jeltsch wrote:
> Am Mittwoch, 11. Februar 2009 18:51 schrieb Don Stewart:
> > For example, if all the haddocks on hackage.org were a wiki, and
> > interlinked, every single package author would benefit, as would all
> > users.
>
> You mean, everyone should be able to mess about with my
On Thu, Feb 12, 2009 at 8:46 AM, Kim-Ee Yeoh wrote:
>
> On the same note, does anyone have ideas for the following snippet? Tried the
> pointfree package but the output was useless.
>
> pointwise op (x0,y0) (x1,y1) = (x0 `op` x1, y0 `op` y1)
import Control.Monad.Reader -- for the (Monad (a ->))
g9ks157k:
> Am Mittwoch, 11. Februar 2009 18:51 schrieb Don Stewart:
> > For example, if all the haddocks on hackage.org were a wiki, and
> > interlinked, every single package author would benefit, as would all
> > users.
>
> You mean, everyone should be able to mess about with my documentation? T
would love to see this.
basic features first i suppose. here are some of my ideas:
1. browseable change history with preview pane (preview pane shows diff and
patch message)
2. darcs send which goes through the usual interactive console but then
prompts with a file save pane where you will save t
John Ky wrote:
> My question is: Is it possible to write a generic doLoop that works
> over arbitrary functions?
>
Yes and no, that is, you can overcome the no.
The following code typechecks, and would run nicely if there was a
fixed version of reactive, by now[1]. Event handlers can take one
ar
Am Mittwoch, 11. Februar 2009 18:51 schrieb Don Stewart:
> For example, if all the haddocks on hackage.org were a wiki, and
> interlinked, every single package author would benefit, as would all
> users.
You mean, everyone should be able to mess about with my documentation? This
would be similar
Am Mittwoch, 11. Februar 2009 23:02 schrieb Corey O'Connor:
> The way I read changes in version numbers for a scheme using the
> format X.Y.Z is:
> * A change in Z indicates bug fixes only
> * A change in Y indicates the interface has changed but not in an
> incompatible way. For instance, maybe
On Sat, Feb 7, 2009 at 11:18 AM, Paul Johnson wrote:
> Paul Johnson wrote:
>
>> A call has gone out <
>> http://www.haskell.org/pipermail/haskell-cafe/2008-December/051836.html>
>> for a new logo for Haskell. Candidates (including a couple <
>> http://www.haskell.org/haskellwiki/Image:Haskell-lo
100 matches
Mail list logo