Why GHC doesn't warn about LHS nullary-constructor pattern bindings?

2012-07-19 Thread Herbert Valerio Riedel
Hello,

Recently, I was a bit suprised that GHC didn't warn about useless
`where` definitions such as the following when using `-Wall` (and I
couldn't find a respective warning GHC CLI flag which would have enabled
reporting a warning in this case -- unless I missed it)

  module Foo where
  
  foo :: Int - Int
  foo n = n + 1
where
  Nothing = Just n

...wouldn't it be a sensible thing for GHC to warn in such cases
(i.e. when the LHS of a pattern binding is a nullary constructor), or is
there a useful application for this construct?

(In my original case, I ended up with such a dead construct after some
unsound code refactoring, and it would have helped me catch my error
earlier, if GHC would have pointed out that somethings fishy with my
code)

___
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 (fwd)

2012-07-19 Thread Henning Thielemann


I want to vote, too.

I am ok with all of

  case of

  \case

  \of

  \case of

For me single arguments are enough. We already have this restriction for 'case' 
and I can work around it simply by wrapping arguments in pairs temporarily (cf. 
curry $ \case ...).


I vote against LambdaIf, since if-then-else is already unnecessary and can be 
written by ifThenElse, and LambdaIf is just ifThenElse with different parameter 
order.


I vote against MultiCaseIf since it can be simply achieved by

ifThenElse b1 a1 $
ifThenElse b2 a2 $
ifThenElse b3 a3 $
a4

http://www.haskell.org/haskellwiki/Case

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


Re: Why GHC doesn't warn about LHS nullary-constructor pattern bindings?

2012-07-19 Thread Henning Thielemann


On Thu, 19 Jul 2012, Herbert Valerio Riedel wrote:


Recently, I was a bit suprised that GHC didn't warn about useless
`where` definitions such as the following when using `-Wall` (and I
couldn't find a respective warning GHC CLI flag which would have enabled
reporting a warning in this case -- unless I missed it)

 module Foo where

 foo :: Int - Int
 foo n = n + 1
   where
 Nothing = Just n


I think that

  where
x@Nothing = Just n

could be useful, if 'x' is evaluated somewhere.

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


Re: Why GHC doesn't warn about LHS nullary-constructor pattern bindings?

2012-07-19 Thread Christopher Done
In your case the Nothing is unused so will never be a problem.

Perhaps more worrying:

foo :: Int - Int
foo n = x + 1
where
  Just x = Nothing

This gives no warnings.

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


Re: API function to check whether one type fits in another

2012-07-19 Thread Philip Holzenspies
Dear Simon, et al,

I finally got back around to working on this idea. I'm not yet quite sure 
whether I've now understood it all. I have reread the latest edition of System 
F with Type Equality Coercions (Jan 2011 version), so I understand that 
inference is now just percolating coercions upwards, as it were, and then 
solving the set of wanted constraints. If the set is consistent, the program 
type-checks. This is at the core of what I have now:


typeCheck :: GhcMonad m = Type - Type - m (Messages, Maybe (TcCoercion, Bag 
EvBind))
typeCheck expectedTy actualTy = do
  let mod = mkModule mainPackageId $ mkModuleName NoModule
  env - getSession
  liftIO $ initTc env HsSrcFile False mod $ do
(coerce,wanted) - captureConstraints $ do
  (expectedWrap, expectedRho) - deeplyInstantiate DefaultOrigin expectedTy
  (actualWrap,   actualRho  ) - deeplyInstantiate DefaultOrigin actualTy
  unifyType actualRho expectedRho
binds - simplifyTop wanted
return (coerce,binds)


It appears both the hole (expectedTy) and the thing to go into the hole 
(actualTy) need to be deeply instantiated, otherwise, this function rejects 
putting (exprType 1) into the first argument position of (exprType (+)), 
because it either can't match 'a' to 'Num b = b', or (if we take the 
rho-type), it misses 'Num b'. Anyway, deeply instantiating both seems to solve 
such problems and, in the cases I've tried, type checks the things I would 
expect and rejects the things I would expect.

There are two missing bits, still:

Firstly, when leaving variables ambiguous (i.e. filling a Monad m = a - m a 
shaped hole with return, leaving 'm' ambiguous), simplifyTop fails. Is it 
possible to allow for ambiguous variables, in roughly the same way that 
(exprType mapM return) works just fine? I've looked at some other 
simplification functions (TcSimplify.*), but the lack of documentation makes my 
guesswork somewhat random.

Secondly, is there a way in the API to find all the appropriate substitutions 
for the variables in the *original* types (i.e. loosing the fresh variables 
introduced by deeplyInstantiate)? Ultimately, I would really like to end up 
with a TvSubst, or any other mapping from TyVar to Type.

Ideas?

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


Re: Template Haskell

2012-07-19 Thread Mikhail Vorozhtsov
Hi Simon.

On Wed, Jul 18, 2012 at 7:25 PM, Simon Peyton-Jones
simo...@microsoft.com wrote:
 Mikhail has improved Template Haskell’s handling of INLINE pragmas,
 SPECIALISE pragmas, and RULES.  I plan to commit his patch
BTW, is there a reason why you use commit messages to attribute other
people's work instead of `git am` or `git commit --author=...`?

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