{-# LANGUAGE TypeSynonymInstances #-} {-# OPTIONS_GHC -Wall -fno-warn-orphans #-} module FRP.Reactive.Num () where import FRP.Reactive.Behavior import Control.Applicative noOv :: String -> String -> a noOv ty meth = error $ meth ++ ": No overloading for " ++ ty noFun :: String -> a noFun = noOv "behavior" -- Eq & Show are prerequisites for Num, so they need to be faked here instance Eq (Behavior b) where (==) = noFun "(==)" (/=) = noFun "(/=)" instance Ord b => Ord (Behavior b) where min = liftA2 min max = liftA2 max instance Show (Behavior b) where show = noFun "show" showsPrec = noFun "showsPrec" showList = noFun "showList" instance Num b => Num (Behavior b) where negate = fmap negate (+) = liftA2 (+) (*) = liftA2 (*) fromInteger = pure . fromInteger abs = fmap abs signum = fmap signum instance Fractional b => Fractional (Behavior b) where recip = fmap recip fromRational = pure . fromRational instance Floating b => Floating (Behavior b) where pi = pure pi sqrt = fmap sqrt exp = fmap exp log = fmap log sin = fmap sin cos = fmap cos asin = fmap asin atan = fmap atan acos = fmap acos sinh = fmap sinh cosh = fmap cosh asinh = fmap asinh atanh = fmap atanh acosh = fmap acosh