module Data.Sign
(
Sign (..)
, negate
, abs
, mult
, recip
, div
, pow
, signOf
, symbol
) where
import qualified Prelude as P
import Prelude hiding (negate, abs, recip, div)
import Algebra.Enumerable (Enumerable (..), universeBounded)
import qualified Algebra.Lattice as L
import Control.DeepSeq
import Data.Hashable
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Typeable
import Data.Data
data Sign
= Neg
| Zero
| Pos
deriving (Eq, Ord, Show, Read, Enum, Bounded, Typeable, Data)
instance NFData Sign where rnf x = seq x ()
instance Hashable Sign where hashWithSalt = hashUsing fromEnum
instance Enumerable Sign where
universe = universeBounded
negate :: Sign -> Sign
negate Neg = Pos
negate Zero = Zero
negate Pos = Neg
abs :: Sign -> Sign
abs Neg = Pos
abs Zero = Zero
abs Pos = Pos
mult :: Sign -> Sign -> Sign
mult Pos s = s
mult s Pos = s
mult Neg s = negate s
mult s Neg = negate s
mult _ _ = Zero
recip :: Sign -> Sign
recip Pos = Pos
recip Zero = error "Data.Sign.recip: division by Zero"
recip Neg = Neg
div :: Sign -> Sign -> Sign
div s Pos = s
div _ Zero = error "Data.Sign.div: division by Zero"
div s Neg = negate s
pow :: Integral x => Sign -> x -> Sign
pow _ 0 = Pos
pow Pos _ = Pos
pow Zero _ = Zero
pow Neg n = if even n then Pos else Neg
signOf :: Real a => a -> Sign
signOf r =
case r `compare` 0 of
LT -> Neg
EQ -> Zero
GT -> Pos
symbol :: Sign -> String
symbol Pos = "+"
symbol Neg = "-"
symbol Zero = "0"
instance L.MeetSemiLattice (Set Sign) where
meet = Set.intersection
instance L.Lattice (Set Sign)
instance L.BoundedMeetSemiLattice (Set Sign) where
top = Set.fromList universe
instance L.BoundedLattice (Set Sign)
instance Num (Set Sign) where
ss1 + ss2 = Set.unions [f s1 s2 | s1 <- Set.toList ss1, s2 <- Set.toList ss2]
where
f Zero s = Set.singleton s
f s Zero = Set.singleton s
f Pos Pos = Set.singleton Pos
f Neg Neg = Set.singleton Neg
f _ _ = Set.fromList [Neg,Zero,Pos]
ss1 * ss2 = Set.fromList [mult s1 s2 | s1 <- Set.toList ss1, s2 <- Set.toList ss2]
negate = Set.map negate
abs = Set.map abs
signum = id
fromInteger = Set.singleton . signOf
instance Fractional (Set Sign) where
recip = Set.map recip
fromRational = Set.singleton . signOf
#if !MIN_VERSION_hashable(1,2,0)
hashUsing :: (Hashable b) =>
(a -> b)
-> Int
-> a
-> Int
hashUsing f salt x = hashWithSalt salt (f x)
#endif