Unexpected nested forall in foreign declaration [GHC-92994]

Language extension: CApiFFI, RankNTypes

When using the CApiFFI interface to C functions, there are certain restrictions placed on the Haskell types that may be assigned to foreign functions. In particular, they may not use higher-rank polymorphic types - that is, all foralls must be at the beginning of the type signature.

Examples

Nested forall in a foreign function type

Message

NestedForall.hs:4:1: error: [GHC-92994]
    • Unacceptable result type in foreign declaration:
        Unexpected nested forall
    • When checking declaration:
        foreign import capi safe "foo.h fun" fun
          :: Int -> (forall a. a -> a)
  |
4 | foreign import capi "foo.h fun" fun :: Int -> (forall a . a -> a)
  | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

Explanation

This type contains a forall that does not scope over the entire type signature, which is not allowed in the FFI.

NestedForall.hs
Before
{-# LANGUAGE CApiFFI, RankNTypes #-}
module NestedForall where

foreign import capi "foo.h fun" fun :: Int -> (forall a . a -> a)
After
{-# LANGUAGE CApiFFI, RankNTypes #-}
module NestedForall where

foreign import capi "foo.h fun" fun :: forall a . Int -> a -> a