{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE KindSignatures #-}
module Data.JoinSemilattice.Class.Fractional where
import Data.Hashable (Hashable)
import Data.JoinSemilattice.Defined (Defined)
import Data.JoinSemilattice.Intersect (Intersect)
import Data.JoinSemilattice.Class.Sum (SumR)
import Data.Kind (Type)
class SumR x => FractionalR (x :: Type) where
multiplyR :: ( x, x, x ) -> ( x, x, x )
default multiplyR :: Fractional x => ( x, x, x ) -> ( x, x, x )
multiplyR ( x, y, z ) = ( z / y, z / x, x * y )
divideR :: FractionalR x => ( x, x, x ) -> ( x, x, x )
divideR ( x, y, z ) = let ( z', y', x' ) = multiplyR ( z, y, x ) in ( x', y', z' )
recipR :: (FractionalR x, Num x) => ( x, x ) -> ( x, x )
recipR ( x, y ) = let ( x', y', _ ) = multiplyR ( x, y, 1 ) in ( x', y' )
instance (Eq x, Fractional x) => FractionalR (Defined x)
instance (Bounded x, Enum x, Eq x, Fractional x, Hashable x)
=> FractionalR (Intersect x)