[Haskell-cafe] ANN: fix-imports-0.1.2

2011-07-12 Thread Evan Laforge
Not sure if anyone else is using this, but I've fixed some bugs and
bumped fix-imports by a few more versions.

Here's copy paste from the package description:

A small standalone program to manage the import block of a haskell
program. It will try to add import lines for qualified names with no
corresponding import, remove unused import lines, and sort the import
block according to some heuristic you can define. This only works for
qualified imports! Unqualified imports are left untouched.

It's most convenient if bound to an editor key.

Changes since last announcement:

Mon Jul 11 23:00:19 PDT 2011  qdun...@gmail.com
  * version 0.1.2

Mon Jul 11 22:58:56 PDT 2011  qdun...@gmail.com
  * fix but where multiple comments above an import are lost

Fri Jul  1 15:16:40 PDT 2011  qdun...@gmail.com
  * don't reload file if no changes were made

Fri Jul  1 14:43:02 PDT 2011  qdun...@gmail.com
  * sort and format the import block even if imports weren't added or removed

Wed Jun 15 12:39:12 PDT 2011  qdun...@gmail.com
  * version 0.1.1

Wed Jun 15 12:14:31 PDT 2011  qdun...@gmail.com
  * upgrade to haskell-src-exts 1.11, which removes the mandatory fixities

Wed Jun 15 12:11:27 PDT 2011  qdun...@gmail.com
  * fix bug causing qualified vs. non-qualified imports to be sorted
inconsistently

Thu Jun  2 12:10:08 PDT 2011  qdun...@gmail.com
  * more specific versions for base

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


Re: [Haskell-cafe] ANN: fix-imports-0.1.2

2011-07-12 Thread Ivan Lazar Miljenovic
On 12 July 2011 16:09, Evan Laforge qdun...@gmail.com wrote:
 Not sure if anyone else is using this, but I've fixed some bugs and
 bumped fix-imports by a few more versions.

 Here's copy paste from the package description:

 A small standalone program to manage the import block of a haskell
 program. It will try to add import lines for qualified names with no
 corresponding import, remove unused import lines, and sort the import
 block according to some heuristic you can define. This only works for
 qualified imports! Unqualified imports are left untouched.

 It's most convenient if bound to an editor key.

This sounds interesting; it would be helpful if you could provide an
example if you could provide an example in the README or description
of what exactly this program does however.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com

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


Re: [Haskell-cafe] ANN: fix-imports-0.1.2

2011-07-12 Thread Evan Laforge
On Mon, Jul 11, 2011 at 11:48 PM, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:
 A small standalone program to manage the import block of a haskell
 program. It will try to add import lines for qualified names with no
 corresponding import, remove unused import lines, and sort the import
 block according to some heuristic you can define. This only works for
 qualified imports! Unqualified imports are left untouched.

 It's most convenient if bound to an editor key.

 This sounds interesting; it would be helpful if you could provide an
 example if you could provide an example in the README or description
 of what exactly this program does however.

Sure, well... it's like the paragraph above :)

As an example, I just hack away in haskell normally.  When I've edited
a chunk, and have a feeling a changed the dependencies, I hit ',a' in
vim, and it will remove imports that are no longer used, and add
imports that are now needed.  As a bonus it'll sort and format the
import list.

That way I don't have to figure out if there are new modules needed,
go to the top of the file, sift past the module haddock and find the
right spot in the potentially large import list (and maybe I can't
just ! out to 'sort' for that if some are qualified and some are
unqualified), and type all that repetitive 'import qualified
Blah.Blah.Blah as Blah' stuff.  And I don't have to wait for ghc to
warn me about redundant imports and then go delete them one by one.

In addition to being generally convenient, I've found I'm more willing
to use tiny helper functions like 'Maybe.fromMaybe' instead of just
'maybe x id' since the hassle of possibly adding the new import has
been eliminated.

It's a standalone program so it doesn't have to be vim, but that's
what I use, so that's what I include binding glue for.


I've also got an unrelated simple thing that keeps the currently
edited haskell module in a file so I can type :L in ghci to load the
module currently being edited.  Very convenient, especially when
modules start getting nested.

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


Re: [Haskell-cafe] The Typeable class is changing

2011-07-12 Thread Yitzchak Gale
I wrote:
 Please respond to this thread if you own a package
 that will be affected by this change.

Responding to my own request, here are some more
packages that use mkTyCon explicitly:

Ashley Yakeley's time package, which is part of the
Haskell Platform.

My timezone-series package, because it is based on
the time package.

John Millikin's xml-types package.

My dtd-types and dtd-text packages, because they are
based on the xml-types package.

-Yitz

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


Re: [Haskell-cafe] ANN: fix-imports-0.1.2

