[Haskell-cafe] Error message??

Gregory Guthrie guthrie at miu.edu
Wed Dec 15 18:33:23 UTC 2021


I don't understand the error here:

-- ------------------------------------------
--  Find permutation by index
iPerm :: Int -> [a] -> (Int,Int)
iPerm k list = nPerm k $ length list
   where nPerm k n = divMod k (fact(n - 1))

-- indexPerm :: Int -> [a] -> [a]
indexPerm _ [] = []
indexPerm g list = d :: indexPerm r (delete d list)     -- line 19 ***
   where (q,r) = iPerm g list
         d = list !! q

Adding a type signature for indexPerm changes the error (below),
but seems to be the same basic issue.

I thought I might need:
    indexPerm :: Eq a => Int -> [a] -> [a]
to match the restriction on delete argument types, although I would have thought that would be inferred if needed,
  but it gives the same error message.
-----------------------------------------------------------------------
Prelude> (compiling)
[1 of 1] Compiling Main             ( syntaxtest.hs, interpreted )

yntaxtest.hs:19:20: error:
    * Couldn't match expected type `indexPerm r (delete1 d1 list1)'
                  with actual type `a'
        because type variables `indexPerm', `r', `delete1', `d1', `list1'
        would escape their scope
      These (rigid, skolem) type variables are bound by
        an expression type signature:
          forall (indexPerm :: * -> * -> *) r (delete1 :: * -> * -> *) d1 list1.
          indexPerm r (delete1 d1 list1)
        at syntaxtest.hs:19:25-51
    * In the expression: d :: indexPerm r (delete d list)
      In an equation for `indexPerm':
          indexPerm g list
            = d :: indexPerm r (delete d list)
            where
                (q, r) = iPerm g list
                d = list !! q
    * Relevant bindings include
        d :: a (bound at syntaxtest.hs:21:10)
        list :: [a] (bound at syntaxtest.hs:19:13)
       indexPerm :: Int -> [a] -> [delete d list]
          (bound at syntaxtest.hs:18:1)
   |
19 | indexPerm g list = d :: indexPerm r (delete d list)

   |                    ^

   |
19 | indexPerm g list = d :: indexPerm r (delete d list)

   |                    ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Failed, no modules loaded.
-----------------------------------------------------------------------
(error with the explicit type signature)

syntaxtest.hs:19:20: error:
    * Couldn't match expected type `indexPerm r (delete d list)'
                  with actual type `a'
      `a' is a rigid type variable bound by
        the type signature for:
          indexPerm :: forall a. Int -> [a] -> [a]
        at syntaxtest.hs:17:1-30
    * In the expression: d :: indexPerm r (delete d list)
      In an equation for `indexPerm':
          indexPerm g list
            = d :: indexPerm r (delete d list)
            where
                (q, r) = iPerm g list
                d = list !! q
    * Relevant bindings include
        d :: a (bound at syntaxtest.hs:21:10)
        list :: [a] (bound at syntaxtest.hs:19:13)
        indexPerm :: Int -> [a] -> [a] (bound at syntaxtest.hs:18:1)
   |
19 | indexPerm g list = d :: indexPerm r (delete d list)

   |                    ^

   |
19 | indexPerm g list = d :: indexPerm r (delete d list)

   |                    ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Failed, no modules loaded.


Gregory Guthrie



More information about the Haskell-Cafe mailing list