coya-0.1: Coya monoids

Safe HaskellNone
LanguageHaskell2010

Coya

Description

Consider some log-semiring R. Then, for any two x,y :: R, the following holds:

x ^ log y == y ^ log x == e ^ (log x * log y)

Coya is a commutative monoid (R, y = x ^ log y.

The following laws hold:

Left Identity
e # x == x
Right Identity
x # e == x
Associativity
(x # y) # z == x # (y # z)
Commutativity
x # y == y # x

If R is a poset where all elements in R are greater than one, then R also forms a group:

x # (exp (1 / log x)) = x
Synopsis

Documentation

newtype Coya a Source #

The Coya monoid. Its semigroup instance is a binary operation that distributes over multiplication, i.e:

Coya x <> (Coya y * Coya z) == (Coya x <> Coya y) * (Coya x <> Coya z)

The Semiring and Num instances simply lift the underlying type's.

Constructors

Coya 

Fields

Instances
Eq a => Eq (Coya a) Source # 
Instance details

Defined in Coya

Methods

(==) :: Coya a -> Coya a -> Bool #

(/=) :: Coya a -> Coya a -> Bool #

Floating a => Floating (Coya a) Source # 
Instance details

Defined in Coya

Methods

pi :: Coya a #

exp :: Coya a -> Coya a #

log :: Coya a -> Coya a #

sqrt :: Coya a -> Coya a #

(**) :: Coya a -> Coya a -> Coya a #

logBase :: Coya a -> Coya a -> Coya a #

sin :: Coya a -> Coya a #

cos :: Coya a -> Coya a #

tan :: Coya a -> Coya a #

asin :: Coya a -> Coya a #

acos :: Coya a -> Coya a #

atan :: Coya a -> Coya a #

sinh :: Coya a -> Coya a #

cosh :: Coya a -> Coya a #

tanh :: Coya a -> Coya a #

asinh :: Coya a -> Coya a #

acosh :: Coya a -> Coya a #

atanh :: Coya a -> Coya a #

log1p :: Coya a -> Coya a #

expm1 :: Coya a -> Coya a #

log1pexp :: Coya a -> Coya a #

log1mexp :: Coya a -> Coya a #

Fractional a => Fractional (Coya a) Source # 
Instance details

Defined in Coya

Methods

(/) :: Coya a -> Coya a -> Coya a #

recip :: Coya a -> Coya a #

fromRational :: Rational -> Coya a #

Num a => Num (Coya a) Source # 
Instance details

Defined in Coya

Methods

(+) :: Coya a -> Coya a -> Coya a #

(-) :: Coya a -> Coya a -> Coya a #

(*) :: Coya a -> Coya a -> Coya a #

negate :: Coya a -> Coya a #

abs :: Coya a -> Coya a #

signum :: Coya a -> Coya a #

fromInteger :: Integer -> Coya a #

Ord a => Ord (Coya a) Source # 
Instance details

Defined in Coya

Methods

compare :: Coya a -> Coya a -> Ordering #

(<) :: Coya a -> Coya a -> Bool #

(<=) :: Coya a -> Coya a -> Bool #

(>) :: Coya a -> Coya a -> Bool #

(>=) :: Coya a -> Coya a -> Bool #

max :: Coya a -> Coya a -> Coya a #

min :: Coya a -> Coya a -> Coya a #

Read a => Read (Coya a) Source # 
Instance details

Defined in Coya

Real a => Real (Coya a) Source # 
Instance details

Defined in Coya

Methods

toRational :: Coya a -> Rational #

RealFloat a => RealFloat (Coya a) Source # 
Instance details

Defined in Coya

RealFrac a => RealFrac (Coya a) Source # 
Instance details

Defined in Coya

Methods

properFraction :: Integral b => Coya a -> (b, Coya a) #

truncate :: Integral b => Coya a -> b #

round :: Integral b => Coya a -> b #

ceiling :: Integral b => Coya a -> b #

floor :: Integral b => Coya a -> b #

Show a => Show (Coya a) Source # 
Instance details

Defined in Coya

Methods

showsPrec :: Int -> Coya a -> ShowS #

show :: Coya a -> String #

showList :: [Coya a] -> ShowS #

Floating a => Semigroup (Coya a) Source #
Coya x <> Coya y == Coya (x ** log y)
Instance details

Defined in Coya

Methods

(<>) :: Coya a -> Coya a -> Coya a #

sconcat :: NonEmpty (Coya a) -> Coya a #

stimes :: Integral b => b -> Coya a -> Coya a #

Floating a => Monoid (Coya a) Source #
mempty == e
Instance details

Defined in Coya

Methods

mempty :: Coya a #

mappend :: Coya a -> Coya a -> Coya a #

mconcat :: [Coya a] -> Coya a #

Storable a => Storable (Coya a) Source # 
Instance details

Defined in Coya

Methods

sizeOf :: Coya a -> Int #

alignment :: Coya a -> Int #

peekElemOff :: Ptr (Coya a) -> Int -> IO (Coya a) #

pokeElemOff :: Ptr (Coya a) -> Int -> Coya a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Coya a) #

pokeByteOff :: Ptr b -> Int -> Coya a -> IO () #

peek :: Ptr (Coya a) -> IO (Coya a) #

poke :: Ptr (Coya a) -> Coya a -> IO () #

Prim a => Prim (Coya a) Source # 
Instance details

Defined in Coya

Semiring a => Semiring (Coya a) Source # 
Instance details

Defined in Coya

Methods

plus :: Coya a -> Coya a -> Coya a #

zero :: Coya a #

times :: Coya a -> Coya a -> Coya a #

one :: Coya a #

Ring a => Ring (Coya a) Source # 
Instance details

Defined in Coya

Methods

negate :: Coya a -> Coya a #

newtype CoyaGroup a Source #

The Coya monoid constrained to numbers which are greater than 1. This ensures that the group property of inversion holds:

x <> (exp (1 / log x)) == x

Constructors

CoyaGroup 

Fields

Instances
(Floating a, Ord a) => Semigroup (CoyaGroup a) Source #

Equivalent to the Semigroup instance for Coya.

Instance details

Defined in Coya

Methods

(<>) :: CoyaGroup a -> CoyaGroup a -> CoyaGroup a #

sconcat :: NonEmpty (CoyaGroup a) -> CoyaGroup a #

stimes :: Integral b => b -> CoyaGroup a -> CoyaGroup a #

(Floating a, Ord a) => Monoid (CoyaGroup a) Source #

Equivalent to the Monoid instance for Coya.

Instance details

Defined in Coya

(Floating a, Ord a) => Group (CoyaGroup a) Source #
x <> (exp (1 / log x)) == x
Instance details

Defined in Coya

Methods

invert :: CoyaGroup a -> CoyaGroup a #

pow :: Integral x => CoyaGroup a -> x -> CoyaGroup a #

coyaGroup :: forall a. (Ord a, Num a) => a -> Maybe (CoyaGroup a) Source #

A smart constructor for CoyaGroup.