Doesn't warn about variable not in scope
Running this works fine
{-# 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
-- 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.
Trac metadata
Trac field | Value |
---|---|
Version | 8.0.1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |