3

I'm trying to write code to simulate random variables, and I want to keep things as polymorphic as possible. This may involve the use of type families, which are completely new to me.

Here is a simplified version of my code:

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}


data TrivialDist a = Trivial a

getVal :: TrivialDist a -> a
getVal (Trivial x) = x

class JointDist d a where
    toTrivialDist :: d a -> TrivialDist [a]

data TrivialJointDist a = TrivialJoint [a]

instance JointDist TrivialJointDist a where
    toTrivialDist :: TrivialJointDist a -> TrivialDist [a]
    toTrivialDist (TrivialJoint xs) = Trivial xs

class Simulable s a where
    type Samp s a :: *
    -- generates infinite stream of random samples from a distribution
    samples :: s a -> IO [Samp s a]
    -- generates a single random sample from a distribution
    sample :: s a -> IO (Samp s a)
    sample = fmap head . samples

instance Simulable TrivialDist a where
    type Samp TrivialDist a = a
    samples :: TrivialDist a -> IO [a]
    samples (Trivial x) = return $ repeat x

instance (JointDist d a) => Simulable d a where
    type Samp d a = [a]
    samples :: d a -> IO [[a]]
    samples = samples . toTrivialDist

When I load it into ghci, I get this error:

test.hs:30:10: error:
    Conflicting family instance declarations:
      Samp TrivialDist a = a -- Defined at test.hs:30:10
      Samp d a = [a] -- Defined at test.hs:40:10
   |
30 |     type Samp TrivialDist a = a
   |          ^^^^^^^^^^^^^^^^^^^^^^
Failed, 0 modules loaded.

This issue seems to resemble the one found here (the explanation seems to be that GHC can't distinguish the types based on the constraints), but no solution was proposed.

I can get the code to compile if I change the last instance declaration to:

instance Simulable TrivialJointDist a where
    type Samp TrivialJointDist a = [a]
    samples :: TrivialJointDist a -> IO [[a]]
    samples = samples . toTrivialDist

However, I then lose the advantage of polymorphism, as I would need to make separate instance declarations for each subtype of JointDist d a.

Any help is much appreciated!

  • 1
    Correct: you must make separate instance declarations for each instance of `JointDist`. That said there's several code smells here that make me think a much simpler design is warranted. Perhaps it would be possible to give better advice if you can answer this question: is there an instance of `JointDist` which is *not* isomorphic to a `TrivialDist` (and if so, what does it look like)? – Daniel Wagner Feb 16 '19 at 20:29
  • Alternatively you might want to check out some of the libraries that provide random variables for you. My preference is MonadBayes which implements a probability monad that allows sampling, conditioning, and inference. – C. Hammill Feb 16 '19 at 21:29

1 Answers1

0

After monkeying around a bit, I think I've found a solution that uses equality constraints instead of explicit type families:

class Simulable s a b where
    -- generates infinite stream of random samples from a distribution
    samples :: s a -> IO [b]
    -- generates a single random sample from a distribution
    sample :: s a -> IO b
    sample = fmap head . samples

instance (b ~ a) => Simulable TrivialDist a b where
    samples :: TrivialDist a -> IO [a]
    samples (Trivial x) = return $ repeat x

instance {-# OVERLAPPABLE #-} (JointDist d a, b ~ [a]) => Simulable d a b where
    samples :: d a -> IO [[a]]
    samples = samples . toTrivialDist

The {-# OVERLAPPABLE #-} pragma instructs GHC to allow the TrivialDist a b instance to overlap the d a b instance (otherwise we get an error).