I have released data-ordlist 0.2, with a number of changes:
1. The module name is now Data.List.Ordered, instead of Data.OrdList
2. Three bugfixes: (ack!) insertSet and insertBag assumed reverse-ordered
lists, nub failed to remove duplicates. Thanks to Topi Karvonen for
reporting the fir
On Sun, Feb 7, 2010 at 6:43 AM, Ross Paterson wrote:
>
> Why not wrap lists as Set and Bag abstract datatypes? An added bonus
> is that you could make them instances of Monoid.
Well, my current thinking is that if you really want an abstract
datatype for bags and sets, hackage (and the standar
With the urging and assistance of Omar Antolín Camarena, I will be
adding two functions to data-ordlist: mergeAll and unionAll, which
merge (or union) a potentially infinite list of potentially infinite
ordered lists, under the assumption that the heads of the non-empty
lists appear in a non-
> I see no obvious deficiencies. :) Personally, I'd probably structure it like
>
> http://www.haskell.org/haskellwiki/Prime_numbers#Implicit_Heap
This variant, based on the wiki article, is cleaner, slightly
simpler, appears to be just as fast, and allocates slightly less
memory:
> import
On Wed, Feb 17, 2010 at 6:58 AM, Heinrich Apfelmus
wrote:
> Ah, I meant to use the union' from your previous message, but I think
> that doesn't work because it doesn't have the crucial property that the case
>
> union (VIP x xs) ys = ...
>
> does not pattern match on the second argument.
A
On Wed, Feb 17, 2010 at 6:58 AM, Heinrich Apfelmus
wrote:
> Ah, I meant to use the union' from your previous message, but I think
> that doesn't work because it doesn't have the crucial property that the case
>
>union (VIP x xs) ys = ...
>
> does not pattern match on the second argument.
Ah
On Thu, Feb 18, 2010 at 2:32 AM, Evan Laforge wrote:
> 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 sh
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 implement, so maybe you could commit to it in the
> documentation?
Also, I did briefly co
On Sat, Feb 20, 2010 at 5:47 AM, Andrew Coppin
wrote:
> sortOn :: (Ord y) => (x -> y) -> [x] -> [x]
> sortOn foo = sortBy (compare `on` foo)
Incidentally, this function is provided as Data.List.Ordered.sortOn'
in the data-ordlist package...
On Sat, Feb 20, 2010 at 7:39 AM, Ben Millwood wr
Using PostgreSQL on my computer, your code executes in 3.5 seconds
with GHCi, while compiled it executes in 16.2 seconds! Clearly
something is wrong, although I don't yet know enough about Takusen
enough to be able to say what.
I tried hoisting the preparation of the statement out of the loop
As somebody who's hacked on cabal-install a bit (but don't have a
worthwhile patch to contribute (yet?)), I can tell you that versions
support a "tag" structure, at least internally, but I haven't seen a
non-empty tags field and don't know how to make the tags field
non-empty. For that I'd ha
On Sat, Mar 27, 2010 at 1:56 PM, Jason Dagit wrote:
> For some reason it started out as a male dominated field. Let's assume
> for cultural reasons. Once it became a male dominated field, us males
> unknowingly made the work and learning environments somewhat hostile
> or unattractive to women.
On Wed, Mar 31, 2010 at 3:51 PM, Heinrich Apfelmus
wrote:
> which were introduced by John Hughes in his Phd thesis from 1983. They
> are intriguing! Unfortunately, I haven't been able to procure a copy of
> Hughes' thesis, either electronic or in paper. :( Can anyone help? Are
> there any other re
That example doesn't particularly "tie the knot", unless you count
the fact that "break" is itself a recursive function. Usually "tie
the knot" refers to some kind of circular programming, i.e. a
self-referential data structure, or explicit use of Data.Function.fix
to produce a recursive functi
Out of curiousity, I downloaded a binary distribution for GHC-6.12.2,
and tried compressing and recompressing it with bzip2 and lzma
compression, using no command line arguments (all default parameters)
file:
http://haskell.org/ghc/dist/6.12.2/ghc-6.12.2-x86_64-unknown-linux-n.tar.bz2
The fonts aren't rasterized, but PDFs that were converted from PS
tend to look awful in almost any PDF viewer other than Adobe's Acrobat
Reader. Fonts look especially bad.
I don't know exactly what the problem is, but my experience is that
you are best off generating PDF directly, and using Acr
On Thu, Sep 2, 2010 at 1:00 AM, David Powell wrote:
> Thanks Jason, I think I had read that - I quite enjoy Edward's posts.
> Re-reading, seems to confirm what I thought, most (all?) of the FFI calls in
> HDBC-postgresql should be changed to "safe".
Wouldn't that require thread safety on the part
There is a lot of room for improvement to my NumberSieves package.
The package consists of algorithms I extracted and polished up from
when I was working on Project Euler problems. It makes solving a
number of problems into quick five minute affairs. At some point I
would probably do it myself,
I just fixed a fairly serious performance problem with postgresql-libpq's
binding to PQescapeStringConn; in was exhibiting a non-linear slowdown
when more strings are escaped and retained.
https://github.com/lpsmith/postgresql-libpq/commit/adf32ff26cdeca0a12fa59653b49c87198acc9ae
If you are usi
revents multiple DML commands
from being issued in a single request, which would subtly change the
interface postgresql-simple exports.
Best,
Leon
On Mon, Jul 8, 2013 at 10:00 PM, Joey Adams wrote:
> On Mon, Jul 8, 2013 at 9:03 PM, Leon Smith wrote:
>
>> I just fixed a fairly serious per
Out of curiousity, was this a plurality election (vote for one), or an
approval election (vote for many)?
On Tue, May 1, 2012 at 12:11 AM, Kazu Yamamoto wrote:
> Hello,
>
> A twitter election on favorite programming language was held in Japan
> and it appeared that Heskell is No. 10 loved lang
I admit I don't know exactly how MVars are implemented, but given that
they can be aliased and have indefinite extent, I would think that they
look something vaguely like a cdatatype ** var, basically a pointer to an
MVar (which is itself a pointer, modulo some other things such as a thread
q
Let me clarify a bit.
I am familiar with the source of Control.Concurrent.MVar, and I do see {-#
UNPACK #-}'ed MVars around, for example in GHC's IO manager. What I
should have asked is, what does an MVar# look like? This cannot be
inferred from Haskell source; though I suppose I could ha
On Tue, Jul 31, 2012 at 7:37 AM, Bertram Felgenhauer <
bertram.felgenha...@googlemail.com> wrote:
> Note that MVar# itself cannot be unpacked -- the StgMVar record will
> always be a separate heap object.
One could imagine a couple of techniques to unpack the MVar# itself, and
was curious if GH
I see good arguments on both sides of the upper bounds debate, though at
the current time I think the best solution is to omit upper bounds (and I
have done so for most/all of my packages on hackage).But I cannot agree
with this enough:
On Thu, Aug 16, 2012 at 4:45 AM, Joachim Breitner
wrote:
gt; On 8/17/12 11:28 AM, Leon Smith wrote:
>
>> And the
>> difference between reactionary and proactive approaches I think is a
>> potential justification for the "hard" and "soft" upper bounds; perhaps
>> we
>> should instead call them &q
I have some code that reads (infrequently) small amounts of data from
/dev/urandom, and because this is pretty infrequent, I simply open the
handle and close it every time I need some random bytes.
The problem is that I recently discovered that, thanks to buffering within
GHC, I was actually
ers,
> Thomas
>
> On Wed, Nov 28, 2012 at 11:38 AM, Leon Smith
> wrote:
> > I have some code that reads (infrequently) small amounts of data from
> > /dev/urandom, and because this is pretty infrequent, I simply open the
> > handle and close it every time I need some
wrote:
> On 11/28/2012 09:31 PM, Leon Smith wrote:
>
>> Quite possibly, entropy does seem to be a pretty lightweight
>> dependency...
>>
>> Though doesn't recent kernels use rdrand to seed /dev/urandom if it's
>> available? So /dev/urandom is the most p
lt;- peek (castPtr ptr `plusPtr` 8)
return (x,y)
closeRd = closeFd
fdReadAll fd ptr n = do
n' <- fdReadBuf fd ptr n
if n /= n'
then fdReadAll fd (ptr `plusPtr` n') (n - n')
else return ()
main = do
(x,y) <- twoRandomWord64s
S.hP
On Thu, Dec 6, 2012 at 5:23 PM, Brandon Allbery wro\
> Both should be cdevs, not files, so they do not go through the normal
> filesystem I/O pathway in the kernel and should support select()/poll().
> ("ls -l", the first character should be "c" instead of "-" indicating
> character-mode device
I've been toying with some type-level programming ideas I just can't quite
make work, and it seems what I really want is a certain kind of type
unification.
Basically, I'd like to introduce two new kind operators:
kind Set as -- a finite set of ground type terms of kind as
kind Range as = R
It finally occurred to me how to get most of what I want, at least from a
functional perspective.Here's a sample GADT, with four categories of
constructor:
data Foo :: Bool -> Bool -> Bool -> Bool -> * where
A :: Foo True b c d
B :: Foo True b c d
C :: Foo a True c d
D :: Foo
I've been working on a new Haskell interface to the linux kernel's inotify
system, which allows applications to subscribe to and be notified of
filesystem events. An application first issues a system call that returns
a file descriptor that notification events can be read from, and then
issues f
On Fri, May 10, 2013 at 9:00 AM, Andres Löh wrote:
> > This twist is very simple to deal with if you have real existential
> types,
> > with the relevant part of the interface looking approximately like
> >
> > init :: exists a. IO (Inotify a)
> > addWatch :: Inotify a -> FilePath -> IO (Watch a
On Fri, May 10, 2013 at 9:04 AM, MigMit wrote:
> With that kind of interface you don't actually need existential types. Or
> phantom types. You can just keep Inotify inside the Watch, like this:
>
Right, that is an alternative solution, but phantom types are a relatively
simple and well underst
On Fri, May 10, 2013 at 5:49 PM, Alexander Solla wrote:
> I'm not sure if it would work for your case, but have you considered using
> DataKinds instead of phantom types? At least, it seems like it would be
> cheap to try out.
>
>
> http://www.haskell.org/ghc/docs/7.4.2/html/users_guide/kind-poly
this case the type system ensures that no references to the inotify
descriptor can exist after the callback returns.
Best,
Leon
On Fri, May 10, 2013 at 6:52 PM, Alexander Solla wrote:
>
>
>
> On Fri, May 10, 2013 at 3:31 PM, Leon Smith wrote:
>
>> On Fri, May 10, 2013 a
Ok, after mulling over the issues that Will Ness has brought up in
the last few days [1], I think I have a partial explanation for the
apparent tension between Will's observations and Heinrich Apfelmus's
Implicit Heaps article [2], which both concern the implementation of
mergeAll [3].
The merg
I don't believe that HsOpenSSL offers support for creating your own
SSL keys programmatically from Haskell. Do you actually need to
generate keys programmatically? If not, you could manually use
OpenSSL's command line tools; if your needs are simple enough it
shouldn't be too hard to spawn a
On Sat, Jan 8, 2011 at 11:55 AM, Michael Snoyman wrote:
> In general I think it would be a good thing to have solid, low-level bindings
> to PostgreSQL.
Well, there is PostgreSQL and libpq on hackage:
http://hackage.haskell.org/package/libpq
http://hackage.haskell.org/package/PostgreSQL
The P
I've been toying with a little thread manager library, and for
sanity's sake I really need a way to install another top-level
exception handler on an existing thread.I don't want to replace
any other handlers, just put my own handler around the thread's
continuation. Of course, it would be
There is a common idiom used in Control.Concurrent libraries, as
embodied in the implementation of bracket:
http://www.haskell.org/ghc/docs/7.0-latest/html/libraries/base-4.3.0.0/src/Control-Exception-Base.html#bracket
bracket before after thing =
mask $ \restore -> do
a <- before
r <-
This seems a timely email, as I've been submitting a steady-ish
trickle of patches to HDBC-postgresql lately. Honestly, I'm rather
dissatisfied with HDBC in many respects, but I don't have a very
good idea of what a (low-level) database access library for Haskell
*should* be, and I've found
On Wed, Feb 23, 2011 at 10:52 AM, Chung-chieh Shan
wrote:
> Mostly we preferred (as do the domain experts we target) to write
> probabilistic models in direct style rather than monadic style.
> Haskell's laziness doesn't help -- in fact, to avoid running out of
> memory, we'd have to defeat that m
I'm not particularly familiar with the codebase of either PostgreSQL
or GHC, but I'd be rather surprised that porting GHC's garbage
collector to PostgreSQL would be an easy or worthwhile task. For
example, GHC's garbage collector understands the memory layout that
its data structures use, whic
I have a type constructor (Iterator i o m a) of kind (* -> * -> (* ->
*) -> *), which is a monad transformer, and I'd like to use the type
system to express the fact that some computations must be "pure", by
writing the impredicative type (Iterator i o (forall m. m) a).
However I've run into a b
:
feedPure' :: [i]
-> Iterator i o (forall m :: (* -> *). m) a
-> Iterator i o (forall m :: (* -> *). m) a
Is impredicative polymorphism restricted to the kind *?
Best,
Leon
Then I get a tp
On Tue, Apr 12, 2011 at 5:37 AM, Dan Doel wrote
Thanks! The issue with eta-reduction had been confusing me...
Best,
Leon
On Tue, Apr 12, 2011 at 3:35 PM, Dan Doel wrote:
> On Tuesday 12 April 2011 11:27:31 AM Leon Smith wrote:
>> I think impredicative polymorphism is actually needed here; if I write
>> ...
>> Th
I doubt it. Even if you could turn GC completely off, the vast
majority of GHC Haskell programs will run out of memory very quickly.
Lazy evaluation has been called "evaluation by allocation"; unless
your program has very simple requirements and can live in the
completely-strict fragment of Ha
On Wed, Sep 21, 2011 at 3:39 AM, Heinrich Apfelmus
wrote:
> Of course, a list of 1 million items is going to take a lot of memory,
> unless you generate it lazily. Unfortunately mapM cannot generate its
> result lazily because it has to execute all IO actions before returning the
> list of resul
What you need to do is write a function that operates on a string that does
what you want it to, and then use that to write some top-level I/O code.
If you have a function sortFile :: String -> String, you would write
something like this for main:
main :: IO ()
main = do
string <- getConten
For an explanation why runST has the type it does, see page 4 of Simon
Peyton-Jones and John Launchbury's paper "Lazy functional state threads"
http://research.microsoft.com/Users/simonpj/Papers/lazy-functional-state-threads.ps.Z
On Friday 16 August 2002 23:57, Scott J. wrote:
>runST :: forall
Hi Max!
This is a type definiton, which says that parsing takes one argument, a
String, and gives you back a list of OpTree:
parsing :: String->[OpTree]
This is a function definition. The part before the = is called the
left hand side, while the part after the = is called the right hand sid
54 matches
Mail list logo