On Fri, 2011-12-23 at 01:29 +0400, MigMit wrote:
> Отправлено с iPad
>
> 22.12.2011, в 23:56, Conor McBride
> написал(а):
>
> > I'd be glad if "pure" meant "total", but
> > partiality were an effect supported by the run-time system. Then we
> > could choose to restrict ourselves, but we wouldn't
Iteratee-compress provides compressing and decompressing enumerators
including flushing (using John Lato's implementation). Currently only
gzip and bzip is provided but LZMA is planned.
Changes from previous version:
- Move API from enumerator to enumeratee
Next goals:
- LZMA support
- Generic
On Wed, 2011-09-21 at 01:23 +0200, Daniel Fischer wrote:
> On Wednesday 21 September 2011, 00:38:12, Maciej Marcin Piechotka wrote:
> > +1 for:
> >
> > class Eq a => Iq a where
> > (<.) :: a -> a -> Bool
> > (>.) :: a -> a -> Bool
On Tue, 2011-09-20 at 16:05 -0600, Chris Smith wrote:
> On Tue, 2011-09-20 at 17:28 -0400, Casey McCann wrote:
> > Since removing the instances entirely is
> > probably not a popular idea, the least broken solution would be to
> > define NaN as equal to itself and less than everything else, thus
>
On Mon, 2011-09-12 at 11:51 +0400, Grigory Sarnitskiy wrote:
> I want to have Unicode symbols for type operator:
>
> {-# LANGUAGE TypeOperators #-}
Add also:
{-# LANGUAGE UnicodeSyntax #-}
>
> data a ── b = Foo a b
>
> But it doesn't work. Any suggestions?
Regards
signature.asc
Description
On Fri, 2011-09-09 at 00:41 +0200, Roman Cheplyaka wrote:
> * Ertugrul Soeylemez [2011-09-07 16:20:03+0200]
> > In general it's a bad idea to use mapM over IO.
>
> Could you explain why?
>
> Thanks.
>
Hmm. Isn't it explained by next sentence ("For [] it will eat lots of
memory quickly and by i
On Mon, 2011-08-29 at 20:24 -0700, Ryan Ingram wrote:
>
>
> On Sun, Aug 28, 2011 at 8:24 PM, Maciej Marcin Piechotka
> wrote:
> f `fmap` FList g = _|_
> f `fmap` FList g = map id
> f `fmap` FList g = map _|_
> (+ variation of _|_*)
>
On Fri, 2011-08-26 at 20:30 +0100, Andrew Coppin wrote:
> On 26/08/2011 07:36 PM, Steve Schafer wrote:
> > On Fri, 26 Aug 2011 18:24:37 +0100, you wrote:
> >
> >> I would usually want #3 or #4.
> >
> > Out of curiosity, what for? While I do occasionally need to get a
> > "logarithmic size estimate"
On Mon, 2011-08-29 at 12:00 +0900, Sebastian Fischer wrote:
> On Sun, Aug 28, 2011 at 12:41 AM, Sönke Hahn wrote:
> > I was wondering which
> > type could be an instance of Pointed, but not of Applicative. But I can't
> > think of one. Any ideas?
>
> Functional lists:
>
> type FList a = [a]
On Sun, 2011-08-28 at 11:48 -0300, Felipe Almeida Lessa wrote:
> On Sun, Aug 28, 2011 at 7:41 AM, Tony Morris wrote:
> > Pointed f => Pointed (StateT s f)
> >
> > but not
> >
> > Applicative f => Applicative (StateT s f)
>
> But we do have
>
> (Functor m, Monad m) => Applicative (StateT s m)
On Sat, 2011-08-20 at 11:51 -0500, Vincent Gerard wrote:
> Hi cafe,
>
> I have been struggling with this issue for the past days. I have
> investigated at the Haskell, C and even at assembly level...
> Perhaps I'm missing something big ??
>
> I hope someone familiar with FFI could help me on this
On Sat, 2011-07-30 at 15:07 -0700, KC wrote:
> Are there plans a foot (or under fingers) to make a version of Haskell
> that runs on the JVM?
>
I m not GHC developer but wouldn't JVM LLVM backend be sufficient? Since
new GHC AFAIK uses LLVM then it would allow compiling Haskell to LLVM
and LLVM t
On Mon, 2011-07-25 at 00:11 -0400, August Sodora wrote:
> Out of (perhaps naive) curiosity, what difficulties does allowing such
> overriding introduce? Wouldn't the module system prevent the ambiguity
> of which implementation to use?
>
> August Sodora
> aug...@gmail.com
> (201) 280-8138
>
clas
On Sun, 2011-07-24 at 19:29 +0100, Julian Porter wrote:
>
>
>
> On 24 Jul 2011, at 19:19, KC wrote:
>
> > I like the following but again "+" denotes addition and not a
> > general
> > binary operation.
> >
> >
> > > I personally often define the alias:
> > >
> > > (<+>) = mappend
> >
> > A
> 2) One possibility is just have it being (Node x _ _) >>= f = f x
>
It does not follow monad laws (right identity to be more precise):
(Node 1 (Node 2 Empty Empty) Empty) >>= return ≡
return 1 ≡
Node 1 Empty Empty
≠
(Node 1 (Node 2 Empty Empty) Empty)
Regards
signature.asc
Description: This
On Sat, 2011-07-23 at 06:37 -0700, Ting Lei wrote:
> I know the Reverse Polish is not a couple of hundred years old.
> I have an impression of reading something about people writing natural
> deduction systems using only dots in place of parenthesis. And it is
> said that it was "natural" in tho
On Tue, 2011-07-19 at 07:11 +, Ivan Lazar Miljenovic wrote:
> On 19 July 2011 06:52, Ting Lei wrote:
> >
> > I read somewhere that people a couple of hundreds of years ago can manage to
> > express things using ($)-like notation without any parenthesis at all.
>
> The only thing that I can th
On Tue, 2011-07-19 at 01:13 +0200, Yves Parès wrote:
> Oh, I got it: You want to have:
>
> class Bird b where
>
> class Penguin p where
>
> instance (Penguin b) => Bird b where
>fly = -- fly method for penguins
>
I haven't followed the thread carefully but why does the bird have to be
a pe
On Mon, 2011-06-06 at 23:38 +0800, Lyndon Maydwell wrote:
> I'm writing an optimisation routine using Uniplate. Unfortunately, a
> sub-function I'm writing is getting caught in an infinite loop because
> it doesn't return Nothing when there are no optimisations left.
>
> I'd like a way to move the
On Fri, 2011-06-03 at 10:03 +0200, Ketil Malde wrote:
>
> Gresham's law states roughly that bad money drives out good. I thus
> propose a corollary: bad languages drive out good.
That's not entirely true - http://en.wikipedia.org/wiki/Gresham's_law.
"which states that when government compulsor
On Tue, 2011-05-24 at 15:37 +0100, Colin Adams wrote:
> And I thought Hugs was dead. :-)
I think we have explanation for the friendliness of Haskell community -
even the compiler hugs.
Regards
signature.asc
Description: This is a digitally signed message part
__
On Sat, 2011-05-14 at 17:32 -0700, Gregory Crosswhite wrote:
> On 5/14/11 1:25 PM, Maciej Marcin Piechotka wrote:
> > (to mention
> > one which is often neglected - parallel build).
>
> While I do appreciate you stepping in to defend autotools (if for no
> other reason
On Wed, 2011-05-11 at 18:13 -0700, Gregory Crosswhite wrote:
> on top of it and have to start from scratch --- or worse, *autotools*
> (SHUDDER!)
While i don't have much experience autotools seems to be villainize.
Sure it's old and have it's quirks. It is hard to learn and many people
use it im
On Thu, 2011-05-12 at 15:29 +0400, Grigory Sarnitskiy wrote:
> Hello!
>
> I've just started using parallel computations in Haskell. parMap works fine,
> it is so easy to use. However, parMap fails with functions returning lazy
> structures, e.g. tuples.
>
> This code works as expected:
>
> (pa
Sorry for third post but I wonder why the many instances are restricted
by Monad.
Both Functor and Applicative can by constructed without Monad:
> instance (Functor m) => Functor (CtlArg t m) where
> fmap f (CtlArg arg g c) = CtlArg arg (fmap f . g) c
>
> instance (Functor m) => Functor (Ite
Sorry for second-posting. In addition to the problems mentioned
elsewhere (too big packages) I would like to point problems with SSL:
- It uses OpenSSL from what I understand which is not compatible with
GPL-2 as it uses Apache 1.0 licence (in addition to BSD4) as it requires
mentioning OpenSSL (
On Thu, 2011-05-05 at 21:15 -0700, David Mazieres wrote:
> Hi, everyone. I'm pleased to announce the release of a new iteratee
> implementation, iterIO:
>
> http://hackage.haskell.org/package/iterIO
>
> IterIO is an attempt to make iteratees easier to use through an
> interface based on pi
On Wed, 2011-05-04 at 02:00 -0400, Ken Takusagawa II wrote:
> I run into the following type error:
>
> foo :: ST s (STRef s Int) -> Int
> foo p = (runST (p >>= readSTRef))
>
> with ghc 6.12.1
> st.hs:8:16:
> Couldn't match expected type `s1' against inferred type `s'
> `s1' is a rigid t
On Wed, 2011-04-27 at 20:16 +0200, John Obbele wrote:
> Hi Haskellers,
>
>
> I'm currently serializing / unserializing a bunch of bytestrings
> which are somehow related to each others and I'm wondering if
> there was a way in Haskell to ease my pain.
>
> The first thing I'm looking for, is to b
On Tue, 2011-04-26 at 16:34 +0200, Daniel Fischer wrote:
> On Tuesday 26 April 2011 16:04:55, Nick Bowler wrote:
> > On 2011-04-26 15:51 +0200, Daniel Fischer wrote:
> > > On Tuesday 26 April 2011 15:35:42, Ivan Lazar Miljenovic wrote:
> > > > How do you "see" how git branches are related to each o
On Sat, 2011-04-23 at 12:31 +0200, Heinrich Apfelmus wrote:
> David Terei wrote:
> > Good chance you've already read this but if not here is a good post by
> > Linus about his take on the problems with darcs:
> >
> > http://markmail.org/message/vk3gf7ap5auxcxnb
>
> I always have to smile at the
On Fri, 2011-04-22 at 21:26 +0200, Henning Thielemann wrote:
> On Fri, 22 Apr 2011, Christopher Done wrote:
>
> > Use of Fantom's save invoke and Maybe are more or less the same.
> >
> > -- Hard way
> > email = if userList /= Nothing
> >then let user = findUser "bob" (fromJust userLis
On Tue, 2011-04-19 at 10:02 -0300, Felipe Almeida Lessa wrote:
>
> Now, that's what I get from reading the code. I don't remember if it
> is explicitly allowed or forbidden for an iteratee to generate
> leftovers out of nowhere. My guess is that it doesn't make much sense
> to allow it.
For th
On Thu, 2011-04-21 at 19:39 -0500, Jake McArthur wrote:
> On Thu, Apr 21, 2011 at 7:31 PM, Maciej Marcin Piechotka
> wrote:
> > Last time I checked it disallowed my as 5 depended on 4 which depended
> > on 3 which depended on 2 which depended on 1 as all changed x.hs
>
>
On Thu, 2011-04-21 at 19:19 -0500, Jake McArthur wrote:
> On Thu, Apr 21, 2011 at 6:32 PM, Maciej Marcin Piechotka
> wrote:
> > Assume following changes
> > 1. Feature X - file x.hs
> > 2. Feature Y - file y.hs and x.hs
> > 3. Feature Z - file z.hs and x.hs
> &g
On Thu, 2011-04-21 at 23:56 +0200, Nick Smallbone wrote:
> "larry.liuxinyu" writes:
>
> > Somebody told me that:
> > Eduard Sergeev • BTW, more recent QuickCheck (from Haskell Platform
> > 2011.2.0.X - contains QuickCheck-2.4.0.1) seems to identifies the
> > problem correctly:
> >
> > *** Failed!
On Thu, 2011-04-21 at 21:29 +0100, Andrew Coppin wrote:
> I'm sure this must be a VFAQ, but... There seems to be universal
> agreement that Darcs is a nice idea, but is unsuitable for "real"
> projects. Even GHC keeps talking about getting rid of Darcs. Can anybody
> tell me what the "problems"
On Thu, 2011-04-21 at 16:16 -0700, John Meacham wrote:
> Um, the patch theory is what makes darcs "just work". There is no need
> to understand it any more than you have to know VLSI design to
> understand how your computer works. The end result is that darcs
> repositories don't get corrupted and
On Mon, 2011-04-11 at 12:09 +, Serguei Son wrote:
> Consider two versions of sin wrapped:
> foreign import ccall "math.h sin"
> c_sin_m :: CDouble -> IO CDouble
> and
> foreign import ccall "math.h sin"
> c_sin :: CDouble -> CDouble
>
> One can invoke them so:
>
> mapM c_sin_m [1..n]
On Thu, 2011-04-07 at 19:04 +0200, Ertugrul Soeylemez wrote:
> Hello fellow Haskellers,
>
> I'm trying to solve a very practical problem: I need a stateful
> iteratee monad transformer. Explicit state passing is very inconvenient
> and would destroy the elegance of my library.
>
> There are two
On Mon, 2011-03-14 at 17:56 +0100, Yves Parès wrote:
> If you have only one alternative, then you can simply do:
>
> Opt1 <- someIO
>
> E.g., if you are _sure_ that foo returns always a 'Just' within a monad you
> can perfectly do :
>
> Just x <- foo
>
Please beware - it is not exactly the sam
Is there any version of haddock that builds with ghc 7.0.2?
For 2.9.1 I get:
src/Haddock/Interface/Create.hs:282:11:
Couldn't match expected type `Located b0'
with actual type `[LTyClDecl id0]'
Expected type: HsGroup id0 -> [Located b0]
Actual type: HsGroup id0 -> [[
On Sat, 2011-03-05 at 00:51 +0100, Yves Parès wrote:
>
>
> But I don't have an explicit type to put.
> I cound do:
>
> data CtxFooInst
> instance CtxFoo CtxFooInst
>
> and declare runFoo as this:
>
> runFoo :: MyIO CtxFooInst a -> IO a
>
> But I loose the ability to make functions that can ru
On Sat, 2011-02-26 at 14:22 +0300, Miguel Mitrofanov wrote:
> Well, this code in C++ would probably work too:
>
> Klass *k = new Klass(4,5);
> delete k;
> std::cout << k->getY() << std::endl;
>
> though smart compiler would probably issue a warning. See, when you
> delete something, C++ doesn't a
On Tue, 2011-02-22 at 12:36 +0300, Michael A Baikov wrote:
> Actually i can give you full sorce code - it uses also
> attoparsec-iteratee. it leaks with iteratee-compress and works fine
> without it.
If you believe that there is leak - please do so. However I don't
imagine a place where they may o
45 matches
Mail list logo