{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Lattices.UnitIntervalStructures.Lukasiewicz(
UILukasiewicz(UILukasiewicz),
BoundedLattice(..),
mkLukasiewiczUnitInterval,
fromLukasiewiczUnitInterval
) where
import Lattices.ResiduatedLattice
import Lattices.UnitInterval
newtype UILukasiewicz = UILukasiewicz UnitInterval
deriving (UILukasiewicz -> UILukasiewicz -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UILukasiewicz -> UILukasiewicz -> Bool
$c/= :: UILukasiewicz -> UILukasiewicz -> Bool
== :: UILukasiewicz -> UILukasiewicz -> Bool
$c== :: UILukasiewicz -> UILukasiewicz -> Bool
Eq, Eq UILukasiewicz
UILukasiewicz -> UILukasiewicz -> Bool
UILukasiewicz -> UILukasiewicz -> Ordering
UILukasiewicz -> UILukasiewicz -> UILukasiewicz
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UILukasiewicz -> UILukasiewicz -> UILukasiewicz
$cmin :: UILukasiewicz -> UILukasiewicz -> UILukasiewicz
max :: UILukasiewicz -> UILukasiewicz -> UILukasiewicz
$cmax :: UILukasiewicz -> UILukasiewicz -> UILukasiewicz
>= :: UILukasiewicz -> UILukasiewicz -> Bool
$c>= :: UILukasiewicz -> UILukasiewicz -> Bool
> :: UILukasiewicz -> UILukasiewicz -> Bool
$c> :: UILukasiewicz -> UILukasiewicz -> Bool
<= :: UILukasiewicz -> UILukasiewicz -> Bool
$c<= :: UILukasiewicz -> UILukasiewicz -> Bool
< :: UILukasiewicz -> UILukasiewicz -> Bool
$c< :: UILukasiewicz -> UILukasiewicz -> Bool
compare :: UILukasiewicz -> UILukasiewicz -> Ordering
$ccompare :: UILukasiewicz -> UILukasiewicz -> Ordering
Ord, Integer -> UILukasiewicz
UILukasiewicz -> UILukasiewicz
UILukasiewicz -> UILukasiewicz -> UILukasiewicz
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> UILukasiewicz
$cfromInteger :: Integer -> UILukasiewicz
signum :: UILukasiewicz -> UILukasiewicz
$csignum :: UILukasiewicz -> UILukasiewicz
abs :: UILukasiewicz -> UILukasiewicz
$cabs :: UILukasiewicz -> UILukasiewicz
negate :: UILukasiewicz -> UILukasiewicz
$cnegate :: UILukasiewicz -> UILukasiewicz
* :: UILukasiewicz -> UILukasiewicz -> UILukasiewicz
$c* :: UILukasiewicz -> UILukasiewicz -> UILukasiewicz
- :: UILukasiewicz -> UILukasiewicz -> UILukasiewicz
$c- :: UILukasiewicz -> UILukasiewicz -> UILukasiewicz
+ :: UILukasiewicz -> UILukasiewicz -> UILukasiewicz
$c+ :: UILukasiewicz -> UILukasiewicz -> UILukasiewicz
Num, Num UILukasiewicz
Ord UILukasiewicz
UILukasiewicz -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: UILukasiewicz -> Rational
$ctoRational :: UILukasiewicz -> Rational
Real, Fractional UILukasiewicz
Real UILukasiewicz
forall b. Integral b => UILukasiewicz -> b
forall b. Integral b => UILukasiewicz -> (b, UILukasiewicz)
forall a.
Real a
-> Fractional a
-> (forall b. Integral b => a -> (b, a))
-> (forall b. Integral b => a -> b)
-> (forall b. Integral b => a -> b)
-> (forall b. Integral b => a -> b)
-> (forall b. Integral b => a -> b)
-> RealFrac a
floor :: forall b. Integral b => UILukasiewicz -> b
$cfloor :: forall b. Integral b => UILukasiewicz -> b
ceiling :: forall b. Integral b => UILukasiewicz -> b
$cceiling :: forall b. Integral b => UILukasiewicz -> b
round :: forall b. Integral b => UILukasiewicz -> b
$cround :: forall b. Integral b => UILukasiewicz -> b
truncate :: forall b. Integral b => UILukasiewicz -> b
$ctruncate :: forall b. Integral b => UILukasiewicz -> b
properFraction :: forall b. Integral b => UILukasiewicz -> (b, UILukasiewicz)
$cproperFraction :: forall b. Integral b => UILukasiewicz -> (b, UILukasiewicz)
RealFrac, Num UILukasiewicz
Rational -> UILukasiewicz
UILukasiewicz -> UILukasiewicz
UILukasiewicz -> UILukasiewicz -> UILukasiewicz
forall a.
Num a
-> (a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a
fromRational :: Rational -> UILukasiewicz
$cfromRational :: Rational -> UILukasiewicz
recip :: UILukasiewicz -> UILukasiewicz
$crecip :: UILukasiewicz -> UILukasiewicz
/ :: UILukasiewicz -> UILukasiewicz -> UILukasiewicz
$c/ :: UILukasiewicz -> UILukasiewicz -> UILukasiewicz
Fractional)
instance BoundedLattice UILukasiewicz where
/\ :: UILukasiewicz -> UILukasiewicz -> UILukasiewicz
(/\) (UILukasiewicz UnitInterval
x) (UILukasiewicz UnitInterval
y) = UnitInterval -> UILukasiewicz
UILukasiewicz (UnitInterval
x forall l. BoundedLattice l => l -> l -> l
/\ UnitInterval
y)
\/ :: UILukasiewicz -> UILukasiewicz -> UILukasiewicz
(\/) (UILukasiewicz UnitInterval
x) (UILukasiewicz UnitInterval
y) = UnitInterval -> UILukasiewicz
UILukasiewicz (UnitInterval
x forall l. BoundedLattice l => l -> l -> l
\/ UnitInterval
y)
bot :: UILukasiewicz
bot = UnitInterval -> UILukasiewicz
UILukasiewicz forall l. BoundedLattice l => l
bot
top :: UILukasiewicz
top = UnitInterval -> UILukasiewicz
UILukasiewicz forall l. BoundedLattice l => l
top
mkLattice :: Double -> UILukasiewicz
mkLattice = Double -> UILukasiewicz
mkLukasiewiczUnitInterval
instance ResiduatedLattice UILukasiewicz where
tnorm :: UILukasiewicz -> UILukasiewicz -> UILukasiewicz
tnorm UILukasiewicz
a UILukasiewicz
b = (UILukasiewicz
a forall a. Num a => a -> a -> a
+ UILukasiewicz
b forall a. Num a => a -> a -> a
- forall l. BoundedLattice l => l
top) forall l. BoundedLattice l => l -> l -> l
\/ forall l. BoundedLattice l => l
bot
UILukasiewicz
a --> :: UILukasiewicz -> UILukasiewicz -> UILukasiewicz
--> UILukasiewicz
b = (forall l. BoundedLattice l => l
top forall a. Num a => a -> a -> a
- UILukasiewicz
a forall a. Num a => a -> a -> a
+ UILukasiewicz
b) forall l. BoundedLattice l => l -> l -> l
/\ forall l. BoundedLattice l => l
top
instance Show UILukasiewicz where
show :: UILukasiewicz -> String
show (UILukasiewicz UnitInterval
x) = forall a. Show a => a -> String
show UnitInterval
x
mkLukasiewiczUnitInterval :: Double -> UILukasiewicz
mkLukasiewiczUnitInterval :: Double -> UILukasiewicz
mkLukasiewiczUnitInterval Double
x = UnitInterval -> UILukasiewicz
UILukasiewicz forall a b. (a -> b) -> a -> b
$ Double -> UnitInterval
mkUnitInterval Double
x
fromLukasiewiczUnitInterval :: UILukasiewicz -> Double
fromLukasiewiczUnitInterval :: UILukasiewicz -> Double
fromLukasiewiczUnitInterval (UILukasiewicz (UnitInterval Double
x)) = Double
x