Re: GHC ARM builds?

2012-07-12 Thread Erik de Castro Lopo
Karel Gardas wrote:

 Last note: GHC/ARM depends on GHC's specific calling convention support 
 in LLVM. Unfortunately for ARM platform it was merged into LLVM 3.0, but 
 not into LLVM HEAD (at that time), so LLVM 3.1 doesn't support GHC/ARM 
 at all. I'm trying to resubmit the support for inclusion here: 
 http://lists.cs.uiuc.edu/pipermail/llvmdev/2012-June/051119.html -- but 
 it's still not merged in.

Karel, its probably time you pinged them again asking for that to be
merged :-).

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

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Call to arms: lambda-case is stuck and needs your help

2012-07-12 Thread Mikhail Vorozhtsov

On 07/12/2012 04:27 AM, Iavor Diatchki wrote:

Hello,
I am late to the discussion and this is not entirely on topic, for which
I apologize, but I like the multi-branch case syntax someone mentioned
earlier:

Writing:

  case
| p1 - e1
| p2 - e2
| ...

desugars to:

  case () of
_ | p1 - e2
  | p2 - e2
  | ...

-Iavor
PS:  I think it also makes sense to use if instead of case for this.
  Either way,  I find myself writing these kind of cases quite often, so
having the sugar would be nice.

See [1]. I plan to implement it after lambda-case goes in.

[1] http://hackage.haskell.org/trac/haskell-prime/wiki/MultiWayIf

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Type error when deriving Generic for an associated data type

2012-07-12 Thread Bas van Dijk
Hi,

I'm hitting on an issue when deriving Generic for an associated data type:

{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics

class Foo a where
data T a :: *

instance Foo Int where
data T Int = Bla deriving Generic

Couldn't match type `Rep (T Int)' with `M1 t0 t1 (M1 t2 t3 U1)'
Expected type: Rep (T Int) x
  Actual type: M1 t0 t1 (M1 t2 t3 U1) x
In the pattern: M1 (M1 U1)
In an equation for `to': to (M1 (M1 U1)) = Bla
In the instance declaration for `Generic (T Int)'

The GHC trac seems to be down. Is this a known issue?

Cheers,

Bas

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Type error when deriving Generic for an associated data type

2012-07-12 Thread Andres Löh
Hi Bas.

 I'm hitting on an issue when deriving Generic for an associated data type:

[...]

Your example compiles for me with HEAD (but fails with 7.4.1 and
7.4.2, yes). I've not tested if it also works.

Cheers,
  Andres

-- 
Andres Löh, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Type error when deriving Generic for an associated data type

2012-07-12 Thread José Pedro Magalhães
Hi Bas,

On Thu, Jul 12, 2012 at 11:27 AM, Bas van Dijk v.dijk@gmail.com wrote:

 Hi,

 I'm hitting on an issue when deriving Generic for an associated data type:

 ...

 The GHC trac seems to be down. Is this a known issue?


Yes, and it's supposed to be fixed in HEAD. Can you try it with HEAD?


Thanks,
Pedro
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: “Ambiguous type variable in the constraint” error in rewrite rule

2012-07-12 Thread Simon Peyton-Jones
The error message is unhelpful.  HEAD reports this:

Could not deduce (Monoid w) arising from a use of `g'
from the context (Monad (WriterT w Identity))
  bound by the RULE f-g at Foo.hs:14:3-14
Possible fix: add (Monoid w) to the context of the RULE f-g
In the expression: g
When checking the transformation rule f-g

And that is quite right.  On the LHS you have an application
f (WriterT w Identity) d
  where d :: Monad (WriterT w Identity)

Recall that Writer w = WriterT w Identity.

For the rewrite to work you have to rewrite this to
g w d'
  where
d' :: Monoid w

Well, how can you get a Monoid w dictionary from a Monad (WriterT w Identity)?


I was surprised that the SPECIALISE pragma worked, but here's what it does (you 
can see with -ddump-rules):


 Tidy Core rules 
SPEC Foo.f [ALWAYS]
forall (@ a) (@ w) ($dMonoid :: Data.Monoid.Monoid w).
  Foo.f @ a
@ (Control.Monad.Trans.Writer.Strict.WriterT
 w Data.Functor.Identity.Identity)
(Control.Monad.Trans.Writer.Strict.$fMonadWriterT
   @ w
   @ Data.Functor.Identity.Identity
   $dMonoid
   Data.Functor.Identity.$fMonadIdentity)
  = Foo.f_f @ a @ w $dMonoid

Ah!  This rule will only match if the LHS is

f (WriterT w Identity) ($fMonadWriterT w Identity dm $fMonadIdentity)

So it's a nested pattern match.  That makes the LHS match less often; namely 
only when the dictionary argument to 'f' is an application of $fMonadWriterT, 
the function that arises from the instance decl
instance (Monoid w, Monad m) = Monad (WriterT w m) where

In exchange for matching less often, we now do get access to the (Monoid w) 
argument.

