Re: [Haskell-cafe] Haskell's type inference considered harmful

2012-07-20 Thread Andreas Abel

Haha, I like this example.

However, if your are using ExtendedDefaultRules then you are likely to 
know you are leaving the clean sound world of type inference.  The 
example of my student works on plain GHC...


The other responses to my message confined to point me to best 
practices to avoid the design bugs of Haskell's type inference. 
However, if I want best practices, I can go to JavaScript.


To stirr action, mails on haskell-cafe seem useless.

I am already biased towards Haskell.  But as an unbiased decision maker, 
I would not consider a language with undead code for my projects...


Cheers,
Andreas


On 17.07.12 10:46 AM, o...@okmij.org wrote:

1. Haskell's type inference is NON-COMPOSITIONAL!


Yes, it is -- and there are many examples of it. Here is an example
which has nothing to do with MonomorphismRestriction or numeric
literals

{-# LANGUAGE  #-}

class C a where
 m :: a - Int

instance C () where
 m _ = 1

instance C Bool where
 m _ = 2

main = do
x - return undefined
let y = x
print . fst $ (m x, show x)
-- let dead = if False then not y else True
return ()

The program prints 1. If you uncomment the (really) dead code, it will
print 2. Why? The dead code doesn't even mention x, and it appears
after the printing! What is the role of show x, which doesn't do anything?

Exercises: what is the significance of the monadic bind to x? Why
can't we replace it with let x = undefined?

[Significant hint, don't look at it]

Such a behavior always occurs when we have HM polymorphism restriction
and some sort of non-parametricity -- coupled with default rules or
overlapping instances or some other ways of resolving overloading. All
these features are essential (type-classes are significant,
defaulting is part of the standard and is being used more and more).




--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/



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


Re: [Haskell-cafe] Cabal install fails due to recent HUnit

2012-07-20 Thread Simon Hengel
Hi Ross,
can you fix this on Hackage?  My suggested solution is to again just
remove the test-suite sections from the cabal file, if that is fine with
Richard.

The current situation is unfortunate, as it breaks almost all installs
from Hackage with cabal-install 0.10.2 / Cabal 1.10.1.0, e.g. you can
not even upgrade cabal-install anymore:

$ cabal --version
cabal-install version 0.10.2
using version 1.10.1.0 of the Cabal library
$ cabal install cabal-install
Resolving dependencies...
cabal: Couldn't read cabal file HUnit/1.2.5.0/HUnit.cabal

Cheers,
Simon

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


Re: [Haskell-cafe] Cabal install fails due to recent HUnit

2012-07-20 Thread Simon Hengel
 Upgrading to Cabal-1.10.2.0 (or cabal-install-0.14.0 with
 Cabal-1.14.0) should fix the problem.

Currently you would have to do the upgrade manually, as `cabal-install
cabal-install` won't work (or alternatively edit your local
~/.cabl/packages/hackage.haskell.org/00-index.tar).

See my other mail to this thread.

Cheers,
Simon

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


Re: [Haskell-cafe] Cabal install fails due to recent HUnit

2012-07-20 Thread Ross Paterson
On Fri, Jul 20, 2012 at 09:34:16AM +0100, Simon Hengel wrote:
 Hi Ross,
 can you fix this on Hackage?  My suggested solution is to again just
 remove the test-suite sections from the cabal file, if that is fine with
 Richard.

I'll modify the packages in-place if there's a consensus on what to do.

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


[Haskell-cafe] COBOL-85 parser, anyone?

2012-07-20 Thread Richard O'Keefe
Does anyone have a parser for COBOL-85 written in Haskell,
or written using some freely available tool that communicates
easily with Haskell?

I don't need it _yet_, but I'm talking with someone who is
trying to get access to a real legacy site with a bunch of,
well, basically COBOL 85, but there are extensions...
We're not talking about transformation at this stage, just
analysis.

I could probably hack up the extensions given a place to start.

I've found some papers and more dead links than I care for
and lots of mention of ASF+SDF which is apparently superseded
by Rascal.



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


[Haskell-cafe] Bug or feature?

2012-07-20 Thread Miguel Mitrofanov
Hi cafe!

I'm a bit confused by the DefaultSignatures extension. It's unclear whether to 
consider the following an example of clever use of this extension, or an 
example of abuse of it:

{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module SubClass where
import GHC.Prim(Constraint)
data Void (c :: * - Constraint) = Void
data Evidence c a where Evidence :: c a = Evidence c a
class c1 := c2 where
isSubClass :: c1 a = Void c1 - Evidence c2 a
default isSubClass :: c2 a = Void c1 - Evidence c2 a
isSubClass Void = Evidence
instance Show := Show
instance Floating := Fractional
instance Real := Num
-- instance Fractional := Floating -- NO ROTTEN WAY

{- Examples -}
data Wrapper c where Wrapper :: c a = a - Wrapper c
instance (c := Show) = Show (Wrapper c) where
show (Wrapper (a :: t)) = case isSubClass (Void :: Void c) :: Evidence Show 
t of Evidence - show a
absWrap :: (c := Num) = Wrapper c - Wrapper c
absWrap (Wrapper (a :: t) :: Wrapper c) = case isSubClass (Void :: Void c) :: 
Evidence Num t of Evidence - Wrapper (abs a)

What do you think?

Also, it's a bit strange that the first example (instance (c := Show) = Show 
(Wrapper c)) requires UndecidableInstances, while the second one (absWrap) 
requires FlexibleContexts - although being remarkably similar.

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


Re: [Haskell-cafe] COBOL-85 parser, anyone?

2012-07-20 Thread Malcolm Wallace
Ralf Laemmel would probably be the world's foremost expert in parsing and 
analysing Cobol using functional languages.  Try contacting him directly at 
uni-koblenz.de

Some of his relevant papers: http://homepages.cwi.nl/~ralf/padl03/  
http://homepages.cwi.nl/~ralf/ctp/

On 20 Jul 2012, at 10:08, Richard O'Keefe wrote:

 Does anyone have a parser for COBOL-85 written in Haskell,
 or written using some freely available tool that communicates
 easily with Haskell?
 
 I don't need it _yet_, but I'm talking with someone who is
 trying to get access to a real legacy site with a bunch of,
 well, basically COBOL 85, but there are extensions...
 We're not talking about transformation at this stage, just
 analysis.
 
 I could probably hack up the extensions given a place to start.
 
 I've found some papers and more dead links than I care for
 and lots of mention of ASF+SDF which is apparently superseded
 by Rascal.
 
 
 
 ___
 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] how to select random elements of a Data.Set?

