Re: [Haskell-cafe] Conduit : is it possible to write this function?

2013-08-26 Thread Erik de Castro Lopo
Michael Snoyman wrote:

 You can build this up using the = operator[1] in stm-conduit, something
 like:
 
 eitherSrc :: MonadResourceBase m
  = Source (ResourceT m) a - Source (ResourceT m) b - Source
 (ResourceT m) (Either a b)
 eitherSrc src1 src2 = do
 join $ lift $ Data.Conduit.mapOutput Left src1 =
 Data.Conduit.mapOutput Right src2
 
 I think this can be generalized to work with more base monads with some
 tweaks to (=).

Thanks Michael, that looks like it will fit the bill!

Cheers,
Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] TypeLits Typeable

2013-08-26 Thread José Pedro Magalhães
Hi Nicolas,

It's not intentional, but Iavor is aware of this, and we want to change it.
I'm CC-ing him as he might know more about what the current plan is.


Cheers,
Pedro


On Sat, Aug 24, 2013 at 3:20 PM, Nicolas Trangez nico...@incubaid.comwrote:

 Hello Cafe,

 I was playing around with TypeLits in combination with Typeable (using
 GHC 7.7.7.20130812 FWIW), but was surprised to find Symbols aren't
 Typeable, and as such the following doesn't work. Is this intentional,
 or am I missing something?

 Thanks,

 Nicolas

 {-# LANGUAGE DataKinds,
  KindSignatures,
  DeriveFunctor,
  DeriveDataTypeable #-}
 module Main where

 import Data.Typeable
 import GHC.TypeLits

 data NoSymbol n a b = NoSymbol a b
   deriving (Typeable)

 data WithSymbol (n :: Symbol) a b = WithSymbol a b
   deriving (Typeable)

 data Sym
   deriving (Typeable)

 main :: IO ()
 main = do
 print $ typeOf (undefined :: NoSymbol Sym Int Int)

 let d = undefined :: WithSymbol sym Int Int
 {-
 print $ typeOf d

 No instance for (Typeable Symbol sym)
   arising from a use of 'typeOf'
 -}

 return ()


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-26 Thread Niklas Hambüchen
On #haskell we recently had a discussion about the following:

   import System.Random

   list - replicateM 100 randomIO :: IO [Int]

I would think that this gives us a list of a million random Ints. In
fact, this is what happens in ghci. But with ghc we get:

   Stack space overflow: current size 8388608 bytes.
   Use `+RTS -Ksize -RTS' to increase it.

This is because sequence is implemented as

 sequence (m:ms) = do x - m
  xs - sequence ms
  return (x:xs)

and uses stack space when used on some [IO a].

From a theoretical side, this is an implementation detail. From the
software engineering side this disastrous because the code is

  * obviously correct by itself
  * the first thing people would come up with
  * not exaggerating: a million elements is not much
  * used a lot of places: mapM, replicateM are *everywhere*

and yet it will kill our programs, crash our airplanes, and give no
helpful information where the problem occurred.

Effectively, sequence is a partial function.

(Note: We are not trying to obtain a lazy list of random numbers, use
any kind of streaming or the likes. We want the list in memory and use it.)

We noticed that this problem did not happen if sequence were implemented
with a difference list.

What do you think about this? Should we fix functions like this,
probably trading off a small performance hit, or accept that idiomatic
Haskell code can crash at any time?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-26 Thread Niklas Hambüchen
As an example that this actually makes problems in production code, I
found this in the wildlife:

https://github.com/ndmitchell/shake/blob/e0e0a43/Development/Shake/Database.hs#L394

-- Do not use a forM here as you use too much stack space
bad - (\f - foldM f [] (Map.toList status)) $ \seen (i,v) - ...

I could bet that there is a lot of code around on which we rely, which
has the same problem but does not go that far in customisation.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] xmonad (+ mate) evince problem?

2013-08-26 Thread Johannes Waldmann
Problem solved: with mate, use atril instead of evince. 
(I think it is a gtk2/tgk3 issue and it's got nothing to do with xmonad.)



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ordNub

2013-08-26 Thread Niklas Hambüchen
On 14/07/13 20:20, Niklas Hambüchen wrote:
 As you might not know, almost *all* practical Haskell projects use it,
 and that in places where an Ord instance is given, e.g. happy, Xmonad,
 ghc-mod, Agda, darcs, QuickCheck, yesod, shake, Cabal, haddock, and 600
 more (see https://github.com/nh2/haskell-ordnub).

GHC uses nub.

Also let me stress again that the n² case happens even if there are no
duplicates.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proposal: Hackage's packages should be seperated by buildable

2013-08-26 Thread Heinrich Apfelmus

He-chien Tsai wrote:

I'm sick for checking whether package is obsolete or not.
I think packages build failed long time ago should be collected and moved
to another page until someone fix them, or hackage pages should have a
filter for checking obsolete packages.


People are working on it.

  http://new-hackage.haskell.org/


Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] TypeLits Typeable

2013-08-26 Thread Iavor Diatchki
Hi guys,

Yep, we know about this and, I believe, the plan is to add custom rules to
the constraint solver to solve `Typable n` constraints (where n is  a
number or symbol).   Just for the record, the other design choice was to
add instance `Typeable (n :: Symbol)`, but that conflicted with some of the
polymorphic instances already present in the library, so we decided to go
for the custom constraint solver rules.

This should not be hard to do, I just need to sit down and do it---my
current priority has been to catch up the type-nats solver with HEAD and
clean up things for merging.

-Iavor





On Mon, Aug 26, 2013 at 1:19 AM, José Pedro Magalhães j...@cs.uu.nl wrote:

 Hi Nicolas,

 It's not intentional, but Iavor is aware of this, and we want to change it.
 I'm CC-ing him as he might know more about what the current plan is.


 Cheers,
 Pedro


 On Sat, Aug 24, 2013 at 3:20 PM, Nicolas Trangez nico...@incubaid.comwrote:

 Hello Cafe,

 I was playing around with TypeLits in combination with Typeable (using
 GHC 7.7.7.20130812 FWIW), but was surprised to find Symbols aren't
 Typeable, and as such the following doesn't work. Is this intentional,
 or am I missing something?

 Thanks,

 Nicolas

 {-# LANGUAGE DataKinds,
  KindSignatures,
  DeriveFunctor,
  DeriveDataTypeable #-}
 module Main where

 import Data.Typeable
 import GHC.TypeLits

 data NoSymbol n a b = NoSymbol a b
   deriving (Typeable)

 data WithSymbol (n :: Symbol) a b = WithSymbol a b
   deriving (Typeable)

 data Sym
   deriving (Typeable)

 main :: IO ()
 main = do
 print $ typeOf (undefined :: NoSymbol Sym Int Int)

 let d = undefined :: WithSymbol sym Int Int
 {-
 print $ typeOf d

 No instance for (Typeable Symbol sym)
   arising from a use of ‛typeOf’
 -}

 return ()


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-26 Thread Bryan O'Sullivan
On Mon, Aug 26, 2013 at 1:46 AM, Niklas Hambüchen m...@nh2.me wrote:

 This is because sequence is implemented as

  sequence (m:ms) = do x - m
   xs - sequence ms
   return (x:xs)

 and uses stack space when used on some [IO a].


This problem is not due to sequence, which doesn't need to add any
strictness here. It occurs because the functions in System.Random are
excessively lazy. In particular, randomIO returns an unevaluated thunk.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Extending Type Classes

2013-08-26 Thread Henning Thielemann


 The problem of refinement of type classes annoys me from time to time 
when I work on the NumericPrelude. It is an experimental type class 
hierarchy for mathematical types. Sometimes a new data type T shall be 
implemented and it turns out that you can implement only a part of all 
methods of a certain class. Then a natural step is to split the class into 
two classes A and B: 'A' contains the methods we can implement for T and 
'B' contains the remaining methods and 'B' is a sub-class of 'A'.
 First, this means that all client code has to be rewritten. Second, code 
for instances becomes very lengthy, because over the time code tends to 
contain one instances for every method. However the many small instances 
actually carry information: Every instance has its specialised 
constraints. E.g. you would certainly try to use only Applicative 
constraints in an Applicative instance and not Monad constraints. However, 
if there is a way to define Applicative and Monad instances in one go, the 
Applicative instance may get Monad constraints.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] definition of the term combinator

2013-08-26 Thread Kristopher Micinski
I've always stuck to the definition of a closed lambda term (the Y, U, S,
K, etc... combinators, for example). The colloquial usage generally implies
something like a higher order function that does something interesting
(and possibly DSL-y).

Kris



On Sat, Aug 24, 2013 at 12:09 AM, damodar kulkarni
kdamodar2...@gmail.comwrote:

 Hello,
 The word combinator is used several times in the Haskell community. e.g.
 parser combinator, combinator library etc.

 Is it exactly the same term that is used in the combinatory logic ?
 A combinator is a higher-order function that uses *only function
 application* and earlier defined combinators to define a result from its
 arguments. [1]

 It seems, the term combinator as in, say, parser combinator, doesn't
 have much to do with the *only function application* requirement of the
 combinatory logic, per se.

 If the above observation holds, is the term combinator as used in the
 Haskell community, properly defined?

 In other words:

 Where can I find a formal and precise definition of the term combinator,
 as a term used by the Haskell community to describe something?

 Ref: http://en.wikipedia.org/wiki/Combinatory_logic

 Thanks and regards,
 -Damodar Kulkarni


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-26 Thread Niklas Hambüchen
Maybe an unlimited stack size should be the default?

As far as I understand, the only negative effect would be that some
programming mistakes would not result in a stack overflow. However, I
doubt the usefulness of that:

* It already depends a lot on the optimisation level
* If you do the same thing in a slightly different way, and you allocate
on the heap instead of on the stack you will not get it either

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-26 Thread Albert Y. C. Lai

On 13-08-26 04:46 AM, Niklas Hambüchen wrote:

Effectively, sequence is a partial function.

(Note: We are not trying to obtain a lazy list of random numbers, use
any kind of streaming or the likes. We want the list in memory and use it.)

We noticed that this problem did not happen if sequence were implemented
with a difference list.

What do you think about this? Should we fix functions like this,
probably trading off a small performance hit, or accept that idiomatic
Haskell code can crash at any time?


1. Disputed: sequence overflows stack, for all monads
(Bonus: a demo of Control.Monad.ST.Lazy)
(Bonus: a secret of Control.Monad.State revealed)

import Control.Monad.ST.Lazy(runST)
import Control.Monad.State(evalState)

long :: Monad m = m [Int]
long = sequence (map return [1..100])

infinite :: Monad m = m [()]
infinite = sequence (repeat (return ()))

-- these take constant time
one_a = take 1 (runST long)
one_b = take 1 (evalState long ())
unit_a = take 1 (runST infinite)
unit_b = take 1 (evalState infinite ())

sequence is exactly right for Control.Monad.ST.Lazy and 
Control.Monad.State. If you fix sequence, you will cause idiomatic use 
of sequence and Control.Monad.State to use too much time (up to 
infinite) and too much memory (up to infinite).


Note: Control.Monad.State = Control.Monad.State.Lazy

For more demos of Control.Monad.ST.Lazy and Control.Monad.State(.Lazy), 
see my

http://lpaste.net/41790
http://lpaste.net/63925


2. What to do for IO, Control.Monad.ST, Control.Monad.State.Strict, etc

As you said, we can combine right recursion (foldM) and difference list 
(aka Hughes list). I will dispute its questionable benefit in the next 
section, but here it is first.


sequence_hughes ms = do
h - go id ms
return (h [])
  where
go h [] = return h
go h (m:ms) = do
x - m
go (h . (x :)) ms

equivalently,

sequence_hughes ms = do
h - foldM op id ms
return (h [])
  where
op h m = do
x - m
return (h . (x :))

However, as I said, sequence_hughes is totally wrong for 
Control.Monad.State and Control.Monad.ST.Lazy. And this is not even my 
dispute of the questionable benefit.



3. Disputed: stack is limited, heap is unlimited

sequence_hughes consumes linear heap space in place of linear stack 
space. That's all it does. There is no free lunch.


Empirically: on linux i386 32-bit GHC 7.6.3 -O2:

xs - sequence (replicate 200 (return 0 :: IO Int))
print (head xs)

8MB stack, 16MB heap

xs - sequence_hughes (replicate 200 (return 0 :: IO Int))
print (head xs)

24MB heap

What has sequence_hughes saved?

Since a couple of years ago, GHC RTS has switched to growable stack, 
exactly like growable heap. It starts small, then grows and shrinks as 
needed. It does not need a cap. The only reason it is still capped is 
the petty:


to stop the program eating up all the available memory in the machine 
if it gets into an infinite loop (GHC User's Guide)


Asymmetrically, the heap is not capped by default to stop the program 
eating up all the available memory.


And the default stack cap 8MB is puny, compared to the hundreds of MB 
you will no doubt use in the heap. (Therefore, on 64-bit, you have to 
change 200 to 100 in the above.) (Recall: [Int] of length n 
entirely in memory takes at least 12n bytes: 4 for pointer to Int, 4 for 
the number itself, 4 for pointer to next, and possibly a few more bytes 
I forgot, and possibly a few more bytes if the Int is lazy e.g. randomIO 
as Bryan said. That's just on 32-bit. Multiply by 2 on 64-bit.)


The correct fix is to raise the stack cap, not to avoid using the stack.

Indeed, ghci raises the stack cap so high I still haven't fathomed where 
it is. This is why you haven't seen a stack overflow in ghci for a long 
time. See, ghci agrees: the correct thing to do is to raise the stack cap.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe