Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

How to cast `forall a. a -> a` back to `a -> a`?

In my actual problem I have a function f, passed as a parameter, that changes the order in a list but has no requirements regarding type and does not change the type either. I want to apply that function on [Int] and [Bool] so I have to resolve both contexts trying to typecast f to either [Int] -> [Int] or [Bool] -> [Bool]. I solved this with Rank2Types. But then I use any on a list of functions like f and any requires the functions to be [a] -> [a] rather than forall a. [a] -> [a].

The code below while nonsensical perfectly reproduces the error:

{-# LANGUAGE Rank2Types #-}

--debug :: (forall a. [a] -> [a]) -> Bool 
debug swap = any combine [swap]
  where
    combine :: (forall a. [a] -> [a]) -> Bool
    combine f =  usefonBool f && usefonInt f
    --usefonBool :: (forall a. [a] -> [a]) -> Bool
    usefonBool f = f [True,True] == [False]

    --usefonInt :: (forall a. [a] -> [a]) -> Bool
    usefonInt f = (f [1,2]) == [2,1]

The error message is:

• Couldn't match type ‘a’ with ‘forall a1. [a1] -> [a1]’
  ‘a’ is a rigid type variable bound by
    the inferred type of debug :: a -> Bool
    at /path/debug.hs:(4,1)-(12,36)
  Expected type: a -> Bool
    Actual type: (forall a. [a] -> [a]) -> Bool
• In the first argument of ‘any’, namely ‘combine’
  In the expression: any combine [swap]
  In an equation for ‘debug’:
      debug swap
        = any combine [swap]
        where
            combine :: (forall a. [a] -> [a]) -> Bool
            combine f = usefonBool f && usefonInt f
            usefonBool f = f [True, ....] == [False]
            usefonInt f = (f [1, ....]) == [2, ....]
• Relevant bindings include
    swap :: a (bound at /path/debug.hs:4:7)
    debug :: a -> Bool (bound at /path/debug.hs:4:1)
|

My goal is to find an annotation that lets me use an f on different types and then apply any on a list of such generic functions.

If I uncomment all my type annotations (or just the top one) the error changes to

• Couldn't match type ‘[a0] -> [a0]’ with ‘forall a. [a] -> [a]’
  Expected type: ([a0] -> [a0]) -> Bool
    Actual type: (forall a. [a] -> [a]) -> Bool
• In the first argument of ‘any’, namely ‘combine’
  In the expression: any combine [swap]
  In an equation for ‘debug’:
      debug swap
        = any combine [swap]
        where
            combine :: (forall a. [a] -> [a]) -> Bool
            combine f = usefonBool f && usefonInt f
            usefonBool :: (forall a. [a] -> [a]) -> Bool
            usefonBool f = f [True, ....] == [False]
            ....
  |
like image 967
peer Avatar asked Oct 14 '25 14:10

peer


1 Answers

First, note that Rank2Types is a deprecated name. It's equivalent to RankNTypes in modern GHC, and that's the preferred name for the extension.

Here's the underlying problem. A "list of such generic functions" could have the type:

[forall a. [a] -> [a]]

Sadly, this isn't a valid Haskell type because Haskell doesn't support "impredicative polymorphism". Specifically, the following program:

{-# LANGUAGE RankNTypes #-}
myFunctions :: [forall a. [a] -> [a]]
myFunctions = [f1, f2]
   where f1 (x:y:rest) = y:x:rest
         f2 = reverse

produces the error message:

DebugRank.hs:2:16: error:
    • Illegal polymorphic type: forall a. [a] -> [a]
      GHC doesn't yet support impredicative polymorphism
    • In the type signature: myFunctions :: [forall a. [a] -> [a]]

There's an extension, ImpredicativeTypes. It's flakey and incomplete, but it allows the following to compile:

{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE ImpredicativeTypes #-}

myFunctions :: [forall a. [a] -> [a]]
myFunctions = [f1, f2]
   where f1 (x:y:rest) = y:x:rest
         f2 = reverse

debug :: [forall a. [a] -> [a]] -> Bool
debug = any combine
  where
    combine :: (forall a. [a] -> [a]) -> Bool
    combine f = usefonBool f && usefonInt f
    usefonBool f = f [True,True] == [False]
    usefonInt  f = f [1,2] == [2,1]

main = print (debug myFunctions)

I'd still recommend against using it, though.

The usual alternative is to use a newtype wrapper for the polymorphic function:

newtype ListFunction = ListFunction (forall a. [a] -> [a])

This requires some boilerplate, but no extensions other than RankNTypes:

myFunctions :: [ListFunction]
myFunctions = [ListFunction f1, ListFunction f2]
   where f1 (x:y:rest) = y:x:rest
         f2 = reverse

debug :: [ListFunction] -> Bool
debug = any combine
  where
    combine :: ListFunction -> Bool
    combine (ListFunction f) = usefonBool f && usefonInt f
    usefonBool f = f [True,True] == [False]
    usefonInt  f = f [1,2] == [2,1]

The complete code:

{-# LANGUAGE RankNTypes #-}

newtype ListFunction = ListFunction (forall a. [a] -> [a])

myFunctions :: [ListFunction]
myFunctions = [ListFunction f1, ListFunction f2]
   where f1 (x:y:rest) = y:x:rest
         f2 = reverse

debug :: [ListFunction] -> Bool
debug = any combine
  where
    combine :: ListFunction -> Bool
    combine (ListFunction f) = usefonBool f && usefonInt f
    usefonBool f = f [True,True] == [False]
    usefonInt  f = f [1,2] == [2,1]

main = print $ debug myFunctions
like image 128
K. A. Buhr Avatar answered Oct 17 '25 12:10

K. A. Buhr