Re: [Haskell-cafe] OS X ghci problem

2013-07-14 Thread Carter Schonwald
relatedly: johnW has nightly builds of GHC head for OS X 10.8 available for
download for those who would be up for braving such experimentation
ghc.newartisans.com


On Sat, Jul 13, 2013 at 10:16 PM, Jason Dagit dag...@gmail.com wrote:

 On Sat, Jul 13, 2013 at 6:44 PM, Carter Schonwald
 carter.schonw...@gmail.com wrote:
  has anyone tried using ghci HEAD? If the problem is linker based...
 perhaps
  ghci that uses the system Dylinker might resolve it?

 If someone gets brave and tries this I'd love to hear if it works.
 Although, that's too new for something we hope most people can use.
 I'm already feeling sheepish about requiring a minimum of 7.2.1 on OSX
 (that was the first version that knew what to do with .m files).

 Jason

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


[Haskell-cafe] ordNub

2013-07-14 Thread Niklas Hambüchen
tldr: nub is abnormally slow, we shouldn't use it, but we do.


As you might know, Data.List.nub is O(n²). (*)

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).

I've taken the Ord-based O(n * log n) implementation from yi using a Set:

  ordNub :: (Ord a) = [a] - [a]
  ordNub l = go empty l
where
  go _ [] = []
  go s (x:xs) = if x `member` s then go s xs
else x : go (insert x s) xs


and put benchmarks on
http://htmlpreview.github.io/?https://github.com/nh2/haskell-ordnub/blob/1f0a2c94a/report.html
(compare `nub` vs `ordNub`).

`ordNub` is not only in a different complexity class, but even seems to
perform better than nub for very small numbers of actually different
list elements (that's the numbers before the benchmark names).

(The benchmark also shows some other potential problem: Using a state
monad to keep the set instead of a function argument can be up to 20
times slower. Should that happen?)

What do you think about ordNub?

I've seen a proposal from 5 years ago about adding a *sort*Nub function
started by Neil, but it just died.


(*) The mentioned complexity is for the (very common) worst case, in
which the number of different elements in the list grows with the list
(alias you don't have an N element list with always only 5 different
things inside).

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


Re: [Haskell-cafe] ordNub

2013-07-14 Thread Clark Gaebel
Similarly, I've always used:

import qualified Data.HashSet as S

nub :: Hashable a = [a] - [a]
nub = S.toList . S.fromList

And i can't think of any type which i can't write a Hashable instance, so
this is extremely practical.
On Jul 14, 2013 7:24 AM, Niklas Hambüchen m...@nh2.me wrote:

 tldr: nub is abnormally slow, we shouldn't use it, but we do.


 As you might know, Data.List.nub is O(n²). (*)

 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).

 I've taken the Ord-based O(n * log n) implementation from yi using a Set:

   ordNub :: (Ord a) = [a] - [a]
   ordNub l = go empty l
 where
   go _ [] = []
   go s (x:xs) = if x `member` s then go s xs
 else x : go (insert x s) xs


 and put benchmarks on

 http://htmlpreview.github.io/?https://github.com/nh2/haskell-ordnub/blob/1f0a2c94a/report.html
 (compare `nub` vs `ordNub`).

 `ordNub` is not only in a different complexity class, but even seems to
 perform better than nub for very small numbers of actually different
 list elements (that's the numbers before the benchmark names).

 (The benchmark also shows some other potential problem: Using a state
 monad to keep the set instead of a function argument can be up to 20
 times slower. Should that happen?)

 What do you think about ordNub?

 I've seen a proposal from 5 years ago about adding a *sort*Nub function
 started by Neil, but it just died.


 (*) The mentioned complexity is for the (very common) worst case, in
 which the number of different elements in the list grows with the list
 (alias you don't have an N element list with always only 5 different
 things inside).

 ___
 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] ordNub

2013-07-14 Thread Clark Gaebel
Oops sorry I guess my point wasn't clear.

Why ord based when hashable is faster? Then there's no reason this has to
be in base, it can just be a free function in Data.HashSet. If stability is
a concern then there's a way to easily account for that using HashMap.

  - Clark
