On Thu, Feb 11, 2010 at 1:49 PM, John Van Enk wrote:
> Perhaps just defining the interface and demonstrating that different RTS's
> are swappable would be enough?
I read a paper by (I think) a Simon, in which he described a haskell
RTS. It would make it easier to experiment with GC, scheduling,
>> Finally, it is the array subscript operator:
>>
>> let x = arr ! 10
>
> Shouldn't this be
>
> let x = arr !! 10
!! is the list subscript. Look in Data.Array.IArray for (!). Or Data.Map.
There's still no consensus on typeclasses for collections, so these
are all separate functions. Has anyon
On Sun, Feb 14, 2010 at 2:22 PM, Stephen Tetley
wrote:
> On 14 February 2010 22:11, Evan Laforge wrote:
>
>> There's still no consensus on typeclasses for collections, so these
>> are all separate functions. Has anyone taken a shot at a set of
>> AT-using classes
> I'm no fan of (!!) on lists or other containers where it isn't O(1),
> but lookup/member are a bit more promising. However are there any
> useful derived operations or constructions that can be defined only in
> terms of a Lookup type class? For comparison, Monoid has mconcat as a
> derived op an
By purest coincidence I just wrote the exact same function (the simple
mergeAll', not the VIP one). Well, extensionally the same...
intensionally mine is 32 complicated lines and equivalent to the 3
line mergeAll'. I even thought of short solution by thinking that
pulling the first element destro
BTW, I notice that your merges, like mine, are left-biased. This is a
useful property (my callers require it), and doesn't seem to cost
anything to implement, so maybe you could commit to it in the
documentation?
By left-biased I mean that when elements compare equal, pick the
leftmost one, e.g.
On Thu, Feb 18, 2010 at 5:22 PM, Leon Smith wrote:
> On Thu, Feb 18, 2010 at 3:07 AM, Evan Laforge wrote:
>> BTW, I notice that your merges, like mine, are left-biased. This is a
>> useful property (my callers require it), and doesn't seem to cost
>> anything to imp
On Wed, Feb 24, 2010 at 3:10 PM, Ivan Miljenovic
wrote:
> On 24 February 2010 20:17, Magnus Therning wrote:
>> I often find that I do want an export list to reduce clutter in the
>> finished code, but for testing I'd like to expose everything in a
>> module. Is there a nice way to deal with this
> real :: Parser String
> real = do
> d <- decimal
> f <- option "" $ do
> p <- char '.'
> n <- many1 digit
> return $ p : n
Just to throw two bits in here, this is the only style that doesn't
require leaning on the space bar and squinting to line things up,
doesn't require any fancy ed
> The difference (in work) between map Wrapped and conv is the difference
> between map id and id :: [a] -> [a]. In the absence of any fusion/rewrite
> rules, the former breaks down a list, and builds up a new one with exactly the
> same elements (or, every element x becomes an id x thunk, perhaps)
This may not be helpful for you, but when I did GUI stuff with haskell
I wrote the GUI part in c++ with fltk, exposed a medium-level api
specific to that gui, and then call that api through the FFI. This is
sort of like the web browser + backend thing, except switch c++ and
fltk for javascript and
On Thu, Apr 1, 2010 at 1:46 PM, Luke Palmer wrote:
> Hi,
>
> I'd like to draw attention to a little script I wrote. I tend to use
> qualified imports and short names like "new" and "filter". This makes
> hasktags pretty much useless, since it basically just guesses which
> one to go to. hothask
Ohh, and the other issue I had was that setting iskeyword causes 'w'
to skip over '.'s. This causes trouble for me because I'm used to
using 'w' to skip between components of the symbol and 'W' to skip it
entirely. Is there a workaround you use, maybe a better way to
navigate?
___
> 3) Configuration
>
> I haven't looked at this yet but I suspect people will not want
> another configuration file in their projects. Perhaps you could
> propose some kind of Cabal integration instead.
It would be a shame if I had to figure out how to write a cabal file
for my project and replace
On Tue, May 4, 2010 at 1:23 PM, David Waern wrote:
> 2010/5/4 Sean Leather :
>> Somewhat OT, but is there a place where we can request/review features in
>> the new HTML presentation of Haddock. Are there any mockups of what the
>> pages might look like? I've had some ideas pop around my head ever
> On the one hand, this is doable with the GHC API. On the other, that more
> or less means your program contains what amounts to a full copy of GHC.
And the result is that your binary will grow by 35mb, add a few
seconds to launch time, the first expression will take 3 or 4 seconds
to evaluate,
> I wonder: Of cases where overload resolution via available instances
> would be reasonable, how many would also make sense as a closed type
> class? By comparison, it seems that many uses of OverlappingInstances
> are really just trying to express a closed type class with one or more
> default in
> Hi Evan, hasn't EHC had something like this for a while with 'type
> class directives'?
I dunno, I don't even know what ehc is. Is it this?
http://www.cs.uu.nl/wiki/Ehc/WebHome
I turned up a paper that mentioned type class directives, but I
haven't read it yet. In any case, the EHC page says
> So, sadly, I think your chances of shipping your a title written in Haskell
> on the iPhone are shot to hell.
+1 for the android version.
Disclaimer: biased google employee
:P
Unfortunately then you get another cockamamie restriction in the whole
JVM vs. tail calls thing... but if you can ge
> [1] By co I mean Ruby, Python, Perl and others. There are no so many
> languages that do recognize the difference.
% python -Q new
Python 2.4.6 (#1, Aug 3 2009, 17:05:16)
[GCC 4.0.1 (Apple Inc. build 5490)] on darwin
Type "help", "copyright", "credits" or "license" for more information.
10 / 3
On Thu, Jun 3, 2010 at 3:05 PM, Don Stewart wrote:
> wasserman.louis:
>> What, if anything, stands in the way of parallelizing Cabal installs, make -j
>> style?
>
> Parallelizing ghc --make
>
> http://vimeo.com/6572966
Something I wondered from watching that talk, rather than trying to
make gh
> How should I work around that. I could use two different "name" function, but
> I don't like this. Would I have to define a typeclass "namedFunction" which
> all have a "name" function?
How about a "named" type:
data Named a = Named {
val_of :: a,
name_of :: String
}
You can put it in Fu
>> So how does one get off haskell? Are there people in similar situations
>> that have managed? How did you do it?
I used to get annoyed about all the java boilerplate and awkwardness.
But then I learned that if I relax and stop thinking so much about the
aesthetics of what I'm writing, I can jus
I have a parameterized data type:
> data Val result = VNum Double | VThunk (SomeMonad result)
> type Environ result = Map Symbol (Val result)
I have a class to make it easier to typecheck Vals:
> class Typecheck a where
> from_val :: Val result -> Maybe a
>
> instance Typecheck Double where
>
> I think your problem here is that there's no mention of `a' on the
> left-hand size of from_val's type signature; you either need to use
> MPTC+fundep to associate what result is compared to a, or else use a
> phantom type parameter of Val to make it "data Val result a = ..." and
> then "from_val
> I'm interested in situations where you think fundeps work and type families
> don't. Reason: no one knows how to make fundeps work cleanly with local type
> constraints (such as GADTs).
>
> If you think you have such as case, do send me a test case.
Well, from looking at the documentation, it
Record punning is not all that useful with qualified module names. If
I write '(M.Record { M.rec_x })' it says " Qualified variable in
pattern" and if I write '(M.Record { rec_x })' it says 'Not in scope:
`rec_x''. Could it be this extension be further extended slightly so
that 'f (M.Record { M.r
On Fri, Jul 24, 2009 at 4:48 PM, Iavor Diatchki wrote:
> Hello,
> I think that Even refers to an example like this:
...
Yeah, that's exactly what I meant, sorry if it wasn't clear initially.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://w
One issue I have which I haven't seen anyone mention is that it's not
useful with qualified names, by which I mean always importing
qualified. Of course if you have no problem always using qualified
names, the problem this extension is solving doesn't exist. Though I
do like short names I'm not t
> | Even is suggesting that instead of reporting an error, in the second
> | case we could use the translation:
> |
> | f (A.A { A.a }) = a --> f (A.A { A.a = a })
> |
> | (i.e., when punning occurs with a qualified name, use just the
> | unqualified part of the name in the pattern)
>
> Yes,
Is there any particular reason to not move the instance to the
prelude? A module was failing when imported from one place and ok
when imported from another, so I spent a frustrating 10 minutes
searching for the instance. I couldn't find a way to search haddock
for instances (not even grep on the
On Fri, Sep 11, 2009 at 6:10 AM, Edward Kmett wrote:
> Unfortunately, the instance of Monad for Either a is somewhat misguided in
> Haskell.
>
> There is a spurious restraint that the Left value in your Either be a member
> of some Error class, which was brought about by the deletion of MonadZero
> if I understand you correctly, all libraries that software I write depends
> on, directly or indirectly, must be free of namespace conflicts. Is that
> correct?
Well, it may be more accurate to say that class instances have no
namespaces, and are all implicitly global. When you import a module
> Reaktor has a few limitations though.
>
> 1. It's virtually impossible to debug the thing! (I.e., if your synth
> doesn't work... good luck working out why.)
>
> 2. It lacks looping capabilities. For example, you cannot build a
> variable-size convolution block - only a fixed-size one. (If you wa
> Indeed, you can write certain DSP algorithms beautifully in Haskell.
> Now, if only it could talk to the audio hardware... (Or just use common
> file formats even.)
Oh, that's easy. I wrote an FFI interface to portaudio a while back
to write a delay-looping type utility in haskell. It was pret
> Let's ignore System.Time since it's obsoleted by Data.Time.
While you're updating the Data.Time docs, could you mention the above
in System.Time? I recently looked at both and used System.Time
because Data.Time looked too complicated.
___
Haskell-Cafe
> > "frees the programmer from writing superfluous type signatures" is a
> > weak (and dubious) advantage. I very often write "superfluous" type
> > signatures first (to be sure I know what I'm asking my program to do)
> > and only then let Haskell check it. Then I leave it in as good
> > documenta
> it seems that script may be not terminated if its output isn't read, so
> better code should be
>
> (_, h, g, _) <- runInteractiveCommand "script params"
> result <- hGetLine h
> hGetContents h >>= evaluate.length
> hGetContents g >>= evaluate.length
Tangent here, but does anyone else think that
> A newtype can only have one constructor, with one argument, and is
> essentially a wrapper for that argument type.
>
> In the general case, you want to use "data" instead of "newtype":
>
> data Rectangle = R Int Int
I'm sure there's a trivial explanation for this, but here's something
that I'v
> I'm sure there's a trivial explanation for this, but here's something
> that I've always kind of wondered about: Given a single constructor
> type like "data X = X A B C" can't that be transformed into "newtype X
> = X (A, B, C)"? There must be some difference, because if there
> weren't we cou
> I interpreted Evan's question as "why can't you have newtypes with
> multiple fields?" -- i.e., newtype X = X A B C -- and that's the
> question I was answering. But maybe I misunderstood.
Well, the question was both, and "strictness" answers both. Thanks
for the clarification. I should have r
> Would not it be interesting and useful (but not really efficient) to
> have patterns something like:
>
> foo :: Eq a => a -> ...
> foo (_{4}'b') = ...
>
> which would match a list with four elements ending with an element 'b'. Or:
>
> foo (_+';'_+';'_) = ...
Maybe you could use view patterns?
f
> > Parser combinators basically provide generalized regexes, and they all
> > take lists of arbitrary tokens rather than just Chars. I've written a
> > simple combinator library before that dispenses with all the monadic
> > goodness in favor of a group combinator and returning [Either [tok]
> >
> This takes an iterator over some collection of Foos and finds the one
> with the highest value of updateTime. 9 lines of code, or 12 with the
> closing curly brackets.
>
> In Haskell this is so short and obvious you probably wouldn't bother
> declaring it as a function, but if you did, here it i
> > A real time incremental gc would be really cool. Some people claim
> > they exist, but which languages have one?
>
> Define "real time". I'll note that, after all the mud that's been
> slung at Java, you've been able to get low-pause-time parallel GC in
> Java for years and years, and can get
> PS: I would love to see an immutable filesystem that does not allow writing
> to files, it only creates new files and garbage collects files that have no
> incoming reference anymore... Just like a garbage collected heap, and a bit
> like an OLAP databases (as far as I remember my DB theory...
> As I say, every time I've tried to do this, I end up writing a function to
> "run this stuff", and it typically takes a few hours to reach the point
> where it type-checks.
It took me a while the first time, but then I just learned the pattern
and I do it that way every time. Here's my pattern:
On Fri, Jul 16, 2010 at 11:21 AM, Don Stewart wrote:
> Generally, in Erlang or Haskell, the semantics we use is to keep
> all the old code in memory, for the case of closures and thunks that
> point back into that code.
>
> You can imagine a fine-grained semantics where as each top level
> functi
On Mon, Jul 26, 2010 at 12:54 PM, Kevin Jardine wrote:
> On Jul 26, 6:45 pm, Nick Bowler wrote:
>
>> Since when do mailing lists not have threading? Web forums with proper
>> support for threading seem to be few and far apart.
>
> Most of the email clients I'm familiar with don't support threade
> I've always thought that being able to write:
>
>> catMaybes :: [Maybe a] -> [a]
>> catMaybes xs = [ x | Just x <- xs ]
>
> is really cool, which relies on:
>
>> fail _ = []
>
> being in the Monad instance for List.
Really? I thought that's just a feature of list comprehensions. List
comps are
On Tue, Aug 3, 2010 at 3:06 PM, Gregory Crosswhite
wrote:
> But you've got it backwards: if the function I am calling can call back
> into Haskell (i.e., is marked as "safe"), then GHC *doesn't* block the
> world, but if the function I am calling will never call back into Haskell
> (i.e., is mark
>> Just think of "unsafe" in relation to "unsafeIndex" or something.
>> It's faster, but you have to be sure the index is in bounds.
> Yes, but the whole reason to use "unsafe" is to get higher performance
> at the cost of safety. If the result of calling an "unsafe" foreign
> function is that you
This is something I've wanted for a long time, but I always intended
to just submit a patch since it would be trivial, but maybe other
people have an opinion about it too:
I've always wanted a button to collapse or maybe toggle all expanded
branches. Once a library gets large, it's easier to navi
On Fri, Aug 13, 2010 at 6:41 PM, Brandon S Allbery KF8NH
wrote:
> -BEGIN PGP SIGNED MESSAGE-
> Hash: SHA1
>
> On 8/13/10 16:37 , Kevin Jardine wrote:
>> Surely efficient Unicode text should always be the default? And if the
>
> Efficient for what? The most efficient Unicode representation
> It sounds to me like your life would be a lot easier if you knew about
> cabal-install's root-cmd configuration parameter! Open your
> .cabal/config file and uncomment and set:
>
> root-cmd: sudo
I didn't know about this either. As an aside, is the cabal config
file documented at all? I haven'
Is there a data type that's spine lazy like a list, but can be seeked (sought?)
efficiently? IntMap and Sequence are spine strict so if you take the head
element all the elements are forced even if their contents are not. E.g.,
'Sequence.index (Sequence.fromList [0..]) 0' will diverge, but obviou
> However, I haven't thought about how operations such as 'cons' and
> 'tail' would be implemented =). OP just asked about indexing ;-).
Hah, serves me right I suppose. I figured the promise of some type
fanciness would be catnip to some well-typed cats out there, but your
implementation is even
> I wonder... How many people are actually working on Cabal?
>
> When I first started using Haskell, I got the impression that there were
> hundreds, maybe even thousands, of developers working on GHC. (After all,
> how else could you write such a huge codebase in less than two centuries?)
> But no
On Sat, Aug 21, 2010 at 6:52 PM, Michael D. Adams wrote:
> Could you be more specific about what operations you want and their
> properties (e.g. performance laziness, etc.)? For example, do you
> need to be able to cons onto the front or is the list generated once
> and never consed onto? Do yo
On Sat, Aug 28, 2010 at 12:22 PM, Carter Schonwald
wrote:
> i believe that a valid idiom is to define a class C that has no functions,
> but requires any instance to also be of type classes A and B, so that you
> can write: C a => blah
> rather than (A a,B a)=> blah, though I don't know how o
Lately I've been spending more and more time trying to figure out how
to resolve circular import problems. I add some new data type and
suddenly someone has a new dependency and now the modules are
circular. The usual solution is to move the mutually dependent
definitions into the same module, bu
Here's a different approach:
If you just want to make the typechecker distinguish between some
values but still have some functions that don't care what "subtype"
they are, you can use phantom types:
data Obj x = Obj X Y Z
data BlogObj
type Blog = Obj BlogObj
data CommentObj
type Comment = Obj
> Perhaps, this is madness, but I wanted to read other opinions on this topic.
Packages already have multiple tags, right? So how about a search box
that uses ANDed tags (in addition to description etc), and a browsing
interface where you can see tags of packages matching the current
search, and
> Ertugrul's advice is still correct. I'd wager there are very few concurrent
> applications that could survive a killThread without disaster. People simply
> don't write or test code with that in mind, and even when they do, it's more
> likely than not to be wrong.
Does this apply to pure code?
2010/9/16 Alexey Karakulov :
> Hi. I'm writing GUI (gtk) program which purpose is take some data as user
> input, perform some evaluations, and produce some plots and coefficients.
> Since some evaluations take significant time (about 10 seconds), I try to
> cache results. The problem is that depen
[ sorry, forgot reply to all ]
>> simpleComment = do{ string ""))
>> }
>>
>> Note the overlapping parsers anyChar and string "", ...
Yes, I think the doc just made a mistake there. In fact, it looks
like the same mistake is in the current doc at
http://hackage.haskell.org/packa
> data Foo a b
> = Foo a
> | Bar b
> | Foobar a b
> deriving (Eq, Ord)
>
> There, that looks good.
There is a trap if you do a similar thing with records:
data Foo = Foo
{ a :: Int
, b :: Int
}
If you use '-- |' style haddock it can't go on 'a'. Since I tend to
On Mon, Sep 27, 2010 at 2:09 PM, aditya siram wrote:
> How do you guys indent long function arguments? I run into this all
> the time with the 'maybe' function which takes 3 arguments:
> maybe :: b -> (a -> b) -> Maybe a -> b
> I usually end up doing things like (pretend the arguments are aligned
> I'm going to go ahead and offer a contrary viewpoint -- lining up code
> vertically makes it so much easier to read that the extra work involved
I haven't noticed it being easier to read, but I don't like syntax
highlighting either, and lots of people seem to like that too. Taste
is taste.
> (
>> Also, either your pipes don't line up, or you violate your own rule
>
> They line up fine in a fixed width font. Programming in any
> indentation-sensitive language in a proportional font leads inevitably to
> use of tabs to make things line up properly, which leads directly to pain.
I write h
Sorry, forgot to reply to all
> You also sometimes refactor part of a module to another module, and
> then you need to copy over all the necessary imports. I tend to copy
> all my imports over and then remove the ones GHCi tells me aren't
> necessary. So, one solution to make this automatic copy o
-1 for if then. The examples of "curried" if then else look, to my
eyes, less readable than the pointed version. And it's easy enough to
write a 'bool' deconstructor, or an 'ifM' for the monadic case.
+1 for something to solve the "dummy <- m; case dummy of" problem.
Here are the possibilities I
> I would also very much like to have multi-argument pattern matching, but in
>
> \case a b -> ...
> ...
>
> it sure suggests to me that `a` should be applied to `b` before casing.
I feel like sugar is designed to make a couple of specific uses nicer.
Being as general and orthogonal a
I admit I haven't read this whole thread in detail, but when I want
something with an implementation that can vary dynamically I just pass
a different function. Your original python example is equivalent to
just passing strings in haskell, so lets add an argument:
type Process = Int -> String
he
> I think I'm starting too see what my problem is. I think it boils down to
> hankering for Duck Typing and variadic functions. I fully appreciate that
> passing functions is a wonderful and powerful technique for catering for
> variation, but Haskell's type system cramps my style by insisting that
>> How
>> are you expecting to call the functions in that container? "for f in
>> c: try: return f(*misc_args) except: pass"?
>
> to_do = [(call, (AuntMabel,)),
> (buy, ([(12*kg, sugar), (6*bushel, wheat)])),
> (introduce, (Romeo, Juliet))]
>
> for do,it in to_do:
> do(*it)
As
> I don't know of any way to examine this for a running program. You can get
> GHC to spit out core and STG using -ddump-core and -ddump-stg flags:
There's no -ddump-core flag. I was puzzled about the proper way to
get "final" core, and have been using -ddump-simpl, but I don't know
if that's co
> The latter. atomicModifyIORef is harder though still, since it is a
> primop with the same properties as modifyIORef :/
>
>> So would it make sense to create a strict modifyIORef' function?
>
>
> Very much so. In fact, I'd argue the vast majority of uses are for the
> WHNF-strict version.
I just
>> Of course, I'm talking about profiling in time. GHC also enables you
>> to profile in space as well. I'm not actually sure to which one
>> you're referring.
>
> In general, time profiling. Although the space profiling is useful too,
> it gives you hints on what the (lazy) program does, as oppose
I was happy to see the recent announcement about hs-plugins being
updated to work with newer ghc. I have a project and had always been
planning to use it.
However, there are some questions I've had about it for a long time.
The 'yi' paper mentions both 'yi' and 'lambdabot' as users of
hs-plugins.
>> So my questions are:
>>
>> Why did lambdabot and yi abandon plugins?
>
> Because it was unmaintained for around 5 years, and was fundamentally
> less portable than simpler state serialization solutions that offered
> some of the same benefits as full code hot swapping.
Fair enough. The idea of
> Last, i remove pdynload code from my project temporary with below reasons:
>
> 1) Hold running state is difficult, like network state in browser or
> running state in terminal emulator.
This doesn't seem too hard to me. Provided you are not swapping the
module that defines the state in the firs
> Any time you see something "inexplicable" like lots of time being attributed
> to something simple like "get", it means that something isn't strict enough
> and "get" is having to force a bunch of lazy evaluations to do its job.
> Since you're using State.Strict but lift-ing to get there, I'd fir
On Thu, Oct 28, 2010 at 3:05 PM, John Goerzen wrote:
> On 10/27/2010 01:22 PM, Donn Cave wrote:
>>
>> Don't know, but probably challenging enough to make it worth challenging
>> the assumption that Python now has a good email library.
>>
>>> From a cursory look at the 3.0 library documentation, it
> Honestly, I think a big part of this isn't documentation practices so much
> as it is the expression problem. For a lot of the problems I tackle, the OO
> model is not appropriate for capturing program structure. Pairing this with
> Java's requirement of one class per file means that the actual f
> If this is accurate, why would anyone want to use the lazy State?
To answer my own question, if you want a monad stack to produce lazy
output. E.g. if you want to lazily produce data but also have
exceptions and state:
ErrorT e (LazyWriterT w (LazyStateT s Identity))
AFAIK this is the only wa
On Thu, Aug 28, 2008 at 5:02 PM, Neil Mitchell <[EMAIL PROTECTED]> wrote:
> Hi
>
>> Tools like Neil Mitchell's Catch can do more sophisticated checking, as long
>> as your program can be compiled by YHC. Sometimes fromJust can be quite
>> useful, though, especially in tandem with isJust. For exampl
>> systems that don't use an existing user-space thread library (such as
>> Concurrent Haskell or libthread [1]) emulate user-space threads by
>> keeping a pool of processors and re-using them (e.g., IIUC Apache does
>> this).
>
> Your response seems to be yet another argument that processes are to
> All of this works of course because in Haskell, "=" is not an assignment,
> it's a definition, and the RHS is not a variable, it's a pattern. And "4" is
> a perfectly legitimate pattern. Now, if only I could find a use for all this
> that borders on "useful"...! ;-)
I like this one:
let {1 + 1
> In Haskell,
> "The sequence enumFromTo e1 e3 is the list [e1,e1+1,e1+2,...e3].
> The list is empty if e1 > e3."
I like it, since it means that things like [n .. n + length m - 1]
work as expected when m is []. Or say 'map (array!) [bsearch x ..
bsearch y - 1]'.
Tangent: Of course, I would pr
On Wed, Sep 24, 2008 at 2:03 PM, Iain Barnett <[EMAIL PROTECTED]> wrote:
> Hi,
>
> I have a function, that produces a random number between two given numbers
>
> rand :: Int -> Int -> IO Int
> rand low high = getStdRandom (randomR (low,high))
>
>
> (Naively) I'd like to write something like
>
> tak
> As I understand, there are two ways to do that. Either Haskell code is
> called from C, or C code is called for Haskell. So my questions are:
> 1. Are they both possible?
Yep.
> 2. If yes, which is better performance-wise? (C function is
> performance-critical). If generated function is calle
On Wed, Oct 1, 2008 at 3:39 PM, Bill <[EMAIL PROTECTED]> wrote:
> On Wed, 2008-10-01 at 16:46 -0400, John Van Enk wrote:
> . . .
>> I fully realize how un-clever this is. Some one please give me
>> something more worth of the original list. :)
>
> You shoot the gun but nothing happens (Haskell is
Here's what I have in one file:
-- | Parse the text of an event with the given parser @[EMAIL PROTECTED]
parse :: (Monad m) => P.CharParser () a -> String -> Derive.DeriveT m a
parse p text = do
(val, rest) <- case P.parse (p_rest p) "" text of
Left err -> Derive.throw $
"p
This actually brings up something I was wondering about lately. I
recently stumbled across a language called clojure, which is a
lisp-like that runs on the JVM. The interesting thing is that
mutations go through a transactional mutable reference system, and the
other datastructures are all immuta
On Mon, Dec 1, 2008 at 4:39 PM, Andrea Rossato
<[EMAIL PROTECTED]> wrote:
> Hello,
>
> I'm writing the bindings to a C library which uses, in some functions,
> global variables.
>
> To make it clearer, those functions need a global variable to be
> defined. A C program using my_function, one of the
On Mon, Dec 29, 2008 at 1:15 PM, Ryan Ingram wrote:
> Both readTVar and writeTVar are worse than O(1); they have to look up
> the TVar in the transaction log to see if you have made local changes
> to it.
>
> Right now it looks like that operation is O(n) where n is the number
> of TVars accessed
> It's always possible to decompose the final program down into one that
> could be based on locks. But this is often at the cost of
> maintainability; the code becomes one mess of spaghetti locking in
> order to maintain whatever invariants need to be maintained to prevent
> deadlock and compose
> In the short term, yes. But it's my opinion that most anything that's
> a win for ease of modification is a win for performance in the long
> run, if it gets more people writing code.
Also agreed, in theory. The language is definitely also in line with
this philosophy. In practice, though, it
> Although equal? treats the two as the *same*, they're different lists
> because if we modify one (e.g by set-car!) the other won't be affected.
>
> So here comes another question: when we say a function always give the
> same output for the same input, what the *same* means here? ídentity
> or eq
1 - 100 of 367 matches
Mail list logo