I am trying to define default method implementations, but only if the class's type variables derive certain other classes.
I have tried creating type-dependent instances using =>
(am I even using it correctly?), but I get a "duplicate instance declaration error": (https://repl.it/@solly_ucko/Distributions)
{-# LANGUAGE FlexibleInstances, FunctionalDependencies, MultiParamTypeClasses, InstanceSigs #-}
import Data.Int
import Data.Ratio
import Data.Set
import System.Random
duplicate :: a -> (a, a)
duplicate a = (a, a)
listRange :: Enum a => a -> a -> [a]
listRange a b = [a..b]
class Fractional w => Distribution d v w where
probability :: d v w -> v -> w
probabilityOfRange :: Ord v => d v w -> v -> v -> w
ranges :: (Ord v) => d v w -> Set (v, v)
ranges = (Data.Set.map duplicate) . values
sample :: RandomGen g => d v w -> g -> (v, g)
--sample d g = (scanl1 (+) $ flip Prelude.map $ probability d, g) -- Will need to implement some sort of binary tree, most likely.
sampleIO :: d v w -> IO v
sampleIO = getStdRandom . sample
values :: d v w -> Set v
instance (Ord v, Fractional w) => Distribution d v w where
probability d v = probabilityOfRange d v v
instance Enum v => Distribution d v w where
probabilityOfRange d v1 v2 = sum $ Prelude.map (probability d) [v1..v2]
instance (Enum v, Ord v) => Distribution d v w where
values = fromList . (concatMap $ uncurry listRange) . toList . ranges
When I then try to add real instances (and comment out some of the "instances" I created earlier so that the compiler can reach that point), it gives me an error about conflicting instances.
data Empty v w = Empty
instance Distribution Empty v (Ratio Int8) where
sample _ g = (undefined, g)
sampleIO _ = return undefined
probabilityOfRange _ _ _ = 0
values _ = empty
data Singleton v w = Singleton v
instance Distribution Singleton v Integer where
sample (Singleton v) g = (v, g)
sampleIO (Singleton v) = return v
probabilityOfRange (Singleton v1) v2 v3
| v2 <= v1 && v1 <= v3 = 1
| otherwise = 0
data Uniform v w = Uniform (Set v)
To clarify, my goal is for probability
and values
to be defined for all Distributions
, and for probabilityOfRange
to be defined for all Distributions
with values deriving Ord
. I also wish to provide defaults when additional constraints are met, because without them, a reasonable default (based on other methods) is impossible.
Trying to specify a default for a single method using something like:
instance (Ord v, Fractional w) => Distribution d v w where
probability d v = probabilityOfRange d v v
won't work. Haskell instances don't "accumulate". For a given triple of types d v w
, at most one instance Distribution d v w
clause will apply. (If multiple clauses could apply because of "overlapping" instances, there are mechanisms to choose the "best" match, but there are no direct mechanisms to combine methods from multiple instance clauses.)
In general, if you have a class method:
class Distribution d v w where
probability :: d v w -> v w
and you'd like to define a default method with a more restrictive type signature (i.e., with constraints on some of the types):
probability :: (Ord v) => d v w -> v -> w
probability d v = probabilityOfRange d v v
there are two approaches.
The first is to make use of the DefaultSignatures
extension. This allows you to separate the type signature for the method from the (possibly more restrictive) type signature of the default method. The syntax is:
class Fractional w => Distribution d v w where
probability :: d v w -> v -> w
default probability :: (Ord v) => d v w -> v -> w
probability d v = probabilityOfRange d v v
...
The caveat here is that, if you define an instance that doesn't override the default method, then it must satisfy the constraint Ord v
, or it won't typecheck.
If you want more control over when the default method is used, then the usual approach is to separate the default definition out into a separate function that must be explicitly included in instances that wish to use it. So, you'd have:
class Fractional w => Distribution d v w where
probability :: d v w -> v -> w
probabilityDefault :: (Distribution d v w, Ord v) => d v w -> v -> w
probabilityDefault d v = probabilityOfRange d v v
and an instance that wishes to use the default must do so explicitly:
instance Distribution Whatever Int w where
probability = probabilityDefault