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?
Instance method are methods which require an object of its class to be created before it can be called. To invoke a instance method, we have to create an Object of the class in which the method is defined.
Using isinstance() function, we can test whether an object/variable is an instance of the specified type or class such as int or list. In the case of inheritance, we can checks if the specified class is the parent class of an object. For example, isinstance(x, int) to check if x is an instance of a class int .
Polymorphism is the ability of an object to take on many forms. Polymorphism in OOP occurs when a super class references a sub class object.
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!
If you love us? You can donate to us via Paypal or buy me a coffee so we can maintain and grow! Thank you!
Donate Us With