2011-07-12 Thread Ivan Lazar Miljenovic
On 12 July 2011 17:18, Evan Laforge qdun...@gmail.com wrote:
 On Mon, Jul 11, 2011 at 11:48 PM, Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com wrote:
 A small standalone program to manage the import block of a haskell
 program. It will try to add import lines for qualified names with no
 corresponding import, remove unused import lines, and sort the import
 block according to some heuristic you can define. This only works for
 qualified imports! Unqualified imports are left untouched.

 It's most convenient if bound to an editor key.

 This sounds interesting; it would be helpful if you could provide an
 example if you could provide an example in the README or description
 of what exactly this program does however.

 Sure, well... it's like the paragraph above :)

I meant more in the Before: ... After: ... sense ;-) (i.e. visually
being able to tell what your program does, rather than just a
description).

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com

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


Re: [Haskell-cafe] ANN: fix-imports-0.1.2

2011-07-12 Thread Evan Laforge
 I meant more in the Before: ... After: ... sense ;-) (i.e. visually
 being able to tell what your program does, rather than just a
 description).

Oh, ok, I guess I can do that too:

Before:

module M where
import ZZ.Out.Of.Order
import qualified No.Longer.Needed as Needed

-- x = Needed.y -- just removed this
y = New.something -- just added this

After:

module M where
import qualified Heavily.Nested.New as New
import ZZ.Out.Of.Order

-- x = Needed.y -- just removed this
y = New.something -- just added this

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


Re: [Haskell-cafe] Inconsistent trailing comma in export list and record syntax

2011-07-12 Thread Christian Maeder
Generally allowing trailing (or leading or repeated) commas would clash 
with tuple sections. Also the pair constructor (,) is a special case.


http://www.haskell.org/ghc/docs/7.0.4/html/users_guide/syntax-extns.html#tuple-sections

Cheers Christian

Am 11.07.2011 12:09, schrieb Joachim Breitner:

Hi,

Am Montag, den 11.07.2011, 10:49 +0200 schrieb L Corbijn:

You could of course say that I'm using a bad style, but it remains
that it seems to be inconsistent to allow a trailing comma in one
place and not in the other. So is there an reason for this?


there is actually a bug report against the ghc package in Debian from a
user, requesting a more liberal comma separated list parsing. We did not
patch ghc in Debian to that end, though :-)
http://bugs.debian.org/cgi-bin/bugreport.cgi?bug=511834

Greetings,
Joachim




___
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] The Typeable class is changing

2011-07-12 Thread Jon Fairbairn
Carl Howells chowe...@janrain.com writes:

 This will affect snap-core and heist, of the things I've provided
 Typeable instances for.

 In snap-core, deriving makes it use the internal module name, rather
 than the canonical location of the type.  This causes issues with the
 Hint library, so it's worked around by using a manual instance of
 Typeable.

There’ll be a replacement for mkTycon (mkTycon3), so you can
still do manual instances…

 So, this change will hit me for two different reasons, and sadly
 involve using CPP to control how things are compiled.

so that shouldn’t be necessary.

-- 
Jón Fairbairn jon.fairba...@cl.cam.ac.uk



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


Re: [Haskell-cafe] [Haskell] Call for GUI examples - Functional Reactive Programming

2011-07-12 Thread Paul Liu
Hi James, I think you meant to reply to the list.

For one, I wouldn't consider GUI programming based on HTML as
declarative, since more often than not, the format says nothing about
its behavior, and when it does, it's through javascript, which is
hardly declarative.

Regards,
Paul Liu

On Tue, Jul 12, 2011 at 5:17 AM, James Deng cnjamesd...@gmail.com wrote:
 These days, more and more GUI programming are done in declarative, such as
 HTML(jQuery), Mozilla XUL, android UI XML.

 Haskell is an excellent declarative language, so should have the advantages
 of constructing GUI in declarative, intuitive and powerful way. But so far,
 there is not such a GUI library intuitive like Html, powerful like XUL.

 I expect something like html to layout GUI, and a haskell GUI engine would
 render the user interfaces files.
 Where is the gap lying?

 On 07/12/2011 05:51 AM, Paul Liu wrote:

 You guys might want to checkout the recent work on Euterpea at Yale
 CS. In particular:

 1. Paul Hudak is writing a new book.
 http://plucky.cs.yale.edu/cs431/reading.htm
 2. It uses FRP and arrows for sound synthesis.
 3. It combines FRP signals with monadic (which recently gets
 re-written in arrows) GUI composition.
 4. New novel techniques is being developed to handle I/O within arrows
 framework.

 The code can be obtained through darcs, details at
 http://plucky.cs.yale.edu/cs431/software_resources.htm

 Notably, the way it handles GUI is that the composition of widgets are
 static, but the signals flowing between them are dynamic. This closely
 follows Conal Elliott's Phooey approach, and greatly reduces the
 complexity of GUI programming.

 Disclaimer: I was an ex-student who worked on this project.

 Regards,
 Paul Liu

 On Thu, Jul 7, 2011 at 11:08 PM, Heinrich Apfelmus
 apfel...@quantentunnel.de wrote:

 Dear Haskellers,

 Can GUI programming be liberated from the IO monad?


 Regards,
 --
 James Deng
 http://cnjdeng.appspot.com



