module Synthesizer.Basic.Phase (
T,
fromRepresentative,
toRepresentative,
increment,
decrement,
multiply,
) where
import qualified Algebra.ToInteger as ToInteger
import qualified Algebra.RealRing as RealRing
import qualified Algebra.Ring as Ring
import qualified Algebra.Additive as Additive
import System.Random (Random(..))
import Test.QuickCheck (Arbitrary(arbitrary), choose)
import Foreign.Storable (Storable(..), )
import Foreign.Ptr (castPtr, )
import Data.Tuple.HT (mapFst, )
import qualified NumericPrelude.Numeric as NP
import NumericPrelude.Numeric
import NumericPrelude.Base
import Prelude ()
import qualified GHC.Float as GHC
newtype T a = Cons {decons :: a}
deriving Eq
instance Show a => Show (T a) where
showsPrec p x =
showParen (p >= 10)
(showString "Phase.fromRepresentative " . showsPrec 11 (toRepresentative x))
instance Storable a => Storable (T a) where
{-# INLINE sizeOf #-}
sizeOf = sizeOf . toRepresentative
{-# INLINE alignment #-}
alignment = alignment . toRepresentative
{-# INLINE peek #-}
peek ptr = fmap Cons $ peek (castPtr ptr)
{-# INLINE poke #-}
poke ptr = poke (castPtr ptr) . toRepresentative
instance (Ring.C a, Random a) => Random (T a) where
randomR = error "Phase.randomR makes no sense"
random = mapFst Cons . randomR (zero, one)
instance (Ring.C a, Random a) => Arbitrary (T a) where
arbitrary = fmap Cons $ choose (zero, one)
{-# INLINE fromRepresentative #-}
fromRepresentative :: RealRing.C a => a -> T a
fromRepresentative = Cons . RealRing.fraction
{-# INLINE toRepresentative #-}
toRepresentative :: T a -> a
toRepresentative = decons
{-# INLINE increment #-}
increment :: RealRing.C a => a -> T a -> T a
increment d = lift (d Additive.+)
{-# INLINE decrement #-}
decrement :: RealRing.C a => a -> T a -> T a
decrement d = lift (Additive.subtract d)
{-# INLINE add #-}
add :: (Ring.C a, Ord a) => T a -> T a -> T a
add (Cons x) (Cons y) =
let z = x+y
in Cons $ if z>=one then z-one else z
{-# INLINE sub #-}
sub :: (Ring.C a, Ord a) => T a -> T a -> T a
sub (Cons x) (Cons y) =
let z = x-y
in Cons $ if z<zero then z+one else z
{-# INLINE neg #-}
neg :: (Ring.C a, Ord a) => T a -> T a
neg (Cons x) =
Cons $ if x==zero then zero else one-x
{-# INLINE multiply #-}
multiply :: (RealRing.C a, ToInteger.C b) => b -> T a -> T a
multiply n = lift (NP.fromIntegral n Ring.*)
instance RealRing.C a => Additive.C (T a) where
{-# INLINE zero #-}
{-# INLINE (+) #-}
{-# INLINE (-) #-}
{-# INLINE negate #-}
zero = Cons Additive.zero
(+) = add
(-) = sub
negate = neg
{-# INLINE lift #-}
lift :: (RealRing.C b) =>
(a -> b) -> T a -> T b
lift f =
fromRepresentative . f . toRepresentative
{-# INLINE customFromRepresentative #-}
customFromRepresentative ::
(Additive.C a) =>
(a -> i) -> (i -> a) -> a -> T a
customFromRepresentative toInt fromInt x =
Cons (x Additive.- fromInt (toInt x))
{-# INLINE customLift #-}
customLift ::
(Additive.C b) =>
(b -> i) -> (i -> b) ->
(a -> b) -> T a -> T b
customLift toInt fromInt f =
customFromRepresentative toInt fromInt . f . toRepresentative
{-# INLINE customMultiply #-}
customMultiply ::
(Ring.C a, Ord a, ToInteger.C b) =>
(a -> i) -> (i -> a) ->
b -> T a -> T a
customMultiply toInt fromInt n (Cons x) =
customFromRepresentative toInt fromInt $
if n<zero && x>zero
then (one-x) * NP.fromIntegral (NP.negate n)
else x * NP.fromIntegral n
{-# RULES
"Phase.multiply @ Float" multiply = customMultiply GHC.float2Int GHC.int2Float;
"Phase.multiply @ Double" multiply = customMultiply GHC.double2Int GHC.int2Double;
"Phase.increment @ Float" increment = \d -> customLift GHC.float2Int GHC.int2Float (+d);
"Phase.increment @ Double" increment = \d -> customLift GHC.double2Int GHC.int2Double (+d);
"Phase.decrement @ Float" decrement = \d -> customLift GHC.float2Int GHC.int2Float (subtract d);
"Phase.decrement @ Double" decrement = \d -> customLift GHC.double2Int GHC.int2Double (subtract d);
#-}