2012-07-20 Thread jwaldmann
Dear all,

how would I quickly select an element of a Set (as in Data.Set)
uniformly at random? 

Via the API, this can only be done in linear time? (via toList)
If I could access the tree structure, 
then of course it could be logarithmic.

But probably I'd need a weighted selection sooner or later,
and this would require some specific code anyway. Or does it not?

Actually I need a sequence of such selections
(each selected element is deleted immediately).
I don't need all elements 
(so, computing a random permuation might be too much).

J.W.



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


Re: [Haskell-cafe] how to select random elements of a Data.Set?

2012-07-20 Thread Brent Yorgey
On Fri, Jul 20, 2012 at 01:24:57PM +, jwaldmann wrote:
 Dear all,
 
 how would I quickly select an element of a Set (as in Data.Set)
 uniformly at random? 
 
 Via the API, this can only be done in linear time? (via toList)
 If I could access the tree structure, 
 then of course it could be logarithmic.

If you had access to the Set constructors, this would be very easy, as
each node caches a size.  Unfortunately there does not appear to be
any way to do this in sub-linear time via the exposed API, because
there is no way to directly access the subtrees.

I wonder about the wisdom of exporting a function like

  -- | Partition a set into two approximately equal-sized subsets.
  --   If @divide s == (s1,s2)@, then 
  -- * @s1 `intersect` s2 == empty@
  -- * @s1 `union` s2 == s@
  -- * The sizes of @s1@ and @s2@ differ by at most a constant factor
  --   (currently, 3).
  divide :: Set a - (Set a, Set a)

