This package [1] provides an implementation of a skip list using STM.
A skip list
is a probabilistic data structure with Data.Map-like operations. In contrast
to a balanced tree, a skip list does not need any (expensive) rebalancing,
which makes it particularly suitable for concurrent programming.
Thank you for the info., I didn't know that it had already been proposed.
The constraint families seem definitely useful.
hugo
On Thu, Nov 25, 2010 at 12:53 PM, Sebastian Fischer wrote:
> On Thu, 2010-11-25 at 10:41 +0900, Hugo Pacheco wrote:
> > Would this be a desired feature for other people?
Hi,
In System.Posix.IOCtl, there is such a class:
class Storable d => IOControl req d | req -> d where
ioctlReqSource :: req -> CInt
How to instance it? I do it as:
data TIOCGWINSZ = TIOCGWINSZ
#starttype struct winsize
#field ws_row , CUShort
#field ws_col , CUShort
#field ws_xpixel , CUShort
On Thu, 2010-11-25 at 10:41 +0900, Hugo Pacheco wrote:
> Would this be a desired feature for other people?
I'd like to have Haskell Type Constraints Unleashed
http://users.ugent.be/~tschrijv/Research/papers/constraint_families.pdf
which includes equality constraint synonyms.
Sebastian
___
A quick review of GHC 7.0.1 revealed two challenges for developers.
I downloaded the GHC 7.0.1 sources, configured for a home directory
install, and built and installed the compiler. Very close to the end,
my machine froze, perhaps due to memory exhaustion. In any event, a
reboot allowed me to c
Dear Haskellers,
When programming with type functions, I often find myself with a set of
invariants that are frequent in my programs and can be expressed as equality
constraints on the context of the functions.
I wonder if there is any way in current GHC to express some kind of synonyms
for equal
Hi!
Why is there no Eq instance for Chan? There is Eq for MVar so it is
quite possible to define also Eq for Chan?
What I would like to do is keep track how many consumers I have for
each Chan so duplicating them with dupChan as necessary. So I was
thinking of storing a list of Chans which alread
On Wednesday 24 November 2010 21:46:22, Gregory Propf wrote:
> I have a pretty basic question. I've been wondering about whether
> monadic functions that do NOT us IO can be pure or not. There seems to
> be some confusion on this topic on the web. I'm especially interested
> in whether they can
Generally speaking, all Haskell functions are pure unless they use unsafe-
functions or FFI inside.
Отправлено с iPhone
Nov 24, 2010, в 23:46, Gregory Propf написал(а):
> I have a pretty basic question. I've been wondering about whether monadic
> functions that do NOT us IO can be pure or no
I have a pretty basic question. I've been wondering about whether monadic
functions that do NOT us IO can be pure or not. There seems to be some
confusion on this topic on the web. I'm especially interested in whether they
can be memoized. It seems to me that something like a function in the
On Wed, Nov 24, 2010 at 7:08 PM, Antoine Latter wrote:
> I meant that 'pop' and 'push' should have been written with 'modify', 'get',
> and 'set' instead of the raw constructor, not as a drop-in replacement.
Indeed, you can also use the 'state' function instead of the 'State'
constructor in your
I meant that 'pop' and 'push' should have been written with 'modify', 'get',
and 'set' instead of the raw constructor, not as a drop-in replacement.
I can show you examples later if this isn't clear, unless I'm not
understanding your code above.
Antoine
On Nov 24, 2010 10:46 AM, "Adam Miezianko"
On 11/24/2010 03:14, jean-christophe mincke wrote:
> Hello,
>
> I am still playing with template-haskell...
>
> I wonder, is there any reason why a quasiquoter cannot create haskell
> statements and declarations in addition to expressions and patterns? Or
> more generally create any legal Haskell
On Tue, Nov 23, 2010 at 6:58 PM, Adam Miezianko wrote:
> I'm working through Learn You a Haskell for Great Good [1] and getting
> a compiler error while playing around with some of the code. I have
> this:
>
> -- BEGIN state.hs
> import Control.Monad.State
>
> type Stack = [Int]
>
> pop :: State
On Tue, Nov 23, 2010 at 7:58 PM, Adam Miezianko wrote:
> I'm working through Learn You a Haskell for Great Good [1] and getting
> a compiler error while playing around with some of the code. I have
> this:
> Now, I'm not exactly sure how to read the documentation for
> Control.Monad.State [2] but
Hello,
I am still playing with template-haskell...
I wonder, is there any reason why a quasiquoter cannot create haskell
statements and declarations in addition to expressions and patterns? Or more
generally create any legal Haskell syntax tree.
I.e Suppose I would like to create a quasiquoter f
Bryan O'Sullivan and I are hosting a SF Bay Area Haskell Hackathon at the
Hacker Dojo in Mountain View, California.
Details are all sketchy at this point, but we plan on two components:
1) Haskell Project Hackathon
2) Learn Haskell Workshop
See:
http://wiki.hackerdojo.com/w/page/Haskell-
I am pleased to announce version 2999.11.0.0 of graphviz [1], my
Haskell bindings to the Graphviz suite of graph visualisation tools
[2].
[1]: http://hackage.haskell.org/package/graphviz
[2]: http://graphviz.org/
This release is mostly backwards-compatible (unless you dealt directly
with Point an
I'm working through Learn You a Haskell for Great Good [1] and getting
a compiler error while playing around with some of the code. I have
this:
-- BEGIN state.hs
import Control.Monad.State
type Stack = [Int]
pop :: State Stack Int
pop = State $ \(x:xs) -> (x,xs)
push :: Int -> State Stack ()
I don't know what this tuple is representing, but if you want to group you'll
have to specify on 'what':
- the tuple,
- the fst or
- the snd
Here's a possibility with grouping on the fst
import Data.List
import Data.Ord
import Data.Function
groupAtoms ::
(Float -> Bool)
-> [(Float,Integer)
Hello,
I am still playing with template-haskell...
I wonder, is there any reason why a quasiquoter cannot create haskell
statements and declarations in addition to expressions and patterns? Or more
generally create any legal Haskell syntax tree.
I.e Suppose I would like to create a quasiquoter f
Well, you can resort to functional dependencies, I guess...
{-# LANGUAGE FlexibleInstances, FunctionalDependencies, MultiParamTypeClasses,
UndecidableInstances #-}
module FunDeps where
data Rec a r = Rec a r
data RecNil = RecNil
data Wrapper a = Wrapper a
class Wrapped r w | r -> w where i :: r
I am pleased to announce the 0.7.0.0 release of my graph-theoretic
source code analysis tool SourceGraph [1], and the library it uses
Graphalyze 0.11.0.0 [2].
[1]: http://hackage.haskell.org/package/SourceGraph
[2]: http://hackage.haskell.org/package/Graphalyze
Changes in SourceGraph (apart from
Hello everybody,
(second try, since the first mail somehow didn't arrive)
I've just uploaded a caching DNS resolver library, which also includes a
command line utility for quick mass DNS resolution:
http://hackage.haskell.org/package/dnscache
Although I've tested it throroughly it's still in
Hello everybody,
I've just uploaded a caching DNS resolver library, which also includes a
command line utility for quick mass DNS resolution:
http://hackage.haskell.org/package/dnscache
Although I've tested it throroughly it's still in beta phase. Feel free
to play around with it. Feedback i
25 matches
Mail list logo