[Haskell] ANNOUNCE: jhc 0.6.0 Haskell Compiler

2009-03-16 Thread John Meacham
Hi, I am pleased to announce jhc 0.6.0, It has been a long time since an
official release, so there have been a lot of changes. Jhc is an
optimizing haskell compiler that focuses on creating fast and portable
code. Jhc is still mainly of interest to jhc hackers and developers than
the general haskell public, but it is starting to see use in embedded
development with haskell so I decided to make more public announcements
of major releases in the future.

some links:

The jhc homepage:
http://repetae.net/computer/jhc/

Installation Instructions:
http://repetae.net/computer/jhc/building.shtml

The jhc manual:
http://repetae.net/computer/jhc/manual.html

And I am happy to announce, there is now a yum repository*  for jhc and my
other projects (such as DrIFT), so if you use an rpm based linux
distribution, you can keep up to date with jhc official releases by
doing:

; rpm -i  http://repetae.net/yum/repetae-repo-1.0-3.noarch.rpm 
; yum install jhc


A couple recent changes:

jhc now comes bundled with the 'containers' and 'applicative' library
making it much easier to compile many haskell programs out there. 
(Data.Graph, Data.IntMap, Data.IntSet, Data.Map, Data.Sequence,
Data.Set, Data.Tree, Control.Applicative, Control.Arrow,
Control.Category, Data.Foldable, Data.Traversable)

signifigant speed and resource usage improvements in compilation time.

transparent cross compilation support for creating windows programs on a
unix box. (or iPhone/Nokia Tablet/etc..)


If you are interested in jhc development, please sign up on the jhc
mailing list here: http://www.haskell.org/mailman/listinfo/jhc

John

* I would love to get proper 'deb's and BSD packages built also
  automatically, if anyone wants to help with this, please join the list
  and let us know.


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] indirectly recursive dictionaries

2009-03-16 Thread Ralf Laemmel
{-

Recursive instance heads as in ...
 instance C0 (x,Bool) => C0 x
... are Ok if we allow for typechecking scheme as described in "SYB with class".
The main idea is to assume C0 x in proving the preconditions of the
body of the clause.
This is also works for mutual recursion among type classes and
instances to the extent exercised in ditto paper.

What about the below example though?
Here recursion detours through an extra class in a way that leads to
nonterminating typechecking with GHC 6.10.1.
Does anyone agree that a constraint resolution scheme like the one
mentioned could be reasonably expected to cover this case?

Regards,
Ralf

-}

{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-overlapping-instances #-}
{-# OPTIONS -fallow-undecidable-instances #-}

-- Direct recursion terminates (typechecking-wise)

class C0 x
 where
 m0 :: x -> ()
 m0 = const undefined

instance (C0 x, C0 y) => C0 (x,y)
instance C0 Bool
instance C0 (x,Bool) => C0 x

foo :: ()
foo = m0 (1::Int)


-- Indirect recursion does not terminate (typechecking-wise)

class C1 x
 where
 m1 :: x -> ()
 m1 = const undefined

instance (C1 x, C1 y) => C1 (x,y)
instance C1 Bool
instance (C2 x y, C1 (y,Bool)) => C1 x

class C2 x y | x -> y
instance C2 Int Int

-- It is this declaration that causes nontermination of typechecking.
bar :: ()
bar = m1 (1::Int)
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Re: scoped type variables

2009-03-16 Thread Norman Ramsey
[Opening discussion to broader audience: I asked Simon PJ about
scoped type variables and type abbreviations]

 > | With scoped type variables, it would be useful to be able to define
 > | a type abbreviation in a where clause, so that the scoped
 > | type variable could be used on a right-hand side.  Apparently
 > | this wasn't done.  Was there any technical reason why not?
 >
 > Would you care to give an example? Do you mean
 > f x = e where a = Int

No.  I give an example below, but I've just spent 10 minutes grubbing
through the Haskell 98 Report so I can phrase the question more
precisely:

  Given the extension to scoped type variables, I believe that the
  'type' abbreviation declaration should have been 'promoted' from
  syntactic category 'topdecl' to syntactic category 'decl', because
  it is convenient and useful to be able to exploit a scoped type
  variable in a type abbreviation.  Was this possibility simply
  overlooked, or was a deliberate choice made not to do it?

Here is a synopsis of code I would like to write:

  solve :: forall m l a . Graph m l -> Fuel -> DFM a (a, Fuel)
  solve = solveGraph
where
   -- in the defintions below, type variable 'a' is free 
   -- on the RHS but is bound by the forall above
   type FactKont b = Graph m l -> a -> Fuel -> DFM a b
   type FuelKont b = Graph m l ->  Fuel -> DFM a b

   solveMid  :: m -> FactKont b -> FactKont b
   solveLast :: l -> FuelKont b -> FactKont b 
 ...

For my sanity I'd like to define type abbreviations that refer to 'm'
and 'l' also...

Under the current regime, I'm forced to do what amounts to lambda
lifting on the type abbreviations.  Not only does this lead to a
extra type parameters which distract from the main event, but in
floating the type abbreviation out to top level, I am forced to choose
a unique name for it, which I might prefer not to do if the same
module contains several similar functions with similar (but not
identical) type abbreviations.  

Of course the naming issue arises even in Haskell 98, but the ability
to bring type variables into scope in a 'where' clause adds urgency.

 > There are lots of design issues.  For example, in GHC today, a scoped type
 > variable stands for a type *variable* not for a *type*.  I took the other
 > approach initially, but I think this is better

I know this distinction is important in instance declarations.
Presumably it also means that the scoped type variable can unify with
something else during type inference?  I fear that without seeing some
formalism I can't be too sure what's going on---is there a technical
report somewhere that explains the distinction?

In any case, I hope this question is orthogonal to the problem of
permitting a type declaration as a 'decl' in a where clause and not a
mere lonely 'topdecl'.   Is anybody else keen to have this ability?


Norman

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


[Haskell] ANN: The Monad.Reader (13)

2009-03-16 Thread Wouter Swierstra
I am pleased to announce that a new issue of The Monad.Reader is now  
available:


 http://www.haskell.org/haskellwiki/The_Monad.Reader

The Monad.Reader is a quarterly magazine about functional programming.

Issue 13 consists of the following four articles:

* Stephen Hicks
Rapid Prototyping in TEX

* Brent Yorgey
The Typeclassopedia

* Chris Eidhof, Eelco Lempsink
Book Review: "Real World Haskell"

* Derek Elkins
Calculating Monads with Category Theory

Special thanks to Ashley Yakeley for his help with publishing The  
Monad.Reader on the Haskell wiki.


If you'd like to write something for the next issue of The  
Monad.Reader, please get in touch. I haven't fixed the deadline for  
the next issue, but it should be mid-May or thereabouts.


  Wouter


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