Use specialized implementation if a class instance is available

后端 未结 2 1985
名媛妹妹
名媛妹妹 2021-01-04 01:29

Consider the following situation:

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

I have two functions,

2条回答
  •  耶瑟儿~
    2021-01-04 02:11

    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!

提交回复
热议问题