puzzled
puzzled

Reputation: 77

Rigid Variable in Applicative instantiation

I am getting a compiler error for the Applicative instantiation of Safeness, as follows:

{-# LANGUAGE InstanceSigs #-}

module Main where

main :: IO ()
main = pure ()


data Safeness a 
    = Unsafe a
    | Safe a
    | VerySafe a
    deriving (Eq, Show)


instance Functor Safeness where
    fmap :: (a -> b) -> Safeness a -> Safeness b
    fmap f (Unsafe x) = Unsafe $ f x
    fmap f (Safe x) = Safe $ f x
    fmap f (VerySafe x) = VerySafe $ f x


instance Applicative Safeness where
    pure :: a -> Safeness a
    pure x = Safe x

    (<*>) :: Safeness (a -> b) -> Safeness a -> Safeness b
    (<*>) (Safe f) (Safe x) = Safe $ f x       
    (<*>) (VerySafe f) (VerySafe x) = VerySafe $ f x    
    (<*>) _ x = x     

Compiler error:

    * Couldn't match type `a' with `b'
      `a' is a rigid type variable bound by
        the type signature for:
          (<*>) :: forall a b. Safeness (a -> b) -> Safeness a -> Safeness b      
        at C:\practise\app\Main.hs:27:14-58       
      `b' is a rigid type variable bound by
        the type signature for:
          (<*>) :: forall a b. Safeness (a -> b) -> Safeness a -> Safeness b      
        at C:\practise\app\Main.hs:27:14-58       
      Expected type: Safeness b
        Actual type: Safeness a
    * In the expression: x
      In an equation for `<*>': (<*>) _ x = x
      In the instance declaration for `Applicative Safeness'
    * Relevant bindings include
        x :: Safeness a
          (bound at C:\practise\app\Main.hs:30:13)
        (<*>) :: Safeness (a -> b) -> Safeness a -> Safeness b
          (bound at C:\practise\app\Main.hs:28:5) 
   |
30 |     (<*>) _ x = x       
   |   

I understand that b doesn't have to be the same as a, but it could; and I am always forcing it to be the same in a certain case. What is wrong with that, and how else can I code this for the intended functionality?

Upvotes: 2

Views: 81

Answers (1)

Jon Purdy
Jon Purdy

Reputation: 54971

The problem, as the error message indicates, is in this pattern:

(<*>) _ x = x

Let’s give the first argument a name for clarity, and supply a “hole” for the body:

(<*>) f x = _

Then the compiler will tell us:

/Users/jpurdy/Code/Safe.hs:24:17: error:
    • Found hole: _ :: Safeness b
    …
    • Relevant bindings include
        x :: Safeness a
        f :: Safeness (a -> b)
        (<*>) :: Safeness (a -> b) -> Safeness a -> Safeness b

The only values you can return are Unsafe (_ :: b), Safe (_ :: b), or VerySafe (_ :: b), so you must supply a b; by parametricity, the only way you can get a b is by matching on f to get an a -> b and matching on x to get an a, and applying the function to the value. In other words, you can’t just return x unmodified.

Unfortunately, the solution depends on what you want to do. You could tag the result with the minimum safety of the two arguments:

VerySafe f <*> VerySafe x = VerySafe $ f x
VerySafe f <*> Safe x     = Safe $ f x
VerySafe f <*> Unsafe x   = Unsafe $ f x

Safe f     <*> VerySafe x = Safe $ f x
Safe f     <*> Safe x     = Safe $ f x
Safe f     <*> Unsafe x   = Unsafe $ f x

Unsafe f   <*> VerySafe x = Unsafe $ f x
Unsafe f   <*> Safe x     = Unsafe $ f x
Unsafe f   <*> Unsafe x   = Unsafe $ f x

And this is simpler by factoring the safety parameter out of your type (in type algebra, from a + a + a to 3 × a):

data Safety = Unsafe | Safe | VerySafe
  deriving (Eq, Ord)

data Safeness a = Safeness Safety a

instance Applicative Safeness where

  -- Combine safeties with ‘min’, or use
  -- ‘deriving (Semigroup, Monoid) via (Min Safety)’
  -- to use the Semigroup ‘<>’ operator.
  Safeness s1 f <*> Safeness s2 x
    = Safeness (min s1 s2) (f x)

  -- Must use ‘VerySafe’ instead of ‘Safe’
  -- since it’s the identity for ‘min’,
  -- to satisfy the ‘Applicative’ laws.
  -- (Or respectively ‘mempty’ = ‘maxBound’.)
  pure = Safeness VerySafe

Or you could get fancy and use a GADT to lift the safety parameter to the type level, foregoing the Applicative instance, but allowing only values with the same safety to be combined:

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE GADTs #-}

data Safety = U | S | V

data Safeness (s :: Safety) a where
  VerySafe :: a -> Safeness 'V a
  Safe     :: a -> Safeness 'S a
  Unsafe   :: a -> Safeness 'U a

apply :: Safeness s (a -> b) -> Safeness s a -> Safeness s b
apply (VerySafe f) (VerySafe x) = VerySafe (f x)
apply (Safe f)     (Safe x)     = Safe (f x)
apply (Unsafe f)   (Unsafe x)   = Unsafe (f x)
-- (Other cases are impossible because ‘s’ won’t match.)

As an aside, you could use the DeriveFunctor extension to write deriving (Functor) for Safeness.

Upvotes: 3

Related Questions