-- 
Regards,
Paul Liu

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


Re: [Haskell-cafe] The Typeable class is changing

2011-07-12 Thread Yitzchak Gale
Jon Fairbairn wrote:
 There’ll be a replacement for mkTycon (mkTycon3), so you can
 still do manual instances…

Right, it should be easy to fix manual Typeable instances.
It's just that if no action is taken, they will eventually break.
So it's good to make sure that there is public awareness,
and for the community to have awareness about the scope
of the changes that need to be made.

Also, we should clarify that AFAIK everyone agrees that this
is a welcome improvement to Typeable. We are just trying
to smooth the upgrade process so that it does not cause
unexpected inconvenience to users of the various libraries
on Hackage.

Regards,
Yitz

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


Re: [Haskell-cafe] How to ensure code executes in the context of a specific OS thread?

2011-07-12 Thread Simon Marlow

On 07/07/2011 08:41, Simon Marlow wrote:

On 06/07/2011 21:19, Jason Dagit wrote:

On Wed, Jul 6, 2011 at 12:52 PM, Simon Marlowmarlo...@gmail.com wrote:

On 06/07/11 17:14, David Barbour wrote:



On Wed, Jul 6, 2011 at 8:09 AM, Simon Marlowmarlo...@gmail.com
mailto:marlo...@gmail.com wrote:

On 06/07/2011 15:42, Jason Dagit wrote:

How can I make sure my library works from GHC (with arbitrary

user threads) and from GHCI?

Right, but usually the way this is implemented is with some
cooperation from the main thread. [...] So you can't just do this
from a library - the main thread has to be in on the game. I suppose
you might wonder whether the GHC RTS could implement runInMainThread
by preempting the main thread and running some different code on it.
[...]


I think the real issue is that GHC has a different behavior than GHCi,
and I think this causes a lot of difficulties for people working on GUI
and other FFI integration.

Perhaps it would be possible to reverse the default roles of threads in
GHCi: the main thread run user commands, and a second bound thread will
process user interrupts and such.


Well, GHCi has no main, so it doesn't seem surprising (to me) that it's
different.

However, if -fno-ghci-sandbox doesn't have any drawbacks we could
just make
it the default. I don't actually remember why we run each statement in a
new thread, I think it just seemed like a prudent thing to do.


+1 for this change. I'm not sure how we would know if there are
drawbacks.


Now that I think about it, the original reason may have been that if the
computation grows a large stack, having it in a separate thread means
GHCi can recover the memory. However we have been able to recover stack
memory for some time now, so that is no longer an issue.


I discovered the real reason we run statements in a separate thread: the 
GHCi debugger.  If the computation stops at a breakpoint, then we have 
to save the context and resume GHCi, which can only be done if the 
computation was running in a separate thread.


The way things are arranged right now, each stopped computation gets a 
different thread.  What you want is for all these to be on the main 
thread.  It might be possible to arrange this, but it would require some 
non-trivial reorganisation in the implementation of interactive 
evaluation (compiler/main/InteractiveEval.hs).  I'm going to have to 
leave this for now, sorry.  In the meantime you'll still be able to use 
-fno-ghci-sandbox, but the debugging features in GHCi will be disabled.


Cheers,
Simon




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


[Haskell-cafe] ANN: unification-fd: simple generic unification

2011-07-12 Thread wren ng thornton

-- unification-fd 0.5.0


The unification-fd package offers generic functions for first-order
structural unification (think Prolog programming or Hindley--Milner type
inference). I've had this laying around for a few years, so I figured I
might as well publish it.

An effort has been made to try to make this package as portable as
possible. However, because it uses the ST monad and the mtl-2 package it
can't be H98 nor H2010. However, it only uses the following common
extensions which should be well supported[1]:

Rank2Types
MultiParamTypeClasses
FunctionalDependencies
FlexibleContexts
FlexibleInstances
UndecidableInstances

[1] With the exception of fundeps which are notoriously difficult to
implement. However, they are supported by Hugs and GHC 6.6, so I don't
feel bad about requiring it. Once the API stabilizes a bit more I plan to
release a unification-tf package which uses type families instead, for
those who feel type families are easier to implement or use.



-- Description


