[GHC] #13485: Doesn't warn about variable not in scope

GHC ghc-devs at haskell.org
Sat Mar 25 21:54:01 UTC 2017


#13485: Doesn't warn about variable not in scope
-------------------------------------+-------------------------------------
           Reporter:  Iceland_jack   |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.1
           Keywords:  GADTs          |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Running this works fine

 {{{#!hs
 {-# Language GADTs, TypeFamilies, InstanceSigs #-}

 data FunC a where
   (:$) :: FunC (a -> b) -> FunC a -> FunC b
   Lam  :: (FunC a -> FunC b) -> FunC (a -> b)
   Add  :: Num a => FunC (a -> a -> a)

 class Syntactic a where
   type Internal a
   toFunC   :: a -> FunC (Internal a)
   fromFunC :: FunC (Internal a) -> a

 instance Syntactic (FunC a) where
   type Internal (FunC a) = a
   toFunC, fromFunC :: FunC a -> FunC a
   toFunC   ast = ast
   fromFunC ast = ast

 instance (Syntactic a, Syntactic b) => Syntactic (a -> b) where
   type Internal (a -> b) = Internal a -> Internal b

   toFunC :: (a -> b) -> FunC (Internal a -> Internal b)
   toFunC f = Lam (toFunC . f . fromFunC)

   fromFunC :: FunC (Internal a -> Internal b) -> (a -> b)
   fromFunC f = fromFunC . (f :$) . toFunC

 add :: Num a => FunC a -> FunC a -> FunC a
 add = fromFunC Add
 }}}

 A folklore for infix expressions is writing `expr a b` as `a &expr$ b`, if
 I try that '''without''' importing `(Data.Function.&)` I get

 {{{#!hs
 -- tghl.hs:29:23-25: error: …
 --     • Couldn't match type ‘Internal t0’ with ‘a0 -> a0 -> a0’
 --       Expected type: FunC (Internal t0)
 --         Actual type: FunC (a0 -> a0 -> a0)
 --       The type variables ‘t0’, ‘a0’ are ambiguous
 --     • In the first argument of ‘fromFunC’, namely ‘Add’
 --       In the second argument of ‘(&)’, namely ‘fromFunC Add’
 --       In the expression: (&) a fromFunC Add
 add :: Num a => FunC a -> FunC a -> FunC a
 add a b = a &fromFunC Add$ b
 }}}

 I would expect a `Variable not in scope: (&)` error.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13485>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list