RhubarbAndC
RhubarbAndC

Reputation: 494

Haskell - All functions of form A -> A -> ... -> A

I have a type (call it A) and I want to make a typeclass of the functions of type A -> A, A -> A -> A, A -> A -> A -> ... etc. This doesn't work:

{-# LANGUAGE FlexibleInstances #-}

data A = A

class AsToA a where
  takeA :: AsToA b => a -> A -> Either A b

instance AsToA (A -> A) where
  takeA f a = Left (f a)

instance AsToA b => AsToA (A -> b) where
  takeA f a = Right (f a)

I get the following error message:

AsToA.hs:12:22:
    Couldn't match expected type ‘b1’ with actual type ‘b’
      ‘b’ is a rigid type variable bound by
          the instance declaration at AsToA.hs:11:10
      ‘b1’ is a rigid type variable bound by
          the type signature for

             takeA :: AsToA b1 => (A -> b) -> A -> Either A b1
          at AsToA.hs:12:3
    Relevant bindings include
      f :: A -> b (bound at AsToA.hs:12:9)
      takeA :: (A -> b) -> A -> Either A b1 (bound at AsToA.hs:12:3)
    In the first argument of ‘Right’, namely ‘(f a)’
    In the expression: Right (f a)

Any ideas? Thanks very much for any advice.

Upvotes: 6

Views: 158

Answers (2)

Ørjan Johansen
Ørjan Johansen

Reputation: 18189

As mentioned in the comments to the other answer, you might not really need the Either, and takeA is then basically always id, just with a type restriction. If so you can make this a method-less class:

{-# LANGUAGE FlexibleInstances, FlexibleContexts #-}

data A = A

class AsToA a

takeA :: AsToA a => a -> a
takeA = id

instance AsToA (A -> A)

instance AsToA (A -> b) => AsToA (A -> (A -> b))

Alternatively, you might want to convert the functions to a common type that allows you to pass in As dynamically. If so Either won't be enough, but you can define your own:

{-# LANGUAGE FlexibleInstances, FlexibleContexts #-}

data A = A

data R = Result A | MoreArgs (A -> R)

class AsToA a where
    takeA :: a -> A -> R

instance AsToA (A -> A) where
    takeA f a = Result (f a)

instance AsToA (A -> b) => AsToA (A -> (A -> b)) where
    takeA f a = MoreArgs (takeA $ f a)

Upvotes: 2

chi
chi

Reputation: 116139

There is some confusion between the two bs:

class AsToA a where
  takeA :: AsToA b => a -> A -> Either A b

instance AsToA b => AsToA (A -> b) where
  takeA f a = Right (f a)

These are not the same. Let's rename the first one to c

class AsToA a where
  takeA :: AsToA c => a -> A -> Either A c

instance AsToA b => AsToA (A -> b) where
  takeA f a = Right (f a)

Now, Right (f a) has type Either A b but should have type Either A c for any c such that AsToA c holds. This does not type check.

The issue here is that the signature

  takeA :: AsToA c => a -> A -> Either A c

promises that takeA can return Either A c for any c, caller's choice. This is not what you want, I guess.


I'm still not sure about what the actual intended result is, but I guess the problem is similar to the following one.

Given a function f of type A->A->...->A return a function \x -> f x x ..., with one application of x for each -> in the type (hence of type A->A).

A possible solution is

{-# LANGUAGE FlexibleInstances, OverlappingInstances #-}
data A = A -- could be anything

class C f where
   takeA :: f -> A -> A

instance C (A -> A) where
   takeA f = f

instance C b => C (A -> b) where
    takeA f = \x -> takeA (f x) x

Note that this requires OverlappingInstances to be used, which is quite evil. I'd recommend to avoid it.

To avoid it, in this case it's enough to define an instance even for the type A.

{-# LANGUAGE FlexibleInstances #-}
data A = A -- could be anything

class C f where
   takeA :: f -> A -> A

instance C A where
   takeA a = \_ -> a

instance C b => C (A -> b) where
    takeA f = \x -> takeA (f x) x

Upvotes: 4

Related Questions