The unification API is generic in the type of the structures being unified
and in the implementation of unification variables, following the
two-level types pearl of Sheard (2001). This style mixes well with
Swierstra (2008), though an implementation of the latter is not included
in this package.

That is, all you have to do is define the functor whose fixed-point is the
recursive type you're interested in:

-- The non-recursive structure of terms
data S a = ...

-- The recursive term type
type PureTerm = Fix S

And then provide an instance for Unifiable, where zipMatch performs one
level of equality testing for terms and returns the one-level spine filled
with pairs of subterms to be recursively checked (or Nothing if this level
doesn't match).

class (Traversable t) = Unifiable t where
zipMatch :: t a - t b - Maybe (t (a,b))

The choice of which variable implementation to use is defined by similarly
simple classes Variable and BindingMonad. We store the variable bindings
in a monad, for obvious reasons. In case it's not obvious, see Dijkstra et
al. (2008) for benchmarks demonstrating the cost of naively applying
bindings eagerly.

There are currently two implementations of variables provided: one based
on STRefs, and another based on a state monad carrying an IntMap. The
former has the benefit of O(1) access time, but the latter is plenty fast
and has the benefit of supporting backtracking. Backtracking itself is
provided by the logict package and is described in Kiselyov et al. (2005).


In addition to this modularity, unification-fd implements a number of
optimizations over the algorithm presented in Sheard (2001)--- which is
also the algorithm presented in Cardelli (1987).

* Their implementation uses path compression, which we retain. Though we
modify the compression algorithm in order to make sharing observable.

* In addition, we perform aggressive opportunistic observable sharing, a
potentially novel method of introducing even more sharing than is provided
by the monadic bindings. Basically, we make it so that we can use the
observable sharing provided by the previous optimization as much as
possible (without introducing any new variables).

* And we remove the notoriously expensive occurs-check, replacing it with
visited-sets (which detect cyclic terms more lazily and without the
asymptotic overhead of the occurs-check). A variant of unification which
retains the occurs-check is also provided, in case you really need to fail
fast for some reason.

* Finally, a highly experimental branch of the API performs *weighted*
path compression, which is asymptotically optimal. Unfortunately, the
current implementation is quite a bit uglier than the unweighted version,
and I haven't had a chance to perform benchmarks to see how the constant
factors compare. Hence moving it to an experimental branch.


I haven't had a chance to fully debug these optimizations, though they
pass some of the obvious tests. If you find any bugs, do be sure to let me
know. Also, if you happen to have a test suite or benchmark suite for
unification on hand, I'd love to get a copy.



-- References


Luca Cardelli (1987) /Basic polymorphic typechecking/.
Science of Computer Programming, 8(2):147--172.

Atze Dijkstra, Arie Middelkoop, S. Doaitse Swierstra (2008)
/Efficient Functional Unification and Substitution/,
Technical Report UU-CS-2008-027, Utrecht University.
http://www.cs.uu.nl/research/techreps/repo/CS-2008/2008-027.pdf

Oleg Kiselyov, Chung-chieh Shan, Daniel P. Friedman, and
Amr Sabry (2005) /Backtracking, Interleaving, and/
/Terminating Monad Transformers/, ICFP.

[Haskell-cafe] Fixing Performance Leaks at the Type Level

2011-07-12 Thread Gershom Bazerman
This post is in literate Haskell. It describes how certain performance leaks 
are introduced in type level programming. These leaks do not affect program 
runtimes, but can cause compile times to grow drastically. They exist both with 
Functional Dependencies and Type Families, but are currently worse with the 
former, and have grown worse with the new constraint solver in GHC 7. It is 
intended both as a guide to those encountering these issues, and as a 
motivation for the GHC development team to address such issues as the 
constraint solver is developed and improved. 

 {-# OPTIONS_GHC -fcontext-stack=1000 #-} 
 {-# LANGUAGE FlexibleContexts, FlexibleInstances, FunctionalDependencies, 
 MultiParamTypeClasses, OverlappingInstances, TypeSynonymInstances, 
 TypeOperators, UndecidableInstances, TypeFamilies #-} 
 module TypePerformance where 

Our running example, for simplicity's sake, is a type-level map of a single 
function. For reference, here is the code for a simple value-level map of a 
single function. 

 vfoo = id 
 mapfoo (x : xs) = vfoo x : mapfoo xs 
 mapfoo [] = [] 

Because Haskell is a lazy language, this runs in O(n) time and constant stack. 

We now lift map to the type level, to operate over HLists. 

First, the basic HList types 

 infixr 3 :* 
 data x :* xs = x :* xs deriving Show 
 data HNil = HNil deriving Show 

Next, a large boring HList 

 -- Adds ten cells 
 addData x = i :* i :* d :* d :* s :* 
 i :* i :* d :* d :* s :* 
 x 
 where i = 1 :: Int 
   d = 1 :: Double 
   s =  
 
 -- Has 70 cells. 
 sampleData = addData $ addData $ addData $ addData $ addData $ 
  addData $ addData $ 
  HNil 

Next, a simple polymorphic function to map 

 class Foo x y | x - y 
 where foo :: x - y 
   foo = undefined 

 instance Foo Int Double 
 instance Foo Double Int 
 instance Foo String String 

Now, our map 

 class HMapFoo1 as bs | as - bs where 
 hMapFoo1 :: as - bs 
 
 instance (Foo a b, HMapFoo1 as bs) = HMapFoo1 (a :* as) (b :* bs) where 
 hMapFoo1 (x :* xs) = foo x :* hMapFoo1 xs 
 
 instance HMapFoo1 HNil HNil where 
 hMapFoo1 _ = HNil 

If we enable the following line, compilation time is ~ 9 seconds. 

   testHMapFoo1 = hMapFoo1 sampleData 

Furthermore, playing with the size of sampleData, we see that the time spent in 
compilation is superlinear -- each additional cell costs a greater amount of 
time. This is because while Haskell is lazy at the value level, it is strict at 
the type level. Therefore, just as in a strict language, HMapFoo1's cost grows 
O(n^2) because even as we induct over the as, we build up a stack of bs. Just 
as in a strict language, the solution is to make hMapFoo tail recursive through 
introducing an accumulator. This also reverses the hlist, but never mind that. 

 class HMapFoo2 acc as bs | acc as - bs where 
 hMapFoo2 :: acc - as - bs 
 
 instance (Foo a b, HMapFoo2 (b :* bs) as res) = HMapFoo2 bs (a :* as) res 
 where 
 hMapFoo2 acc (x :* xs) = hMapFoo2 (foo x :* acc) xs 
 
 instance HMapFoo2 acc HNil acc where 
 hMapFoo2 acc _ = acc 

If we enable the following line, compilation time is a much more satisfying 
~0.5s. 

   testHMapFoo2 = hMapFoo2 HNil sampleData 

But wait, there's trouble on the horizon! Consider the following version: 

 class HMapFoo3 acc as bs | acc as - bs where 
 hMapFoo3 :: acc - as - bs 
 
 instance (HMapFoo3 (b :* bs) as res, Foo a b) = HMapFoo3 bs (a :* as) res 
 where 
 hMapFoo3 acc (x :* xs) = hMapFoo3 (foo x :* acc) xs 
 
 instance HMapFoo3 acc HNil acc where 
 hMapFoo3 acc _ = acc 

The only difference between hMapFoo2 and hMapFoo3 is that the order of 
constraints on the inductive case has been reversed, with the recursive 
constraint first and the immediately checkable constraint second. Now, if we 
enable the following line, compilation time rockets to ~6s! 

   testHMapFoo3 = hMapFoo3 HNil sampleData 

Slowdowns such as those described here are not a purely hypothetical issue, but 
have caused real problems in production code. The example given above is fairly 
simple. The constraints used are minimal and easily checked. In real programs, 
the constraints are more difficult, increasing constant factors significantly. 
These constant factors, combined with unexpected algorithmic slowdowns due to 
the type inference engine, can lead (and have lead) to compilation times of 
HList-style code becoming deeply unwieldy-to-unusable, and can lead (and have 
lead) to this occuring only well after this code has been introduced and used 
on smaller cases without trouble. 

The constraint solver should certainly be smart enough to reduce the compile 
times of HMapFoo3 to those of HMapFoo2. In fact, with type families, the there 
is no difference (see below). Could the compiler be smart enough to do the same 
for HMapFoo1? I'm not sure. Certainly, it could at least knock down its own 
constant factors a bit, even if it 

Re: [Haskell-cafe] Fixing Performance Leaks at the Type Level

2011-07-12 Thread Dimitrios Vytiniotis

Dear Gershom,
Just to say many thanks for the extremely useful test cases! We will 
investigate further. 
Best, 
Dimitris



 -Original Message-
 From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
 users-boun...@haskell.org] On Behalf Of Gershom Bazerman
 Sent: 12 July 2011 13:18
 To: Haskell Cafe
 Cc: glasgow-haskell-us...@haskell.org
 Subject: Fixing Performance Leaks at the Type Level
 
 This post is in literate Haskell. It describes how certain performance leaks 
 are
 introduced in type level programming. These leaks do not affect program
 runtimes, but can cause compile times to grow drastically. They exist both
 with Functional Dependencies and Type Families, but are currently worse
 with the former, and have grown worse with the new constraint solver in
 GHC 7. It is intended both as a guide to those encountering these issues, and
 as a motivation for the GHC development team to address such issues as the
 constraint solver is developed and improved.
 
  {-# OPTIONS_GHC -fcontext-stack=1000 #-} {-# LANGUAGE
  FlexibleContexts, FlexibleInstances, FunctionalDependencies,
  MultiParamTypeClasses, OverlappingInstances, TypeSynonymInstances,
  TypeOperators, UndecidableInstances, TypeFamilies #-} module
  TypePerformance where
 
 Our running example, for simplicity's sake, is a type-level map of a single
 function. For reference, here is the code for a simple value-level map of a
 single function.
 
  vfoo = id
  mapfoo (x : xs) = vfoo x : mapfoo xs
  mapfoo [] = []
 
 Because Haskell is a lazy language, this runs in O(n) time and constant stack.
 
 We now lift map to the type level, to operate over HLists.
 
 First, the basic HList types
 
  infixr 3 :*
  data x :* xs = x :* xs deriving Show
  data HNil = HNil deriving Show
 
 Next, a large boring HList
 
  -- Adds ten cells
  addData x = i :* i :* d :* d :* s :*
  i :* i :* d :* d :* s :*
  x
  where i = 1 :: Int
d = 1 :: Double
s = 
 
  -- Has 70 cells.
  sampleData = addData $ addData $ addData $ addData $ addData $
   addData $ addData $
   HNil
 
 Next, a simple polymorphic function to map
 
  class Foo x y | x - y
  where foo :: x - y
foo = undefined
 
  instance Foo Int Double
  instance Foo Double Int
  instance Foo String String
 
 Now, our map
 
  class HMapFoo1 as bs | as - bs where
  hMapFoo1 :: as - bs
 
  instance (Foo a b, HMapFoo1 as bs) = HMapFoo1 (a :* as) (b :* bs) where
  hMapFoo1 (x :* xs) = foo x :* hMapFoo1 xs
 
  instance HMapFoo1 HNil HNil where
  hMapFoo1 _ = HNil
 
 If we enable the following line, compilation time is ~ 9 seconds.
 
testHMapFoo1 = hMapFoo1 sampleData
 
 Furthermore, playing with the size of sampleData, we see that the time
 spent in compilation is superlinear -- each additional cell costs a greater
 amount of time. This is because while Haskell is lazy at the value level, it 
 is
 strict at the type level. Therefore, just as in a strict language, HMapFoo1's
 cost grows O(n^2) because even as we induct over the as, we build up a
 stack of bs. Just as in a strict language, the solution is to make hMapFoo 
 tail
 recursive through introducing an accumulator. This also reverses the hlist, 
 but
 never mind that.
 
  class HMapFoo2 acc as bs | acc as - bs where
  hMapFoo2 :: acc - as - bs
 
  instance (Foo a b, HMapFoo2 (b :* bs) as res) = HMapFoo2 bs (a :* as) res
 where
  hMapFoo2 acc (x :* xs) = hMapFoo2 (foo x :* acc) xs
 
  instance HMapFoo2 acc HNil acc where
  hMapFoo2 acc _ = acc
 
 If we enable the following line, compilation time is a much more satisfying
 ~0.5s.
 
testHMapFoo2 = hMapFoo2 HNil sampleData
 
 But wait, there's trouble on the horizon! Consider the following version:
 
  class HMapFoo3 acc as bs | acc as - bs where
  hMapFoo3 :: acc - as - bs
 
  instance (HMapFoo3 (b :* bs) as res, Foo a b) = HMapFoo3 bs (a :* as) res
 where
  hMapFoo3 acc (x :* xs) = hMapFoo3 (foo x :* acc) xs
 
  instance HMapFoo3 acc HNil acc where
  hMapFoo3 acc _ = acc
 
 The only difference between hMapFoo2 and hMapFoo3 is that the order of
 constraints on the inductive case has been reversed, with the recursive
 constraint first and the immediately checkable constraint second. Now, if we
 enable the following line, compilation time rockets to ~6s!
 
testHMapFoo3 = hMapFoo3 HNil sampleData
 
 Slowdowns such as those described here are not a purely hypothetical issue,
 but have caused real problems in production code. The example given above
 is fairly simple. The constraints used are minimal and easily checked. In real
 programs, the constraints are more difficult, increasing constant factors
 significantly. These constant factors, combined with unexpected algorithmic
 slowdowns due to the type inference engine, can lead (and have lead) to
 compilation times of HList-style code becoming deeply unwieldy-to-
 unusable, and can lead (and have lead) to 

Re: [Haskell-cafe] The Typeable class is changing

2011-07-12 Thread Felipe Almeida Lessa
On Tue, Jul 12, 2011 at 5:30 AM, Jon Fairbairn
jon.fairba...@cl.cam.ac.uk wrote:
 So, this change will hit me for two different reasons, and sadly
 involve using CPP to control how things are compiled.

 so that shouldn’t be necessary.

CPP will be necessary, since we want to support older versions of the
base library as well (which obviously don't have myTycon3).

-- 
Felipe.

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


[Haskell-cafe] Type checking oddity -- maybe my own confusion

2011-07-12 Thread Ryan Newton
Hi all,

Is there something wrong with the code below?  My anticipation was that the
type of test would include the class constraint, because it uses the
Assign constructor.  But if you load this code in GHCI you can see that the
inferred type was test :: E m - E m.

Thanks,
  -Ryan


{-# LANGUAGE GADTs #-}

class AssignCap m
data PureT
data IOT
instance AssignCap IOT

data E m where
  Assign  :: AssignCap m = V - E m - E m - E m
  Varref  :: V - E m
-- ...

type V = String

-- I expected the following type but am not getting it:
-- test :: AssignCap m = E m - E m
test x =
  case x of
   Assign v e1 e2 - Assign v e1 e2
-- And this is the same:
   Assign v e1 e2 - x
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type checking oddity -- maybe my own confusion

2011-07-12 Thread Dimitrios Vytiniotis
Hi Ryan,

Think of AssignCap as an extra argument packaged up with the Assign 
constructor. When
you pattern match against Assign you make the AssignCap constraint *available* 
for use in
the RHS of the pattern; so there's no need for quantification, you already have 
the constraint
you want packaged inside your argument. (Back in the old times when GHC did not 
implement
implication constraints maybe you'd get the type you say). Does that help?

Thanks
d-


From: haskell-cafe-boun...@haskell.org 
[mailto:haskell-cafe-boun...@haskell.org] On Behalf Of Ryan Newton
Sent: 12 July 2011 16:02
To: Haskell Cafe
Subject: [Haskell-cafe] Type checking oddity -- maybe my own confusion

Hi all,

Is there something wrong with the code below?  My anticipation was that the 
type of test would include the class constraint, because it uses the Assign 
constructor.  But if you load this code in GHCI you can see that the inferred 
type was test :: E m - E m.

Thanks,
  -Ryan


{-# LANGUAGE GADTs #-}

class AssignCap m
data PureT
data IOT
instance AssignCap IOT

data E m where
  Assign  :: AssignCap m = V - E m - E m - E m
  Varref  :: V - E m
-- ...

type V = String

-- I expected the following type but am not getting it:
-- test :: AssignCap m = E m - E m
test x =
  case x of
   Assign v e1 e2 - Assign v e1 e2
-- And this is the same:
   Assign v e1 e2 - x

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


Re: [Haskell-cafe] How to ensure code executes in the context of a specific OS thread?

2011-07-12 Thread David Barbour
On Tue, Jul 12, 2011 at 2:58 AM, Simon Marlow marlo...@gmail.com wrote:

 I discovered the real reason we run statements in a separate thread: the
 GHCi debugger.  If the computation stops at a breakpoint, then we have to
 save the context and resume GHCi, which can only be done if the computation
 was running in a separate thread.

 The way things are arranged right now, each stopped computation gets a
 different thread.  What you want is for all these to be on the main thread.
  It might be possible to arrange this, but it would require some non-trivial
 reorganisation in the implementation of interactive evaluation
 (compiler/main/**InteractiveEval.hs).  I'm going to have to leave this for
 now, sorry.  In the meantime you'll still be able to use -fno-ghci-sandbox,
 but the debugging features in GHCi will be disabled.

 Cheers,
Simon


Thanks for looking into it, Simon.

Regards,

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


Re: [Haskell-cafe] Type checking oddity -- maybe my own confusion

2011-07-12 Thread Steffen Schuldenzucker

On 07/12/2011 05:01 PM, Ryan Newton wrote:

Hi all,

Is there something wrong with the code below?  My anticipation was that
the type of test would include the class constraint, because it uses
the Assign constructor.  But if you load this code in GHCI you can see
that the inferred type was test :: E m - E m.


When I complete the pattern match in 'test', it might look like this:

test x = case x of
Assign v e1 e2 - x
Varref v - x

(which is just id :: E m - E m). Of course, we want to be able to write

 test (Varref v)

for any v :: V, and match the second case. But as 'Varref' does not add 
an AssignCap constraint, 'test' must not either.


Hope that helps. Steffen



Thanks,
   -Ryan


{-# LANGUAGE GADTs #-}

class AssignCap m
data PureT
data IOT
instance AssignCap IOT

data E m where
   Assign  :: AssignCap m = V - E m - E m - E m
   Varref  :: V - E m
-- ...

type V = String

-- I expected the following type but am not getting it:
-- test :: AssignCap m = E m - E m
test x =
   case x of
Assign v e1 e2 - Assign v e1 e2
-- And this is the same:
Assign v e1 e2 - x



___
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] Baffling Hackage build log

2011-07-12 Thread wren ng thornton
As a dutiful package maintainer I just checked to make sure unification-fd
built correctly on Hackage. Unfortunately it didn't, and it gives this
inscrutable error log:

cabal: There is no package named unification-fd. Perhaps you need to run
'cabal update' first?

Something awry on Hackage?

-- 
Live well,
~wren


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


Re: [Haskell-cafe] Baffling Hackage build log

2011-07-12 Thread Jack Henahan
No problems here (OS X.6). Baffling, indeed.

On Jul 12, 2011, at 7:58 PM, wren ng thornton wrote:

 As a dutiful package maintainer I just checked to make sure unification-fd
 built correctly on Hackage. Unfortunately it didn't, and it gives this
 inscrutable error log:
 
cabal: There is no package named unification-fd. Perhaps you need to run
'cabal update' first?
 
 Something awry on Hackage?
 
 -- 
 Live well,
 ~wren
 
 
 ___
 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] Why is (+++) not a functor?

2011-07-12 Thread Felipe Almeida Lessa
Hey! =)

ArrowChoice's (+++) documentation [1] says that this is in general
not a functor [1].  What does it mean for (+++) to be or not to be a
functor?

Cheers,

[1] 
http://hackage.haskell.org/packages/archive/base/4.3.1.0/doc/html/Control-Arrow.html#v:-43--43--43-

-- 
Felipe.

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


Re: [Haskell-cafe] Why is (+++) not a functor?

2011-07-12 Thread David Barbour
On Tue, Jul 12, 2011 at 6:55 PM, Felipe Almeida Lessa 
felipe.le...@gmail.com wrote:

 ArrowChoice's (+++) documentation [1] says that this is in general
 not a functor [1].  What does it mean for (+++) to be or not to be a
 functor?


The same note is made for (***). If you review Ross Patterson's paper [1],
you'll see a note: Note that *** does not in general preserve composition;
for example, the order in which effects occur is significant. I expect the
note in Control.Arrow is an oblique reference to this 'fact'.

[1] http://www.soi.city.ac.uk/~ross/papers/notation.pdf
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type checking oddity -- maybe my own confusion

2011-07-12 Thread Ryan Newton
Thanks, that does help.  Very clear description.

Any good ideas about how to tweak my example to do what was intended ;-)?

The desired goal was that everywhere I construct a value using the Assign
constructor, that the resulting value's type to be tainted by the AssignCap
constraint.

Actually... to go a bit further, I thought there was some way to arrange
this so that, upon GHC type-checking the case statement, it would realize
that certain cases are forbidden based on the type, and would consider the
pattern match complete without them (or issue an error if they are present).

Thanks,
  -Ryan

On Tue, Jul 12, 2011 at 11:17 AM, Dimitrios Vytiniotis 
dimit...@microsoft.com wrote:

  Hi Ryan, 

 ** **

 Think of AssignCap as an extra argument packaged up with the Assign
 constructor. When 

 you pattern match against Assign you make the AssignCap constraint **
 available** for use in

 the RHS of the pattern; so there’s no need for quantification, you already
 have the constraint

 you want packaged inside your argument. (Back in the old times when GHC did
 not implement 

 implication constraints maybe you’d get the type you say). Does that help?
 

 ** **

 Thanks

 d-

 ** **

 ** **

 *From:* haskell-cafe-boun...@haskell.org [mailto:
 haskell-cafe-boun...@haskell.org] *On Behalf Of *Ryan Newton
 *Sent:* 12 July 2011 16:02
 *To:* Haskell Cafe
 *Subject:* [Haskell-cafe] Type checking oddity -- maybe my own confusion**
 **

 ** **

 Hi all,

 ** **

 Is there something wrong with the code below?  My anticipation was that the
 type of test would include the class constraint, because it uses the
 Assign constructor.  But if you load this code in GHCI you can see that the
 inferred type was test :: E m - E m.

 ** **

 Thanks,

   -Ryan

 ** **

 ** **

 {-# LANGUAGE GADTs #-}

 ** **

 class AssignCap m 

 data PureT  

 data IOT  

 instance AssignCap IOT 

 ** **

 data E m where 

   Assign  :: AssignCap m = V - E m - E m - E m

   Varref  :: V - E m

 -- ...

 ** **

 type V = String

 ** **

 -- I expected the following type but am not getting it:

 -- test :: AssignCap m = E m - E m

 test x = 

   case x of 

Assign v e1 e2 - Assign v e1 e2

 -- And this is the same:

Assign v e1 e2 - x

 ** **

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