SciBaseTypes-0.1.1.0: Base types and classes for statistics, sciences and humanities
Safe HaskellNone
LanguageHaskell2010

Numeric.Discretized

Description

Discretized floating point numbers, where the scaling factor is kept as two phantom types denoting the rational number used for scaling.

Synopsis

Documentation

data RatioTy a Source #

Some discretizations are of the type ln 2 / 2 (PAM matrices in Blast for example). Using this type, we can annotate as follows: Discretized (RTyLn 2 :% RTyId 2).

One may use Unknown if the scale is not known. For example, the blast matrices use different scales internally and one needs to read the header to get the scale.

Constructors

RTyExp a 
RTyId a 
RTyLn a 
RTyPlus (RatioTy a) (RatioTy a) 
RTyTimes (RatioTy a) (RatioTy a) 
Unknown 

Instances

Instances details
KnownNat k => RatioTyConstant ('RTyExp k :: RatioTy Nat) Source # 
Instance details

Defined in Numeric.Discretized

KnownNat k => RatioTyConstant ('RTyId k :: RatioTy Nat) Source # 
Instance details

Defined in Numeric.Discretized

KnownNat k => RatioTyConstant ('RTyLn k :: RatioTy Nat) Source # 
Instance details

Defined in Numeric.Discretized

(RatioTyConstant a, RatioTyConstant b) => RatioTyConstant ('RTyTimes a b :: RatioTy k) Source # 
Instance details

Defined in Numeric.Discretized

(RatioTyConstant a, RatioTyConstant b) => RatioTyConstant ('RTyPlus a b :: RatioTy k) Source # 
Instance details

Defined in Numeric.Discretized

Num (Discretized ('Unknown :: RatioTy a)) Source # 
Instance details

Defined in Numeric.Discretized

class RatioTyConstant a where Source #

Instances

Instances details
KnownNat k => RatioTyConstant ('RTyExp k :: RatioTy Nat) Source # 
Instance details

Defined in Numeric.Discretized

KnownNat k => RatioTyConstant ('RTyId k :: RatioTy Nat) Source # 
Instance details

Defined in Numeric.Discretized

KnownNat k => RatioTyConstant ('RTyLn k :: RatioTy Nat) Source # 
Instance details

Defined in Numeric.Discretized

(KnownNat k, KnownNat l) => RatioTyConstant (k :% l :: Ratio Nat) Source # 
Instance details

Defined in Numeric.Discretized

(RatioTyConstant a, RatioTyConstant b) => RatioTyConstant ('RTyTimes a b :: RatioTy k) Source # 
Instance details

Defined in Numeric.Discretized

(RatioTyConstant a, RatioTyConstant b) => RatioTyConstant ('RTyPlus a b :: RatioTy k) Source # 
Instance details

Defined in Numeric.Discretized

newtype Discretized (b :: k) Source #

A discretized value takes a floating point number n and produces a discretized value. The actual discretization formula is given on the type level, freeing us from having to carry around some scaling function.

Typically, one might use types likes 100, (100 :% 1), or (RTyLn 2 :% RTyId 2).

The main use of a Discretized value is to enable calculations with Int while somewhat pretending to use floating point values.

Be careful with certain operations like (*) as they will easily cause the numbers to arbitrarily wrong. (+) and (-) are fine, however.

NOTE Export and import of data is in the form of floating points, which can lead to additional loss of precision if one is careless!

TODO fast Show methods required!

TODO blaze stuff?

TODO We might want to discretize LogDomain style values. This requires some thought on in which direction to wrap. Maybe, we want to log-domain Discretized values, which probably just works.

Constructors

Discretized 

Fields

Instances

Instances details
Vector Vector (Discretized t) Source # 
Instance details

Defined in Numeric.Discretized

MVector MVector (Discretized t) Source # 
Instance details

Defined in Numeric.Discretized

Enum (Discretized b) Source # 
Instance details

Defined in Numeric.Discretized

Eq (Discretized b) Source # 
Instance details

Defined in Numeric.Discretized

(KnownNat u, KnownNat l) => Fractional (Discretized (u :% l)) Source # 
Instance details

Defined in Numeric.Discretized

Methods

(/) :: Discretized (u :% l) -> Discretized (u :% l) -> Discretized (u :% l) #

recip :: Discretized (u :% l) -> Discretized (u :% l) #

fromRational :: Rational -> Discretized (u :% l) #

(KnownNat u, KnownNat l) => Num (Discretized (u :% l)) Source # 
Instance details

Defined in Numeric.Discretized

Methods

(+) :: Discretized (u :% l) -> Discretized (u :% l) -> Discretized (u :% l) #

(-) :: Discretized (u :% l) -> Discretized (u :% l) -> Discretized (u :% l) #

(*) :: Discretized (u :% l) -> Discretized (u :% l) -> Discretized (u :% l) #

negate :: Discretized (u :% l) -> Discretized (u :% l) #

abs :: Discretized (u :% l) -> Discretized (u :% l) #

signum :: Discretized (u :% l) -> Discretized (u :% l) #

fromInteger :: Integer -> Discretized (u :% l) #

Num (Discretized ('Unknown :: RatioTy a)) Source # 
Instance details

Defined in Numeric.Discretized

Ord (Discretized b) Source # 
Instance details

Defined in Numeric.Discretized

Read (Discretized b) Source # 
Instance details

Defined in Numeric.Discretized

(KnownNat u, KnownNat l) => Real (Discretized (u :% l)) Source # 
Instance details

Defined in Numeric.Discretized

Methods

toRational :: Discretized (u :% l) -> Rational #

Show (Discretized b) Source # 
Instance details

Defined in Numeric.Discretized

Generic (Discretized b) Source # 
Instance details

Defined in Numeric.Discretized

Associated Types

type Rep (Discretized b) :: Type -> Type #

Methods

from :: Discretized b -> Rep (Discretized b) x #

to :: Rep (Discretized b) x -> Discretized b #

Info (Discretized b) Source # 
Instance details

Defined in Numeric.Discretized

Methods

info :: Discretized b -> String #

Hashable (Discretized t) Source # 
Instance details

Defined in Numeric.Discretized

Methods

hashWithSalt :: Int -> Discretized t -> Int #

hash :: Discretized t -> Int #

(KnownNat k, KnownNat l) => ToJSON (Discretized (k :% l)) Source # 
Instance details

Defined in Numeric.Discretized

(KnownNat k, KnownNat l) => FromJSON (Discretized (k :% l)) Source # 
Instance details

Defined in Numeric.Discretized

Binary (Discretized t) Source # 
Instance details

Defined in Numeric.Discretized

Methods

put :: Discretized t -> Put #

get :: Get (Discretized t) #

putList :: [Discretized t] -> Put #

Serialize (Discretized t) Source # 
Instance details

Defined in Numeric.Discretized

Methods

put :: Putter (Discretized t) #

get :: Get (Discretized t) #

NFData (Discretized t) Source # 
Instance details

Defined in Numeric.Discretized

Methods

rnf :: Discretized t -> () #

Unbox (Discretized t) Source # 
Instance details

Defined in Numeric.Discretized

Num (Discretized k2) => Semiring (Discretized k2) Source # 
Instance details

Defined in Numeric.Discretized

NumericLimits (Discretized t) Source # 
Instance details

Defined in Numeric.Discretized

newtype MVector s (Discretized t) Source # 
Instance details

Defined in Numeric.Discretized

type Rep (Discretized b) Source # 
Instance details

Defined in Numeric.Discretized

type Rep (Discretized b) = D1 ('MetaData "Discretized" "Numeric.Discretized" "SciBaseTypes-0.1.1.0-3Dyd7liFoDd1V6ph3ZjwIR" 'True) (C1 ('MetaCons "Discretized" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDiscretized") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
newtype Vector (Discretized t) Source # 
Instance details

Defined in Numeric.Discretized

discretizeRatio :: forall a u l. (Real a, KnownNat u, KnownNat l) => a -> Discretized ((u :: Nat) :% (l :: Nat)) Source #

Discretizes any Real a into the Discretized value. This conversion is lossy and uses a type-level rational of u :% l!