{-# LANGUAGE CPP #-}
module Data.Random.Internal.Fixed where

import Data.Fixed
import Unsafe.Coerce

#ifdef old_Fixed
-- So much for backward compatibility through base (>=5) ...

resolutionOf :: HasResolution r => f r -> Integer
resolutionOf x = resolution (res x)
    where
        res :: HasResolution r => f r -> r
        res = undefined

resolutionOf2 :: HasResolution r => f (g r) -> Integer
resolutionOf2 x = resolution (res x)
    where
        res :: HasResolution r => f (g r) -> r
        res = undefined

#else

resolutionOf :: HasResolution r => f r -> Integer
resolutionOf :: f r -> Integer
resolutionOf = f r -> Integer
forall k (a :: k) (p :: k -> *). HasResolution a => p a -> Integer
resolution

resolutionOf2 :: HasResolution r => f (g r) -> Integer
resolutionOf2 :: f (g r) -> Integer
resolutionOf2 f (g r)
x = g r -> Integer
forall k (a :: k) (p :: k -> *). HasResolution a => p a -> Integer
resolution (f (g r) -> g r
forall r (f :: * -> *) (g :: * -> *).
HasResolution r =>
f (g r) -> g r
res f (g r)
x)
    where
        res :: HasResolution r => f (g r) -> g r
        res :: f (g r) -> g r
res = f (g r) -> g r
forall a. HasCallStack => a
undefined

#endif

-- |The 'Fixed' type doesn't expose its constructors, but I need a way to
-- convert them to and from their raw representation in order to sample
-- them.  As long as 'Fixed' is a newtype wrapping 'Integer', 'mkFixed' and
-- 'unMkFixed' as defined here will work.  Both are implemented using
-- 'unsafeCoerce'.
mkFixed :: Integer -> Fixed r
mkFixed :: Integer -> Fixed r
mkFixed = Integer -> Fixed r
forall a b. a -> b
unsafeCoerce

unMkFixed :: Fixed r -> Integer
unMkFixed :: Fixed r -> Integer
unMkFixed = Fixed r -> Integer
forall a b. a -> b
unsafeCoerce