This is the effect of -XMonoLocalBinds, which is implied by -XTypeFamilies (and also by -XGADTs). See https://downloads.haskell.org/ghc/latest/docs/html/users_guide/exts/let_generalisation.html.

Happy to give more background -- let me know if that link doesn't answer your question.

Richard

On Feb 10, 2021, at 6:31 AM, Tom Ellis <tom-lists-haskell-cafe-2017@jaguarpaw.co.uk> wrote:

Dear all,

I don't understand why the type of pBD defined in the where clause of
pFG cannot be inferred to a general type in the presence of
TypeFamilies.  In particular I don't understand why nonetheless the
type of pBD definied in the where clause of pF (only slightly simpler)
*can* be inferred.

Can anyone explain?

Thanks

Tom



{-# LANGUAGE TypeFamilies #-}

-- This code came up in the context of writing a parser, but that's
-- not terribly important

import Prelude hiding ((<$>))

data B = B

data D f = F     f
        | GF AP f
        | DF AM f

data AM = AM
data AP = AP

pB :: Parser B
pB = Parser

-- Works fine
pF :: Parser (D B)
pF = pBD GF AP <|> pBD DF AM
 where pBD f p = f p <$> pB

-- Shows the (presumably) inferred type for pBD
pFWithType :: Parser (D B)
pFWithType = pBD GF AP <|> pBD DF AM
 where pBD :: (t -> B -> b) -> t -> Parser b
       pBD f p = f p <$> pB

-- One would hope this type would be inferred too
pFGWithType :: Parser B -> Parser (D B)
pFGWithType pBArg = pBD GF AP <|> pBD DF AM
 where pBD :: (t -> B -> b) -> t -> Parser b
       pBD f p = f p <$> pBArg

-- But omitting it leads to a type error if TypeFamilies is enabled.
-- There is no error if TypeFamilies is not enabled.
pFG :: Parser B -> Parser (D B)
pFG pBArg = pBD GF AP <|> pBD DF AM
 where pBD f p = f p <$> pBArg


-- The specifics of the parser don't matter
data Parser a = Parser

(<|>) :: Parser a -> Parser a -> Parser a
(<|>) _ _ = Parser

(<$>) :: (a -> b) -> Parser a -> Parser b
(<$>) _ _ = Parser
_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Only members subscribed via the mailman list are allowed to post.