It is odd that this is inconsistent, I agree.  Here is why. For a RULE, we must 
have a way to rewrite the LHS to an arbitrarily complicated RHS.  For a 
SPECIALISE pragma
SPECIALISE f :: spec_ty
where f's type is
f :: poly_ty
we simply ask whether poly_ty is more polymorphic than spec_ty; that is, 
whether f can appear in a context requiring a value of type spec_ty. If so, we 
see what arguments f would need to do that, and that's the LHS pattern.


So I hope that explains better what is happening.  If anyone can think of 
better behaviour, I'm open to suggestions!

Simon


| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-
| haskell-users-boun...@haskell.org] On Behalf Of Tsuyoshi Ito
| Sent: 11 July 2012 04:40
| To: glasgow-haskell-users@haskell.org
| Subject: “Ambiguous type variable in the constraint” error in rewrite
| rule
| 
| Hello,
| 
| Why does GHC 7.4.1 reject the rewrite rule in the following code?
| 
|  module Test where
| 
|  import Data.Monoid
|  import Control.Monad.Writer.Strict
| 
|  f :: Monad m = a - m a
|  f = return
| 
|  g :: Monoid w = a - Writer w a
|  g = return
| 
|  {-# RULES
|  f-g f = g
|#-}
| 
| On the line containing the rewrite rule, GHC shows the following error
| message:
| 
| Test.hs:13:12:
| Ambiguous type variable `w0' in the constraint:
|   (Monoid w0) arising from a use of `g'
| Probable fix: add a type signature that fixes these type
| variable(s)
| In the expression: g
| When checking the transformation rule f-g
| 
| Interestingly, the code compiles if the rewrite rule is replaced with
| the following SPECIALIZE pragma:
| 
|  {-# SPECIALIZE f :: Monoid w = a - Writer w a #-}
| 
| I find this strange because if I am not mistaken, this specialization
| is handled by using a rewrite rule of the same type as the one which
| GHC rejects.
| 
| The following ticket might be related, but I am not sure:
| Subclass Specialization in Rewrite Rules
| http://hackage.haskell.org/trac/ghc/ticket/6102
| 
| Best regards,
|   Tsuyoshi
| 
| ___
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Call to arms: lambda-case is stuck and needs your help

2012-07-12 Thread Cale Gibbard
Personally I don't see why everyone appears to prefer the syntax with
\ in it over just the obvious case section syntax which was originally
proposed.

case of { ... }

looks much better to me than

\case of { ... }

and the former makes sense to me as a simple extension of operator
sections to another part of the syntax.

Does anyone else agree?

On 6 July 2012 20:40, Chris Smith cdsm...@gmail.com wrote:
 Whoops, my earlier answer forgot to copy mailing lists... I would love to
 see \of, but I really don't think this is important enough to make case
 sometimes introduce layout and other times not.  If it's going to obfuscate
 the lexical syntax like that, I'd rather just stick with \x-case x of.

 On Jul 6, 2012 3:15 PM, Strake strake...@gmail.com wrote:

 On 05/07/2012, Mikhail Vorozhtsov mikhail.vorozht...@gmail.com wrote:
  Hi.
 
  After 21 months of occasional arguing the lambda-case proposal(s) is in
  danger of being buried under its own trac ticket comments. We need fresh
  blood to finally reach an agreement on the syntax. Read the wiki
  page[1], take a look at the ticket[2], vote and comment on the
  proposals!
 

 +1 for \ of multi-clause lambdas

 It looks like binding of to me, which it ain't, but it is nicely
 brief...

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


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


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Imported foreign functions should be strict

2012-07-12 Thread Favonia
I see. Thanks for the response! Perhaps it is better for the pretty
printer to print out U(S) instead?

Regards,
Favonia

On Tue, Jul 10, 2012 at 3:57 AM, Simon Marlow marlo...@gmail.com wrote:

 This is fine - it means the CDouble is unpacked into its unboxed Double#
 component.  An unboxed value is always represented by L in strictness
 signatures.

 Cheers,
 Simon

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Imported foreign functions should be strict

2012-07-12 Thread Johan Tibell
On Thu, Jul 12, 2012 at 11:29 AM, Favonia favo...@gmail.com wrote:
 I see. Thanks for the response! Perhaps it is better for the pretty
 printer to print out U(S) instead?

 Regards,
 Favonia

I'd love to see a cheat sheet documenting the strictness output. It
confuses me every time, even when I make the effort to read the source
code that generates the demand signature!

-- Johan

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Call to arms: lambda-case is stuck and needs your help

2012-07-12 Thread Daniel Trstenjak

On Thu, Jul 12, 2012 at 01:38:56PM -0400, Cale Gibbard wrote:
 Personally I don't see why everyone appears to prefer the syntax with
 \ in it over just the obvious case section syntax which was originally
 proposed.

I don't think that the 'case section syntax' is obvious, because I don't
see the similarity between a function definition and a partial function
application.

Always using '\' would be a visual hint for a function definition.


Greetings,
Daniel

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Call to arms: lambda-case is stuck and needs your help

2012-07-12 Thread Cale Gibbard
There are of course already lots of ways to create functions which
don't involve \

I mentioned sections (like (+1) desugaring to (\x - x + 1)) already,
and of course, one can partially apply or compose and transform other
functions without explicit lambdas.

We're not exactly talking about function definitions, so much as
expressions whose value happens to be a function. The point is just
that there are already a few other places in the syntax where the
omission of a value results in a function having the omitted value as
its parameter. At least to me, it seems natural to extend that pattern
in this case.

On 12 July 2012 15:03, Daniel Trstenjak daniel.trsten...@gmail.com wrote:

 On Thu, Jul 12, 2012 at 01:38:56PM -0400, Cale Gibbard wrote:
 Personally I don't see why everyone appears to prefer the syntax with
 \ in it over just the obvious case section syntax which was originally
 proposed.

 I don't think that the 'case section syntax' is obvious, because I don't
 see the similarity between a function definition and a partial function
 application.

 Always using '\' would be a visual hint for a function definition.


 Greetings,
 Daniel

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Common syntax for casing/matching (Re[2]: Call to arms: lambda-case is stuck and needs your help)

2012-07-12 Thread Bulat Ziganshin
Hello wagnerdm,

Thursday, July 5, 2012, 7:22:38 PM, you wrote:

 After 21 months of occasional arguing the lambda-case proposal(s) is

this reminded me old joke about PL/I: camel is the horse created by committee

i propose to return back and summarize all the requirements we have in
this area. and then try to develop global solution matching them all.
my summary of requirements follows:

 Now we have 3 ways to performing casing/matching:

 function definition:  f (Just x) (Just y) | x0 = ...  multi-line, 
 multi-parameter
 case statement: case ... of Just x | x0 - ... multi-line, single-parameter, 
 different syntax
 lambda: \(Just x) (Just y) - ...  single-line, multi-parameter, case-like 
 syntax

 What we probably need is to have common syntax for all 3 cases.



another interesting feature may be ruby-style matching defined by
execution of special function `match` instead of pattern matching:

switch var of
  1+1 - print var==2
  [5..10] - print var in [5..10]
  (20)   - print var20

where (var `match` (1+1)), (var `match` [5..10]), (var `match` (20)) is tested


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Common syntax for casing/matching (Re[2]: Call to arms: lambda-case is stuck and needs your help)

2012-07-12 Thread Twan van Laarhoven

On 2012-07-12 23:48, Bulat Ziganshin wrote:

another interesting feature may be ruby-style matching defined by
execution of special function `match` instead of pattern matching:

switch var of
   1+1 - print var==2
   [5..10] - print var in [5..10]
   (20)   - print var20

where (var `match` (1+1)), (var `match` [5..10]), (var `match` (20)) is tested


With view patterns you can write

case var of
((== 1+1) - True) - print var==2
((`elem` [5..10]) - True) - print var in [5..10]
(( 20)   - True) - print var20

Or you can just use guards, of course.


Twan

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to describe this bug?

2012-07-12 Thread Bardur Arantsson
On 07/10/2012 12:51 PM, malcolm.wallace wrote:
 Also, it is more likely to be a buggy instance of Eq, than a real loss
 of referential transparency.
 

Speaking of which... would it be remiss of me to mention the elephant in
the room, namely the Eq instance for Float?

AFAICT there is no possible way for a Float value to fulfill the Eq type
class requirements, so why is it an instance? (I'm thinking of the
weird Nan/Infinity behvaior primarily). Is there *really* such a huge
amount of code out there that relies on an Eq (or Ord for that matter!)
instance for Float? If so... shouldn't that code be fixed rather than
being subtly buggy?

Regards,


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Call to arms: lambda-case is stuck and needs your help

2012-07-12 Thread John Lask

On 13/07/2012 3:08 AM, Cale Gibbard wrote:

Personally I don't see why everyone appears to prefer the syntax with
\ in it over just the obvious case section syntax which was originally
proposed.

case of { ... }

looks much better to me than

\case of { ... }

and the former makes sense to me as a simple extension of operator
sections to another part of the syntax.

Does anyone else agree?



yes.
I prefer case of rather than \case of for aesthetic reasons.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC ARM builds?

2012-07-12 Thread Jens Petersen
On 12 July 2012 14:41, Jens Petersen j...@community.haskell.org wrote:
 ghc-7.4.2 should also build fine on Fedora 17 ARM.

Well, at least with Karel's armhfp patch...

 Just yum install ghc llvm first.

I tested building RC1 on Fedora ARM, and this is basically
the same srpm (src rpm package) for 7.4.2 including that patch:

 http://petersen.fedorapeople.org/ghc-7.4.2-5.1.fc17.src.rpm

which I believe should build cleanly on F17 with newer ghc-rpm-macros.

Jens

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users