which would give you enough to implement what you want, without
breaking the Set abstraction.  (However, even though technically it
doesn't break any abstraction, it still smells somewhat
implementation-dependent...)

-Brent

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


Re: [Haskell-cafe] how to select random elements of a Data.Set?

2012-07-20 Thread Roman Cheplyaka
There was recently a proposal to add indexing operators to Data.Set.
Until it is accepted, you can simulate Set with Map like this

  import Data.Map
  type Set a = Map a ()

Data.Map already has indexing operations (e.g. elemAt, deleteAt).

* jwaldmann waldm...@imn.htwk-leipzig.de [2012-07-20 13:24:57+]
 Dear all,
 
 how would I quickly select an element of a Set (as in Data.Set)
 uniformly at random? 
 
 Via the API, this can only be done in linear time? (via toList)
 If I could access the tree structure, 
 then of course it could be logarithmic.
 
 But probably I'd need a weighted selection sooner or later,
 and this would require some specific code anyway. Or does it not?
 
 Actually I need a sequence of such selections
 (each selected element is deleted immediately).
 I don't need all elements 
 (so, computing a random permuation might be too much).
 
 J.W.
 
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

-- 
Roman I. Cheplyaka :: http://ro-che.info/

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


Re: [Haskell-cafe] how to select random elements of a Data.Set?

2012-07-20 Thread Christian Maeder

Am 20.07.2012 15:24, schrieb jwaldmann:

Dear all,

how would I quickly select an element of a Set (as in Data.Set)
uniformly at random?


If you use a Map a () (or Map a a) you can use Map.elemAt.

The initial conversion is still linear, though.

-- | convert a set into an identity map
setToMap :: Ord a = Set.Set a - Map.Map a a
setToMap = Map.fromDistinctAscList . List.map (\ a - (a, a)) . Set.toList

HTH C.



Via the API, this can only be done in linear time? (via toList)
If I could access the tree structure,
then of course it could be logarithmic.

But probably I'd need a weighted selection sooner or later,
and this would require some specific code anyway. Or does it not?

Actually I need a sequence of such selections
(each selected element is deleted immediately).
I don't need all elements
(so, computing a random permuation might be too much).

J.W.




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


Re: [Haskell-cafe] Fwd: hackage compile failure with QuickCheck 2.5

2012-07-20 Thread Albert Y. C. Lai

On 12-07-17 01:43 PM, Levent Erkok wrote:

It still feels like this'll start biting more folks down the road. I've
created the following cabal ticket so it can be tracked:

https://github.com/haskell/cabal/issues/978

However, my understanding of the problem is rather incomplete; please
feel free to add comments to the ticket.


I apologize for not being interested in a github account (at least for 
now), and therefore not posting there.


1. I am not convinced that it is a cabal issue.

sbv-2.2 demands containers = 0.5 --- which most GHC versions don't have 
--- and template-haskell depends on containers. This requires replacing 
template-haskell or adding a new instance of template-haskell. As long 
as you or an algorithm obey dependencies, there is no way around it.


In fact, cabal-install since 0.14 already adds a hesitation. It aborts 
and warns likely to be broken by the reinstalls. If you use 
--force-reinstalls, it is your poison.


Why is it a cabal bug to obey human-decreed dependencies and instructions?

2. It is a very bad idea to keep around multiple versions of containers, 
multiple versions of template-haskell... generally multiple versions and 
instances of what comes with GHC. The GHC API (package name ghc) 
depends on them, too. Are we going to rebuild GHC multiple times too?


See my http://www.vex.net/~trebla/haskell/sicp.xhtml#pigeon
In fact, see the whole article.

A rumour says that my article caused adding the hesitation to 
cabal-install 0.14. My article was written before.


3. I see that now we have sbv-2.3, and its dependency reads: containers 
== 0.4.2.1


So now people using GHC 7.0.x, 6.12.x... have to add multiple versions 
of containers, rebuild template-haskell, and go through the same ordeal 
again.


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