Can multiple dispatch be achieved in Haskell with pattern matching on type classes?

前端 未结 2 1883
情话喂你
情话喂你 2021-02-05 18:41

This is a question about multiple dispatch in Haskell.

Below I use the term \"compliant to [type class]\" to mean \"has type which is instance of [type class]\", because

相关标签:
2条回答
  • 2021-02-05 18:59

    The normal way to "pattern match" on types in the way you're describing is with type class instances. With concrete types, this is easy using MultiParamTypeClasses; this is how Haskell implements multiple dispatch.

    {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, OverlappingInstances #-}
    module SO26303353 where
    
    class (Num a, Num b) => Power a b where
      my_pow :: a -> b -> a
    
    instance Power Double Double where
      my_pow = (**)
    
    instance Num a => Power a Integer where
      my_pow = (^)
    

    This works just fine. It's more or less idiomatic Haskell, except that (**) and (^) are different operations and some people might object to blurring the distinction.

    You're asking for something a bit more elaborate, however. You want multiple dispatch not only on types but on classes of types. This is a significantly different and more powerful thing. In particular, it would work for all types that could have instances of Floating or Intergral, even types that haven't been written yet! Here's how it would be written ideally:

    instance (Floating a) => Power a a where
      my_pow = (**)
    
    instance (Num a, Integral b) => Power a b where
      my_pow = (^)
    

    This doesn't work, though, because the constraint solver does not backtrack, and does not consider instance constraints when choosing an instance. So my_pow doesn't work, for instance, with two Ints:

    ghci> :t my_pow :: Int -> Int -> Int
    No instance for (Floating Int)
    

    This happens because the "more specific" Power a a instance matches, because the two types are equal. GHC then imposes the Floating constraint on a, and barfs when it can't satisfy it. It does not then backtrack and try the Power a b instance.

    It may or may not be possible to hack around the limitation using advanced type system features, but I don't think you could ever make a drop-in replacement for both (**) and (^) in current Haskell.

    Edit: general comments

    (Note that we're kind of straying away from a Q&A format here.)

    In rereading your question and comment, I notice you're using the term "dispatch" in a way I'm not familiar with. A quick Google turns up articles on double dispatch and the visitor design pattern. Is that where you're coming from? They look a bit like what you're trying to do--write a function that does totally different things based on the types of its arguments. I want to add a few things to this answer that may help hone your sense of idiomatic Haskell. (Or may just be disjointed rambling.)

    Haskell normally disregards the idea of a "runtime type". Even in @Cirdec's more elaborate answer, all the types are statically known, "at compile time." (Using the REPL, ghci, doesn't change things, except that "compile time" gets kind of hazy.) In fact, intuitions about what happen "at runtime" are often different in Haskell than other languages, not least because GHC performs aggressive optimizations.

    Idiomatic Haskell is built on a foundation of parametric polymorphism; a function like replicate :: Int -> a -> [a] works absolutely the same for any type a. As a result, we know a lot about what replicate does without having to look at its implementation. This attitude is really helpful, and it deeply infects the brains of Haskell programmers. You'll notice that me and many other Haskell programmers go crazy with type annotations, especially in a forum like this one. The static types are very meaningful. (Keyword: free theorems.) (This isn't immediately relevant to your question.)

    Haskell uses type classes to permit ad hoc polymorphism. In my mind, 'ad hoc' refers to the fact that the implementation of a function may be different for different types. This is of course critical for numerical types, and has been applied over the years in countless ways. But it's important to understand that everything is still statically typed, even with type classes. To actually evaluate any type-class function--to get a value out of it--you need to in the end choose a specific type. (With numeric types, the defaulting rules frequently choose it for you.) You can of course combine things to produce another polymorphic function (or value).

    Historically, type classes were thought of strictly as a mechanism for function overloading, in the sense of having the same name for several distinct functions. In other words, rather than addInt :: Int -> Int -> Int, addFloat :: Float -> Float -> Float, we have one name: (+) :: Num a => a -> a -> a. But it's still fundamentally the same idea: there are a bunch of completely different functions called (+). (Now we tend to talk about type classes in terms of "laws," but that's a different topic.) There's oftentimes no literal dispatch occurring with a function like (+), or even non-primitive functions.

    Yes, type classes are a bit like interfaces, but don't allow an OOP mindset to creep in too far. If you are writing a function with a type like Num a => a -> a, the expectation is that the only thing you know about a is that it is an instance of Num. You can't look behind the curtain, as it were. (Without cheating. Which is hard.) The only way to manipulate values of type a is with fully polymorphic functions and with other Num functions. In particular, you can't determine whether a is also an instance of some other class.

    The various compiler extensions we've been playing with blur this model a bit, because we now can write, essentially, type level functions. But don't confuse that with dynamic dispatch.

    Oh, by the way, Haskell does support dynamic types. See Data.Dymamic. To be honest, I've never really seen much use for it outside of interop with other languages. (I'm willing to be wrong.) The typical "visitor pattern" problems can be implemented in other ways.

    0 讨论(0)
  • 2021-02-05 19:06

    Like Christian Conkle hinted at, we can determine if a type has an Integral or Floating instance using more advanced type system features. We will try to determine if the second argument has an Integral instance. Along the way we will use a host of language extensions, and still fall a bit short of our goal. I'll introduce the following language extensions where they are used

    {-# LANGUAGE EmptyDataDecls #-}
    {-# LANGUAGE FunctionalDependencies #-}
    {-# LANGUAGE MultiParamTypeClasses #-}
    {-# LANGUAGE FlexibleInstances #-}
    {-# LANGUAGE TypeFamilies #-}
    {-# LANGUAGE UndecidableInstances #-}
    {-# LANGUAGE ScopedTypeVariables #-}
    {-# LANGUAGE OverlappingInstances #-}
    

    Convert Integral context to type

    To begin with we will make a class that will try to capture information from the context of a type (whether there's an Integral instance) and convert it into a type which we can match on. This requires the FunctionalDependencies extension to say that the flag can be uniquely determined from the type a. It also requires MultiParamTypeClasses.

    class IsIntegral a flag | a -> flag
    

    We'll make two types to use for the flag type to represent when a type does (HTrue) or doesn't (HFalse) have an Integral instance. This uses the EmptyDataDecls extension.

    data HTrue
    data HFalse
    

    We'll provide a default - when there isn't an IsIntegral instance for a that forces flag to be something other than HFalse we provide an instance that says it's HFalse. This requires the TypeFamilies, FlexibleInstances, and UndecidableInstances extensions.

    instance (flag ~ HFalse) => IsIntegral a flag
    

    What we'd really like to do is say that every a with an Integral a instance has an IsIntegral a HTrue instance. Unfortunately, if we add an instance (Integral a) => IsIntegral a HTrue instance we will be in the same situation Christian described. This second instance will be used by preference, and when the Integral constraint is encountered it will be added to the context with no backtracking. Instead we will need to list all the Integral types ourselves. This is where we fall short of our goal. (I'm skipping the base Integral types from System.Posix.Types since they aren't defined equally on all platforms).

    import Data.Int
    import Data.Word
    import Foreign.C.Types
    import Foreign.Ptr
    
    instance IsIntegral Int HTrue
    instance IsIntegral Int8 HTrue
    instance IsIntegral Int16 HTrue
    instance IsIntegral Int32 HTrue
    instance IsIntegral Int64 HTrue
    instance IsIntegral Integer HTrue
    instance IsIntegral Word HTrue
    instance IsIntegral Word8 HTrue
    instance IsIntegral Word16 HTrue
    instance IsIntegral Word32 HTrue
    instance IsIntegral Word64 HTrue
    instance IsIntegral CUIntMax HTrue
    instance IsIntegral CIntMax HTrue
    instance IsIntegral CUIntPtr HTrue
    instance IsIntegral CIntPtr HTrue
    instance IsIntegral CSigAtomic HTrue
    instance IsIntegral CWchar HTrue
    instance IsIntegral CSize HTrue
    instance IsIntegral CPtrdiff HTrue
    instance IsIntegral CULLong HTrue
    instance IsIntegral CLLong HTrue
    instance IsIntegral CULong HTrue
    instance IsIntegral CLong HTrue
    instance IsIntegral CUInt HTrue
    instance IsIntegral CInt HTrue
    instance IsIntegral CUShort HTrue
    instance IsIntegral CShort HTrue
    instance IsIntegral CUChar HTrue
    instance IsIntegral CSChar HTrue
    instance IsIntegral CChar HTrue
    instance IsIntegral IntPtr HTrue
    instance IsIntegral WordPtr HTrue
    

    Matching on IsIntegral

    Our end goal is to be able to provide appropriate instances for the following class

    class (Num a, Num b) => Power a b where
        pow :: a -> b -> a
    

    We want to match on types to choose which code to use. We'll make a class with an extra type to hold the flag for whether b is an Integral type. The extra argument to pow' lets type inference choose the correct pow' to use.

    class (Num a, Num b) => Power' flag a b where
        pow' :: flag -> a -> b -> a
    

    Now we'll write two instances, one for when b is Integral and one for when it isn't. When b isn't Integral, we can only provide an instance when a and b are the same.

    instance (Num a, Integral b) => Power' HTrue a b where
        pow' _ = (^)
    
    instance (Floating a, a ~ b) => Power' HFalse a b where
        pow' _ = (**)
    

    Now, whenever we can determine if b is Integral with IsIntegral and can provide a Power' instance for that result, we can provide the Power instance which was our goal. This requires the ScopedTypeVariables extension to get the correct type for the extra argument to pow'

    instance (IsIntegral b flag, Power' flag a b) => Power a b where
        pow = pow' (undefined::flag)
    

    Actually using these definitions requires the OverlappingInstances extension.

    main = do
        print (pow 7 (7 :: Int))
        print (pow 8.3 (7 :: Int))
        print (pow 1.2 (1.2 :: Double))
        print (pow 7 (7 :: Double))
    

    You can read another explanation of how to use FunctionalDependencies or TypeFamilies to avoid overlap in overlapping instances in the Advanced Overlap article on HaskellWiki.

    0 讨论(0)
提交回复
热议问题