On Jul 14, 2013 7:48 AM, Niklas Hambüchen m...@nh2.me wrote:

 One of my main points is:

 Should we not add such a function (ord-based, same output as nub,
 stable, no sorting) to base?

 As the package counting shows, if we don't offer an alternative, people
 obviously use it, and not to our benefit.

 (Not to say it this way:
 We could make the Haskell world fast with smarter fusion, strictness
 analysis and LLVM backends.
 Or we could stop using quadratic algorithms.)

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


Re: [Haskell-cafe] ordNub

2013-07-14 Thread Niklas Hambüchen
One of my main points is:

Should we not add such a function (ord-based, same output as nub, 
stable, no sorting) to base?

As the package counting shows, if we don't offer an alternative, people 
obviously use it, and not to our benefit.

(Not to say it this way:
We could make the Haskell world fast with smarter fusion, strictness 
analysis and LLVM backends.
Or we could stop using quadratic algorithms.)

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


Re: [Haskell-cafe] Deriving with generics without values

2013-07-14 Thread Roman Cheplyaka
Forgot to mention — a good explanation of GHC Generics is the paper
A Generic Deriving Mechanism for Haskell.

Roman

* Roman Cheplyaka r...@ro-che.info [2013-07-14 18:21:58+0300]
 Hi,
 
 (Redirecting this back to cafe to keep it discoverable — hope you don't
 mind.)
 
 * JP Moresmau jpmores...@gmail.com [2013-07-14 16:02:56+0200]
  Hello, sorry to bother you after you've been kind enough to answer me on
  the list! I've looked a the smallcheck code but I don't see how to apply it
  to my issue. First of all, I can't find the definition of - that you use
  for example in ~. I suppose I'm doing something silly...
 
 That comes from LogicT. - is almost the same as =, and ~ is almost
 the same as *. Byt that's not relevant to the generic aspect of the
 code.
 
  But then, if I understand the code, the instances for GSerial rebuild
  a type definition that mimicks the one passed as type argument, using
  the final values (under the K1s) to generate a series. But in my case,
  I want to be able to extract information from the original type, I'm
  not just interested in the final value. What I want to be able is to
  extract for example the constructor name and do something with it. I
  don't see how to achieve that with your system.
 
 Yes, it doesn't do everything that you want to do, but it shows the
 idea.
 
 The information you need is all there — for example, to get the
 constructor name, you need to get hold of the C1 type (which is a
 synonym for M1 C), and then call the conName method.
 
 Lest you get lost in all this, it is useful to visualize the generic
 representation by running your code through -ddump-deriv. Here's an
 example:
 
 % ghci -XDeriveGeneric -ddump-deriv -dsuppress-module-prefixes
 Prelude GHC.Generics data T a = A { a :: a } | B | C deriving Generic
 
  Derived instances 
 Derived instances:
   instance Generic (T a_ao7) where
 from (A g1_aph) = M1 (L1 (M1 (M1 (K1 g1_aph
 from B = M1 (R1 (L1 (M1 U1)))
 from C = M1 (R1 (R1 (M1 U1)))
 to (M1 (L1 (M1 (M1 (K1 g1_api) = A g1_api
 to (M1 (R1 (L1 (M1 U1 = B
 to (M1 (R1 (R1 (M1 U1 = C
   
   instance Datatype D1T where
 datatypeName _ = T
 moduleName _ = :Interactive
   
   instance Constructor C1_0T where
 conName _ = A
 conIsRecord _ = True
   
   instance Constructor C1_1T where conName _ = B
   
   instance Constructor C1_2T where conName _ = C
   
   instance Selector S1_0_0T where selName _ = a
   
 
 Generic representation:
   
   Generated datatypes for meta-information:
 D1T
 C1_0T
 C1_1T
 C1_2T
 S1_0_0T
   
   Representation types:
 type Rep (T a_ao7) = D1
D1T
(C1 C1_0T (S1 S1_0_0T (Rec0 a_ao7))
 :+: (C1 C1_1T U1 :+: C1 C1_2T U1))
 
 This should give you an idea about how the structure you're dealing with
 looks like, and where the important information resides.
 
  I've also look at Aeson with the generic JSON parsing, but that's
  using SYB which is again different, and SYB doesn't seem to provide
  the types of the constructor fields, which I would need too...
 
 It provides the types of the constructor fields through the Typeable
 class, which may or may not be sufficient for your needs... Anyway,
 you're right in that it is a completely different approach.
 
 Roman
 
  On Fri, Jul 12, 2013 at 10:57 AM, Roman Cheplyaka r...@ro-che.info wrote:
  
   Well, in your case, you need not 'from', but 'to', in order to convert
   from a generic representation to yours.
  
   Take a look at how a similar task is done in SmallCheck:
  
   https://github.com/feuerbach/smallcheck/blob/master/Test/SmallCheck/Series.hs#L180
  
   https://github.com/feuerbach/smallcheck/blob/master/Test/SmallCheck/Series.hs#L352
  
   Roman
  
   * JP Moresmau jpmores...@gmail.com [2013-07-12 10:45:39+0200]
Hello all,
My problem is the following: I have my own data types, and I'd like to
derive automatically instances of some type class from them. I've 
started
looking at GHC.Generics, which offer tools to do exactly that. However,
some functions of my typeclass do not take my data type as a parameter,
   but
as a result. Basically:
 class MyClass where
   fromString :: String - a
   
 data MyData=MkMyData {
   myField ::Int
 } deriving (Generic)
   
and I want to automatically generate the instance instance MyClass
   MyData,
using default methods, etc.
The GHC Generic class does say that it uses a from function that convert
from the datatype to its representation: from :: a -
Rep
   http://www.haskell.org/ghc/docs/7.4.1/html/libraries/ghc-prim-0.2.0.0/GHC-Generics.html#t:Rep
   
a
xfrom :: a - Rep
   

Re: [Haskell-cafe] ordNub

2013-07-14 Thread Roman Cheplyaka
Something like that should definitely be included in Data.List.
Thanks for working on it.

Roman

* Niklas Hambüchen m...@nh2.me [2013-07-14 19:20:52+0800]
 tldr: nub is abnormally slow, we shouldn't use it, but we do.
 
 
 As you might know, Data.List.nub is O(n²). (*)
 
 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).
 
 I've taken the Ord-based O(n * log n) implementation from yi using a Set:
 
   ordNub :: (Ord a) = [a] - [a]
   ordNub l = go empty l
 where
   go _ [] = []
   go s (x:xs) = if x `member` s then go s xs
 else x : go (insert x s) xs
 
 
 and put benchmarks on
 http://htmlpreview.github.io/?https://github.com/nh2/haskell-ordnub/blob/1f0a2c94a/report.html
 (compare `nub` vs `ordNub`).
 
 `ordNub` is not only in a different complexity class, but even seems to
 perform better than nub for very small numbers of actually different
 list elements (that's the numbers before the benchmark names).
 
 (The benchmark also shows some other potential problem: Using a state
 monad to keep the set instead of a function argument can be up to 20
 times slower. Should that happen?)
 
 What do you think about ordNub?
 
 I've seen a proposal from 5 years ago about adding a *sort*Nub function
 started by Neil, but it just died.
 
 
 (*) The mentioned complexity is for the (very common) worst case, in
 which the number of different elements in the list grows with the list
 (alias you don't have an N element list with always only 5 different
 things inside).
 
 ___
 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] Deriving with generics without values

2013-07-14 Thread Roman Cheplyaka
Hi,

(Redirecting this back to cafe to keep it discoverable — hope you don't
mind.)

* JP Moresmau jpmores...@gmail.com [2013-07-14 16:02:56+0200]
 Hello, sorry to bother you after you've been kind enough to answer me on
 the list! I've looked a the smallcheck code but I don't see how to apply it
 to my issue. First of all, I can't find the definition of - that you use
 for example in ~. I suppose I'm doing something silly...

That comes from LogicT. - is almost the same as =, and ~ is almost
the same as *. Byt that's not relevant to the generic aspect of the
code.

 But then, if I understand the code, the instances for GSerial rebuild
 a type definition that mimicks the one passed as type argument, using
 the final values (under the K1s) to generate a series. But in my case,
 I want to be able to extract information from the original type, I'm
 not just interested in the final value. What I want to be able is to
 extract for example the constructor name and do something with it. I
 don't see how to achieve that with your system.

Yes, it doesn't do everything that you want to do, but it shows the
idea.

The information you need is all there — for example, to get the
constructor name, you need to get hold of the C1 type (which is a
synonym for M1 C), and then call the conName method.

Lest you get lost in all this, it is useful to visualize the generic
representation by running your code through -ddump-deriv. Here's an
example:

% ghci -XDeriveGeneric -ddump-deriv -dsuppress-module-prefixes
Prelude GHC.Generics data T a = A { a :: a } | B | C deriving Generic

 Derived instances 
Derived instances:
  instance Generic (T a_ao7) where
from (A g1_aph) = M1 (L1 (M1 (M1 (K1 g1_aph
from B = M1 (R1 (L1 (M1 U1)))
from C = M1 (R1 (R1 (M1 U1)))
to (M1 (L1 (M1 (M1 (K1 g1_api) = A g1_api
to (M1 (R1 (L1 (M1 U1 = B
to (M1 (R1 (R1 (M1 U1 = C
  
  instance Datatype D1T where
datatypeName _ = T
moduleName _ = :Interactive
  
  instance Constructor C1_0T where
conName _ = A
conIsRecord _ = True
  
  instance Constructor C1_1T where conName _ = B
  
  instance Constructor C1_2T where conName _ = C
  
  instance Selector S1_0_0T where selName _ = a
  

Generic representation:
  
  Generated datatypes for meta-information:
D1T
C1_0T
C1_1T
C1_2T
S1_0_0T
  
  Representation types:
type Rep (T a_ao7) = D1
   D1T
   (C1 C1_0T (S1 S1_0_0T (Rec0 a_ao7))
:+: (C1 C1_1T U1 :+: C1 C1_2T U1))

This should give you an idea about how the structure you're dealing with
looks like, and where the important information resides.

 I've also look at Aeson with the generic JSON parsing, but that's
 using SYB which is again different, and SYB doesn't seem to provide
 the types of the constructor fields, which I would need too...

It provides the types of the constructor fields through the Typeable
class, which may or may not be sufficient for your needs... Anyway,
you're right in that it is a completely different approach.

Roman

 On Fri, Jul 12, 2013 at 10:57 AM, Roman Cheplyaka r...@ro-che.info wrote:
 
  Well, in your case, you need not 'from', but 'to', in order to convert
  from a generic representation to yours.
 
  Take a look at how a similar task is done in SmallCheck:
 
  https://github.com/feuerbach/smallcheck/blob/master/Test/SmallCheck/Series.hs#L180
 
  https://github.com/feuerbach/smallcheck/blob/master/Test/SmallCheck/Series.hs#L352
 
  Roman
 
  * JP Moresmau jpmores...@gmail.com [2013-07-12 10:45:39+0200]
   Hello all,
   My problem is the following: I have my own data types, and I'd like to
   derive automatically instances of some type class from them. I've started
   looking at GHC.Generics, which offer tools to do exactly that. However,
   some functions of my typeclass do not take my data type as a parameter,
  but
   as a result. Basically:
class MyClass where
  fromString :: String - a
  
data MyData=MkMyData {
  myField ::Int
} deriving (Generic)
  
   and I want to automatically generate the instance instance MyClass
  MyData,
   using default methods, etc.
   The GHC Generic class does say that it uses a from function that convert
   from the datatype to its representation: from :: a -
   Rep
  http://www.haskell.org/ghc/docs/7.4.1/html/libraries/ghc-prim-0.2.0.0/GHC-Generics.html#t:Rep
  
   a
   xfrom :: a - Rep
  http://www.haskell.org/ghc/docs/7.4.1/html/libraries/ghc-prim-0.2.0.0/GHC-Generics.html#t:Rep
  
   a
   x
   But I don't have a a to start from! I see from the related papers that
   the automatically generated code from from actually does pattern matches
  on
   constructors, so I need a value, undefined won't work. However I see the
   

Re: [Haskell-cafe] ordNub

2013-07-14 Thread Francesco Mazzoli
At Sun, 14 Jul 2013 07:31:05 -0400,
Clark Gaebel wrote:
 Similarly, I've always used:
 
 import qualified Data.HashSet as S
 
 nub :: Hashable a = [a] - [a]
 nub = S.toList . S.fromList
 
 And i can't think of any type which i can't write a Hashable instance, so
 this is extremely practical.

Well, the above is not stable while Niklas’ is.  But I guess that’s not
the point of your message :).

I’ve always avoided “nub” too, and FWIW I’d like a constrained version
too—maybe avoiding Data.Set so that it could live in Data.List.  I think
Ord would be much better than Hashable, since it is 1. in “base” 2. much
more established and understood.

Although if you find yourself using “nub” too much you’re probably doing
something wrong...

Francesco

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


Re: [Haskell-cafe] Do combinatorial algorithms have a matroid strucutre XOR non-matroid structure?

2013-07-14 Thread Brent Yorgey
On Thu, Jul 11, 2013 at 03:39:02PM -0700, KC wrote:
 I ask this on this mailing list because there are quite a few
 mathematically oriented people here.

If you accept the Law of Excluded Middle, everything either has a
matroid structure, or not.  On the other hand, if you do not accept
it, then there may be some combinatorial algorithms which have neither
(because we have not found a matroid structure, or proved one does not
exist).  Either way, I do not understand the point of your question.

-Brent

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


Re: [Haskell-cafe] ordNub

2013-07-14 Thread Joey Adams
On Sun, Jul 14, 2013 at 7:31 AM, Clark Gaebel cgae...@uwaterloo.ca wrote:

 Similarly, I've always used:

 import qualified Data.HashSet as S

 nub :: Hashable a = [a] - [a]
 nub = S.toList . S.fromList

 And i can't think of any type which i can't write a Hashable instance, so
 this is extremely practical.

This won't yield results lazily (e.g. nub (repeat 'x') = _|_ instead of 'x'
: _|_), but Niklas' ordNub will.  His ordNub can be translated directly to
HashSet and still have the stability and laziness properties.

A difficulty with putting ordNub in Data.List is that it depends on
containers, which is outside of the base package.  Some options:

 * Move the implementation of Set to base.

 * Implement a lean version of Set in base that only provides 'insert' and
'member'.

 * Define ordNub in Data.Set instead.

Adding a Hashable-based nub to base would be even more problematic, since
you'd need Hashable in base.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-14 Thread Richard A. O'Keefe

On 12/07/2013, at 6:12 PM, Andreas Abel wrote:
[I can't try your F# example but ocaml does something different.]

Yes.  They are different languages.

By the way, I used the F# that comes with Mono.

 On 12.07.2013 02:22, Richard A. O'Keefe wrote:
 For what it's worth,
 
 let x = 1 in
 -   let x = x+1 in
 - let x = x+2 in
 -   x;;
 
 prints
 
 val it : int = 4
 
 in the F# interactive system, but
 
 let x = 1 in
 - let x = x+1 in
 - let x = x+2 in
 -   x;;
 
  let p = e in body
 
 is just
 
  (\ p - body) e
 
 it cannot be simpler than that.

True.  But it *can* be more complex than that,
and in F# it *is*.

  So I do not see your point.

The differently indented versions of the nested let do
different things.  Although F# is a descendant of Ocaml,
it is not the case that all lets in F# allow shadowing.

That's the point.


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


Re: [Haskell-cafe] ordNub

2013-07-14 Thread Conrad Parker
On 15 July 2013 09:54, Joey Adams joeyadams3.14...@gmail.com wrote:
 On Sun, Jul 14, 2013 at 7:31 AM, Clark Gaebel cgae...@uwaterloo.ca wrote:

 Similarly, I've always used:

 import qualified Data.HashSet as S

 nub :: Hashable a = [a] - [a]
 nub = S.toList . S.fromList

 And i can't think of any type which i can't write a Hashable instance, so
 this is extremely practical.

 This won't yield results lazily (e.g. nub (repeat 'x') = _|_ instead of 'x'
 : _|_), but Niklas' ordNub will.  His ordNub can be translated directly to
 HashSet and still have the stability and laziness properties.

 A difficulty with putting ordNub in Data.List is that it depends on
 containers, which is outside of the base package.  Some options:

  * Move the implementation of Set to base.

  * Implement a lean version of Set in base that only provides 'insert' and
 'member'.

  * Define ordNub in Data.Set instead.

 Adding a Hashable-based nub to base would be even more problematic, since
 you'd need Hashable in base.

Right, I suggest the following community course of action:

1a) add ordNub to Data.Set
1b) add ordNub to Data.Hashable
(1 day)

2) make a libraries@ proposal to include a stripped-down Data.Set-like
balanced binary tree implementation to base.
(2 weeks)

3) bikeshed about the name, eg.:
  * is nub really intuitive? how about uniq, like in
perl/ruby/underscore.js?
  * but uniq in unix only removes _adjacent_ duplicates, confusing!
  * how about distinct? sole? unique? azygous?
(7 weeks)

4) Failing consensus on technical grounds (that the stripped-down
Data.Set implementation is overkill for one library function), agree
that anyone who really cares should just use the version from
containers or hashable. Only newbs and textbook authors actually use
base anyway, and it's impossible to change the language definition.
Prelude will continue to fulfil its role of avoiding success at all
costs, quadratic or otherwise.

(Please, let's have both 1a and 1b :)

Conrad.

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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-14 Thread Richard A. O'Keefe

On 13/07/2013, at 11:27 PM, J. Stutterheim wrote:
 - they then abandoned the Macintosh world for
  Windows.  The Mac IDE was killed off; there is
  now an IDE for Windows but not MacOS or Linux.
 
 The good news is that the latest version of Clean[2] and its code 
 generator[3] now works fine again on 64 bit Mac OS X

Is that still the command-line tools, or has the IDE been resurrected?

 - other major features remain Windows-only
 
 The bad news is that this is true to some extend; the dynamics system is 
 still largely Windows-only. However, this is the only language feature I can 
 think of that really is Windows-only.

I have never been able to understand why there should be ANY
OS-dependency in the dynamics feature.

 - the available books about Clean are way out of
  date, several drafts of other books remain
  incomplete.
 - the documentation (like the Report) has always been
  rather amateurish and incomplete.  Certainly
  compared with the Haskell documentation.
 
 An iTasks book is actually in the works, which will contain a fair bit of 
 Clean (although it is not a dedicated Clean book). There are also concrete 
 plans to update the language manual soon-ish.

Not to be offensive, because after saying Denk U I have no more
Dutch words I can use, but it would really pay to find a native
speaker of English to give the manual a final polish.
 
 - there is nothing to compare with the Haskell Platform.
 
 Actually, yes there is[4].

A misundertanding.  Nothing to compare with is idiomatic for
nothing of comparable size to.  Yes, you _can_ compare the
Clean Platform with the Haskell Platform; it's a lot smaller.

 It can be described as a mix between Haskell Platform and a mini Hackage-like 
 repository. There is no such thing as a Clean alternative to cabal install, 
 though.
 
 Keep in mind that there is only a handful of people working on Clean, while 
 Haskell has a huge community in comparison. 

Haskell has always benefited from
- openness
- multiple implementations
- documentation


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


Re: [Haskell-cafe] ordNub

2013-07-14 Thread Thomas DuBuisson
Just so people are aware - five years ago the notion of nubOrd and
nubWith was discussed and a consensus reached on including nubOrd.  I
think Bart got too busy, didn't submit a final patch, and no one with
commit access actually commited any code.

http://haskell.1045720.n5.nabble.com/GHC-2717-Add-nubWith-nubOrd-td3159919.html

I fully support an efficient nub implementation making its way into
base - it's far past time.  Using Set seems sensible.

Cheers,
Thomas



On Sun, Jul 14, 2013 at 4:20 AM, Niklas Hambüchen m...@nh2.me wrote:
 tldr: nub is abnormally slow, we shouldn't use it, but we do.


 As you might know, Data.List.nub is O(n²). (*)

 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).

 I've taken the Ord-based O(n * log n) implementation from yi using a Set:

   ordNub :: (Ord a) = [a] - [a]
   ordNub l = go empty l
 where
   go _ [] = []
   go s (x:xs) = if x `member` s then go s xs
 else x : go (insert x s) xs


 and put benchmarks on
 http://htmlpreview.github.io/?https://github.com/nh2/haskell-ordnub/blob/1f0a2c94a/report.html
 (compare `nub` vs `ordNub`).

 `ordNub` is not only in a different complexity class, but even seems to
 perform better than nub for very small numbers of actually different
 list elements (that's the numbers before the benchmark names).

 (The benchmark also shows some other potential problem: Using a state
 monad to keep the set instead of a function argument can be up to 20
 times slower. Should that happen?)

 What do you think about ordNub?

 I've seen a proposal from 5 years ago about adding a *sort*Nub function
 started by Neil, but it just died.


 (*) The mentioned complexity is for the (very common) worst case, in
 which the number of different elements in the list grows with the list
 (alias you don't have an N element list with always only 5 different
 things inside).

 ___
 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