
The following code (somewhat contrived) code compiles on GHC without issue, and towards the end repeatedly uses the lambda function "(\fn (D x) -> f fn x)". But when I simply try to give it a name, like so: h = (\fn (D x) -> f fn x) I then get a compile error. How can I name this function, or must it remain forever nameless? ( Ideone link: http://ideone.com/mtuYnK ) --- {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE OverlappingInstances #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE NoMonomorphismRestriction #-} import GHC.Exts (Constraint) type family Parent a class C a b where f :: b -> a -> String instance (C (Parent a) b) => C a b where f _ _ = f (undefined :: b) (undefined :: Parent a) data A1 = A1 data A2 = A2 data A3 = A3 data A4 = A4 type instance Parent A2 = A1 type instance Parent A3 = A2 type instance Parent A4 = A3 data F1 = F1 data F3 = F3 instance C A1 F1 where f _ _ = "F1" instance C A3 F3 where f _ _ = "F3" type family Constraints t a :: Constraint data D t = forall a. (Constraints t a) => D a type instance Constraints A1 a = (C a F1) type instance Constraints A2 a = (C a F1, C a F3) type instance Constraints A3 a = (C a F1, C a F3) type instance Constraints A4 a = (C a F1, C a F3) main = do putStrLn (f F1 A1) putStrLn (f F1 A2) putStrLn (f F1 A3) putStrLn (f F1 A4) putStrLn (f F3 A3) putStrLn (f F3 A4) putStrLn $ (\fn (D x) -> f fn x) F1 ((D A1) :: D A1) putStrLn $ (\fn (D x) -> f fn x) F1 ((D A2) :: D A1) putStrLn $ (\fn (D x) -> f fn x) F3 ((D A3) :: D A2) -- h = (\fn (D x) -> f fn x)