JSQuareD
JSQuareD

Reputation: 4786

Use specialized implementation if a class instance is available

Consider the following situation:

slow_func :: Eq a  => [a] -> [a]
fast_func :: Ord a => [a] -> [a]

I have two functions, slow_func and fast_func. These functions are different implementations of the same abstract function (they do the same thing), but one is faster than the other. The faster implementation is only available if the type a can be ordered. Is there a way to construct a function which acts as fast_func when possible, and reverts to slow_func otherwise?

as_fast_as_possible_func :: Eq a => [a] -> [a]

I have already tried the following:

{-# LANGUAGE OverlappingInstances  #-}

class Func a where
    as_fast_as_possible_func :: [a] -> [a]

instance Ord a => Func a where
    as_fast_as_possible_func = fast_func

instance Eq a => Func a where
    as_fast_as_possible_func = slow_func

Unfortunately, this doesn't compile, generating the following error:

Duplicate instance declarations:
  instance Ord a => Func a
    -- Defined at [...]
  instance Eq a => Func a
    -- Defined at [...]

The reason is that OverlappingInstances wants one of the instances to be most specialized with respect to the instance specification, ignoring its context (rather than using the most restrictive context, which is what we need here).

Any way to do this?

Upvotes: 19

Views: 1346

Answers (2)

Shersh
Shersh

Reputation: 9179

Turned out actually you can. Seriously, I'm starting to think that everything is possible in Haskell... You can use results of recently announced constraint-unions approach. I'm using code similar to one that was written by @leftaroundabout. Not sure I did it in best way, just tried to apply concepts of proposed approach:

{-# OPTIONS_GHC -Wall -Wno-name-shadowing #-}

{-# LANGUAGE AllowAmbiguousTypes        #-}
{-# LANGUAGE ConstraintKinds            #-}
{-# LANGUAGE FlexibleContexts           #-}
{-# LANGUAGE FlexibleInstances          #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses      #-}
{-# LANGUAGE RankNTypes                 #-}
{-# LANGUAGE ScopedTypeVariables        #-}
{-# LANGUAGE TypeApplications           #-}
{-# LANGUAGE TypeOperators              #-}

module Main where

import           Data.List (group, nub, sort)

infixr 2 ||
class  c || d where
    resolve :: (c => r) -> (d => r) -> r

slowFunc :: Eq a => [a] -> [a]
slowFunc = nub

fastFunc :: Ord a => [a] -> [a]
fastFunc = map head . group . sort

as_fast_as_possible_func :: forall a. (Ord a || Eq a) => [a] -> [a]
as_fast_as_possible_func = resolve @(Ord a) @(Eq a) fastFunc slowFunc

newtype SlowWrapper = Slow Int deriving (Show, Num, Eq)
newtype FastWrapper = Fast Int deriving (Show, Num, Eq, Ord)

instance      (Ord FastWrapper || d) where resolve = \r _ -> r
instance d => (Ord SlowWrapper || d) where resolve = \_ r -> r

main :: IO ()
main = print . sum . as_fast_as_possible_func $ (Fast . round) 
                                             <$> [sin x * n | x<-[0..n]]
  where n = 20000

The key part here is as_fast_as_possible_func:

as_fast_as_possible_func :: forall a. (Ord a || Eq a) => [a] -> [a]
as_fast_as_possible_func = resolve @(Ord a) @(Eq a) fastFunc slowFunc

It uses appropriate function depending on whether a is Ord or Eq. I put Ord on the first place because everything that is Ord is automatically Eq and type checker rules might not trigger (though I didn't tested this function with constraints swapped). If you use Slow here (Fast . round) instead of Fast you can observe significantly slower results:

$ time ./Nub  # With `Slow` 
Slow 166822

real    0m0.971s
user    0m0.960s
sys     0m0.008s


$ time ./Nub  # With `Fast` 
Fast 166822

real    0m0.038s
user    0m0.036s
sys     0m0.000s

UPDATE

I've updated required instances. Instead of

instance (c || Eq SlowWrapper)  where resolve = \_ r -> r

Now it is

instance d => (Ord SlowWrapper || d) where resolve = \_ r -> r

Thanks @rampion for explanation!

Upvotes: 10

leftaroundabout
leftaroundabout

Reputation: 120751

I would consider two options:

Rewrite rules

You can nominally use slow_func everywhere, but let rewrite rules optimise it when possible. For example,

import Data.List

slowFunc :: Eq a => [a] -> [a]
slowFunc = nub

fastFunc :: Ord a => [a] -> [a]
fastFunc = map head . group . sort

main = print . sum . slowFunc $ round <$> [sin x * n | x<-[0..n]]
 where n = 100000

is slow (duh):

$ ghc -O2 Nub.hs && time ./Nub
[1 of 1] Compiling Main             ( Nub.hs, Nub.o )
Linking Nub ...
-3670322

real    0m51.875s
user    0m51.867s
sys 0m0.004s

but if we add (without changing anything)

{-# NOINLINE slowFunc #-}
{-# RULES "slowFunc/Integer" slowFunc = fastFunc :: [Integer] -> [Integer] #-}

then

$ ghc -O2 Nub.hs && time ./Nub
[1 of 1] Compiling Main             ( Nub.hs, Nub.o )
Linking Nub ...
-3670322

real    0m0.250s
user    0m0.245s
sys 0m0.004s

Rewrite rules are a bit hard to rely on (inlining is just one thing that can get in the way), but at least you can be sure that something that runs with slowFunc will keep working (just perhaps not fast enough) but definitely won't get lost in some missing-instance issue. On the flip side, you should also make very sure that slowFunc and fastFunc actually behave the same – in my example, this is not actually given! (But it can easily be modified accordingly).

As Alec emphasizes in the comments, you will need to add a rewrite rule for every single type that you want to make fast. The good thing is that this can be done after the code is finished and exactly where profiling indicates that it matters, performance-wise.

Individual instances

This is the reliable solution: abstain from any catch-all instances and instead decide for each type what's appropriate.

instance Func Int where
    as_fast_as_possible_func = fast_func
instance Func Double where
    as_fast_as_possible_func = fast_func
...

instance Func (Complex Double) where
    as_fast_as_possible_func = slow_func

You can save some duplicate lines by making the more common version the default:

{-# LANGUAGE DefaultInstances #-}

class Func a where
  as_fast_as_possible_func :: [a] -> [a]
  default as_fast_as_possible_func :: Ord a => [a] -> [a]
  as_fast_as_possible_func = fast_func

instance Func Int
instance Func Double
...

instance Func (Complex Double) where
    as_fast_as_possible_func = slow_func

Upvotes: 9

Related Questions