module Data.Units.NonStd.Frequency where
import Control.Exception
import Data.Word
import Data.Fixed
import GHC.TypeLits
import Data.Proxy
import Data.Units.Base
import Data.Units.SI.System
newtype Tet (b :: Nat) (offs :: ZZ) a = Tet a
deriving ( Int -> Tet b offs a -> ShowS
[Tet b offs a] -> ShowS
Tet b offs a -> String
(Int -> Tet b offs a -> ShowS)
-> (Tet b offs a -> String)
-> ([Tet b offs a] -> ShowS)
-> Show (Tet b offs a)
forall (b :: Nat) (offs :: ZZ) a.
Show a =>
Int -> Tet b offs a -> ShowS
forall (b :: Nat) (offs :: ZZ) a. Show a => [Tet b offs a] -> ShowS
forall (b :: Nat) (offs :: ZZ) a. Show a => Tet b offs a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall (b :: Nat) (offs :: ZZ) a.
Show a =>
Int -> Tet b offs a -> ShowS
showsPrec :: Int -> Tet b offs a -> ShowS
$cshow :: forall (b :: Nat) (offs :: ZZ) a. Show a => Tet b offs a -> String
show :: Tet b offs a -> String
$cshowList :: forall (b :: Nat) (offs :: ZZ) a. Show a => [Tet b offs a] -> ShowS
showList :: [Tet b offs a] -> ShowS
Show, Tet b offs a -> Tet b offs a -> Bool
(Tet b offs a -> Tet b offs a -> Bool)
-> (Tet b offs a -> Tet b offs a -> Bool) -> Eq (Tet b offs a)
forall (b :: Nat) (offs :: ZZ) a.
Eq a =>
Tet b offs a -> Tet b offs a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall (b :: Nat) (offs :: ZZ) a.
Eq a =>
Tet b offs a -> Tet b offs a -> Bool
== :: Tet b offs a -> Tet b offs a -> Bool
$c/= :: forall (b :: Nat) (offs :: ZZ) a.
Eq a =>
Tet b offs a -> Tet b offs a -> Bool
/= :: Tet b offs a -> Tet b offs a -> Bool
Eq, Eq (Tet b offs a)
Eq (Tet b offs a) =>
(Tet b offs a -> Tet b offs a -> Ordering)
-> (Tet b offs a -> Tet b offs a -> Bool)
-> (Tet b offs a -> Tet b offs a -> Bool)
-> (Tet b offs a -> Tet b offs a -> Bool)
-> (Tet b offs a -> Tet b offs a -> Bool)
-> (Tet b offs a -> Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a -> Tet b offs a)
-> Ord (Tet b offs a)
Tet b offs a -> Tet b offs a -> Bool
Tet b offs a -> Tet b offs a -> Ordering
Tet b offs a -> Tet b offs a -> Tet b offs a
forall (b :: Nat) (offs :: ZZ) a. Ord a => Eq (Tet b offs a)
forall (b :: Nat) (offs :: ZZ) a.
Ord a =>
Tet b offs a -> Tet b offs a -> Bool
forall (b :: Nat) (offs :: ZZ) a.
Ord a =>
Tet b offs a -> Tet b offs a -> Ordering
forall (b :: Nat) (offs :: ZZ) a.
Ord a =>
Tet b offs a -> Tet b offs a -> Tet b offs a
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
$ccompare :: forall (b :: Nat) (offs :: ZZ) a.
Ord a =>
Tet b offs a -> Tet b offs a -> Ordering
compare :: Tet b offs a -> Tet b offs a -> Ordering
$c< :: forall (b :: Nat) (offs :: ZZ) a.
Ord a =>
Tet b offs a -> Tet b offs a -> Bool
< :: Tet b offs a -> Tet b offs a -> Bool
$c<= :: forall (b :: Nat) (offs :: ZZ) a.
Ord a =>
Tet b offs a -> Tet b offs a -> Bool
<= :: Tet b offs a -> Tet b offs a -> Bool
$c> :: forall (b :: Nat) (offs :: ZZ) a.
Ord a =>
Tet b offs a -> Tet b offs a -> Bool
> :: Tet b offs a -> Tet b offs a -> Bool
$c>= :: forall (b :: Nat) (offs :: ZZ) a.
Ord a =>
Tet b offs a -> Tet b offs a -> Bool
>= :: Tet b offs a -> Tet b offs a -> Bool
$cmax :: forall (b :: Nat) (offs :: ZZ) a.
Ord a =>
Tet b offs a -> Tet b offs a -> Tet b offs a
max :: Tet b offs a -> Tet b offs a -> Tet b offs a
$cmin :: forall (b :: Nat) (offs :: ZZ) a.
Ord a =>
Tet b offs a -> Tet b offs a -> Tet b offs a
min :: Tet b offs a -> Tet b offs a -> Tet b offs a
Ord, Integer -> Tet b offs a
Tet b offs a -> Tet b offs a
Tet b offs a -> Tet b offs a -> Tet b offs a
(Tet b offs a -> Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a)
-> (Integer -> Tet b offs a)
-> Num (Tet b offs a)
forall (b :: Nat) (offs :: ZZ) a. Num a => Integer -> Tet b offs a
forall (b :: Nat) (offs :: ZZ) a.
Num a =>
Tet b offs a -> Tet b offs a
forall (b :: Nat) (offs :: ZZ) a.
Num a =>
Tet b offs a -> Tet b offs a -> Tet b offs a
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: forall (b :: Nat) (offs :: ZZ) a.
Num a =>
Tet b offs a -> Tet b offs a -> Tet b offs a
+ :: Tet b offs a -> Tet b offs a -> Tet b offs a
$c- :: forall (b :: Nat) (offs :: ZZ) a.
Num a =>
Tet b offs a -> Tet b offs a -> Tet b offs a
- :: Tet b offs a -> Tet b offs a -> Tet b offs a
$c* :: forall (b :: Nat) (offs :: ZZ) a.
Num a =>
Tet b offs a -> Tet b offs a -> Tet b offs a
* :: Tet b offs a -> Tet b offs a -> Tet b offs a
$cnegate :: forall (b :: Nat) (offs :: ZZ) a.
Num a =>
Tet b offs a -> Tet b offs a
negate :: Tet b offs a -> Tet b offs a
$cabs :: forall (b :: Nat) (offs :: ZZ) a.
Num a =>
Tet b offs a -> Tet b offs a
abs :: Tet b offs a -> Tet b offs a
$csignum :: forall (b :: Nat) (offs :: ZZ) a.
Num a =>
Tet b offs a -> Tet b offs a
signum :: Tet b offs a -> Tet b offs a
$cfromInteger :: forall (b :: Nat) (offs :: ZZ) a. Num a => Integer -> Tet b offs a
fromInteger :: Integer -> Tet b offs a
Num, Num (Tet b offs a)
Num (Tet b offs a) =>
(Tet b offs a -> Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a)
-> (Rational -> Tet b offs a)
-> Fractional (Tet b offs a)
Rational -> Tet b offs a
Tet b offs a -> Tet b offs a
Tet b offs a -> Tet b offs a -> Tet b offs a
forall (b :: Nat) (offs :: ZZ) a.
Fractional a =>
Num (Tet b offs a)
forall (b :: Nat) (offs :: ZZ) a.
Fractional a =>
Rational -> Tet b offs a
forall (b :: Nat) (offs :: ZZ) a.
Fractional a =>
Tet b offs a -> Tet b offs a
forall (b :: Nat) (offs :: ZZ) a.
Fractional a =>
Tet b offs a -> Tet b offs a -> Tet b offs a
forall a.
Num a =>
(a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a
$c/ :: forall (b :: Nat) (offs :: ZZ) a.
Fractional a =>
Tet b offs a -> Tet b offs a -> Tet b offs a
/ :: Tet b offs a -> Tet b offs a -> Tet b offs a
$crecip :: forall (b :: Nat) (offs :: ZZ) a.
Fractional a =>
Tet b offs a -> Tet b offs a
recip :: Tet b offs a -> Tet b offs a
$cfromRational :: forall (b :: Nat) (offs :: ZZ) a.
Fractional a =>
Rational -> Tet b offs a
fromRational :: Rational -> Tet b offs a
Fractional, Fractional (Tet b offs a)
Tet b offs a
Fractional (Tet b offs a) =>
Tet b offs a
-> (Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Tet b offs a)
-> Floating (Tet b offs a)
Tet b offs a -> Tet b offs a
Tet b offs a -> Tet b offs a -> Tet b offs a
forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Fractional (Tet b offs a)
forall (b :: Nat) (offs :: ZZ) a. Floating a => Tet b offs a
forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a
forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a -> Tet b offs a
forall a.
Fractional a =>
a
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> Floating a
$cpi :: forall (b :: Nat) (offs :: ZZ) a. Floating a => Tet b offs a
pi :: Tet b offs a
$cexp :: forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a
exp :: Tet b offs a -> Tet b offs a
$clog :: forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a
log :: Tet b offs a -> Tet b offs a
$csqrt :: forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a
sqrt :: Tet b offs a -> Tet b offs a
$c** :: forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a -> Tet b offs a
** :: Tet b offs a -> Tet b offs a -> Tet b offs a
$clogBase :: forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a -> Tet b offs a
logBase :: Tet b offs a -> Tet b offs a -> Tet b offs a
$csin :: forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a
sin :: Tet b offs a -> Tet b offs a
$ccos :: forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a
cos :: Tet b offs a -> Tet b offs a
$ctan :: forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a
tan :: Tet b offs a -> Tet b offs a
$casin :: forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a
asin :: Tet b offs a -> Tet b offs a
$cacos :: forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a
acos :: Tet b offs a -> Tet b offs a
$catan :: forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a
atan :: Tet b offs a -> Tet b offs a
$csinh :: forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a
sinh :: Tet b offs a -> Tet b offs a
$ccosh :: forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a
cosh :: Tet b offs a -> Tet b offs a
$ctanh :: forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a
tanh :: Tet b offs a -> Tet b offs a
$casinh :: forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a
asinh :: Tet b offs a -> Tet b offs a
$cacosh :: forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a
acosh :: Tet b offs a -> Tet b offs a
$catanh :: forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a
atanh :: Tet b offs a -> Tet b offs a
$clog1p :: forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a
log1p :: Tet b offs a -> Tet b offs a
$cexpm1 :: forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a
expm1 :: Tet b offs a -> Tet b offs a
$clog1pexp :: forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a
log1pexp :: Tet b offs a -> Tet b offs a
$clog1mexp :: forall (b :: Nat) (offs :: ZZ) a.
Floating a =>
Tet b offs a -> Tet b offs a
log1mexp :: Tet b offs a -> Tet b offs a
Floating, Num (Tet b offs a)
Ord (Tet b offs a)
(Num (Tet b offs a), Ord (Tet b offs a)) =>
(Tet b offs a -> Rational) -> Real (Tet b offs a)
Tet b offs a -> Rational
forall (b :: Nat) (offs :: ZZ) a. Real a => Num (Tet b offs a)
forall (b :: Nat) (offs :: ZZ) a. Real a => Ord (Tet b offs a)
forall (b :: Nat) (offs :: ZZ) a.
Real a =>
Tet b offs a -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: forall (b :: Nat) (offs :: ZZ) a.
Real a =>
Tet b offs a -> Rational
toRational :: Tet b offs a -> Rational
Real
, Fractional (Tet b offs a)
Real (Tet b offs a)
(Real (Tet b offs a), Fractional (Tet b offs a)) =>
(forall b. Integral b => Tet b offs a -> (b, Tet b offs a))
-> (forall b. Integral b => Tet b offs a -> b)
-> (forall b. Integral b => Tet b offs a -> b)
-> (forall b. Integral b => Tet b offs a -> b)
-> (forall b. Integral b => Tet b offs a -> b)
-> RealFrac (Tet b offs a)
forall (b :: Nat) (offs :: ZZ) a.
RealFrac a =>
Fractional (Tet b offs a)
forall (b :: Nat) (offs :: ZZ) a. RealFrac a => Real (Tet b offs a)
forall (b :: Nat) (offs :: ZZ) a b.
(RealFrac a, Integral b) =>
Tet b offs a -> b
forall (b :: Nat) (offs :: ZZ) a b.
(RealFrac a, Integral b) =>
Tet b offs a -> (b, Tet b offs a)
forall b. Integral b => Tet b offs a -> b
forall b. Integral b => Tet b offs a -> (b, Tet b offs a)
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
$cproperFraction :: forall (b :: Nat) (offs :: ZZ) a b.
(RealFrac a, Integral b) =>
Tet b offs a -> (b, Tet b offs a)
properFraction :: forall b. Integral b => Tet b offs a -> (b, Tet b offs a)
$ctruncate :: forall (b :: Nat) (offs :: ZZ) a b.
(RealFrac a, Integral b) =>
Tet b offs a -> b
truncate :: forall b. Integral b => Tet b offs a -> b
$cround :: forall (b :: Nat) (offs :: ZZ) a b.
(RealFrac a, Integral b) =>
Tet b offs a -> b
round :: forall b. Integral b => Tet b offs a -> b
$cceiling :: forall (b :: Nat) (offs :: ZZ) a b.
(RealFrac a, Integral b) =>
Tet b offs a -> b
ceiling :: forall b. Integral b => Tet b offs a -> b
$cfloor :: forall (b :: Nat) (offs :: ZZ) a b.
(RealFrac a, Integral b) =>
Tet b offs a -> b
floor :: forall b. Integral b => Tet b offs a -> b
RealFrac, Floating (Tet b offs a)
RealFrac (Tet b offs a)
(RealFrac (Tet b offs a), Floating (Tet b offs a)) =>
(Tet b offs a -> Integer)
-> (Tet b offs a -> Int)
-> (Tet b offs a -> (Int, Int))
-> (Tet b offs a -> (Integer, Int))
-> (Integer -> Int -> Tet b offs a)
-> (Tet b offs a -> Int)
-> (Tet b offs a -> Tet b offs a)
-> (Int -> Tet b offs a -> Tet b offs a)
-> (Tet b offs a -> Bool)
-> (Tet b offs a -> Bool)
-> (Tet b offs a -> Bool)
-> (Tet b offs a -> Bool)
-> (Tet b offs a -> Bool)
-> (Tet b offs a -> Tet b offs a -> Tet b offs a)
-> RealFloat (Tet b offs a)
Int -> Tet b offs a -> Tet b offs a
Integer -> Int -> Tet b offs a
Tet b offs a -> Bool
Tet b offs a -> Int
Tet b offs a -> Integer
Tet b offs a -> (Int, Int)
Tet b offs a -> (Integer, Int)
Tet b offs a -> Tet b offs a
Tet b offs a -> Tet b offs a -> Tet b offs a
forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Floating (Tet b offs a)
forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
RealFrac (Tet b offs a)
forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Int -> Tet b offs a -> Tet b offs a
forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Integer -> Int -> Tet b offs a
forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Tet b offs a -> Bool
forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Tet b offs a -> Int
forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Tet b offs a -> Integer
forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Tet b offs a -> (Int, Int)
forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Tet b offs a -> (Integer, Int)
forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Tet b offs a -> Tet b offs a
forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Tet b offs a -> Tet b offs a -> Tet b offs a
forall a.
(RealFrac a, Floating a) =>
(a -> Integer)
-> (a -> Int)
-> (a -> (Int, Int))
-> (a -> (Integer, Int))
-> (Integer -> Int -> a)
-> (a -> Int)
-> (a -> a)
-> (Int -> a -> a)
-> (a -> Bool)
-> (a -> Bool)
-> (a -> Bool)
-> (a -> Bool)
-> (a -> Bool)
-> (a -> a -> a)
-> RealFloat a
$cfloatRadix :: forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Tet b offs a -> Integer
floatRadix :: Tet b offs a -> Integer
$cfloatDigits :: forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Tet b offs a -> Int
floatDigits :: Tet b offs a -> Int
$cfloatRange :: forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Tet b offs a -> (Int, Int)
floatRange :: Tet b offs a -> (Int, Int)
$cdecodeFloat :: forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Tet b offs a -> (Integer, Int)
decodeFloat :: Tet b offs a -> (Integer, Int)
$cencodeFloat :: forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Integer -> Int -> Tet b offs a
encodeFloat :: Integer -> Int -> Tet b offs a
$cexponent :: forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Tet b offs a -> Int
exponent :: Tet b offs a -> Int
$csignificand :: forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Tet b offs a -> Tet b offs a
significand :: Tet b offs a -> Tet b offs a
$cscaleFloat :: forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Int -> Tet b offs a -> Tet b offs a
scaleFloat :: Int -> Tet b offs a -> Tet b offs a
$cisNaN :: forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Tet b offs a -> Bool
isNaN :: Tet b offs a -> Bool
$cisInfinite :: forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Tet b offs a -> Bool
isInfinite :: Tet b offs a -> Bool
$cisDenormalized :: forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Tet b offs a -> Bool
isDenormalized :: Tet b offs a -> Bool
$cisNegativeZero :: forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Tet b offs a -> Bool
isNegativeZero :: Tet b offs a -> Bool
$cisIEEE :: forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Tet b offs a -> Bool
isIEEE :: Tet b offs a -> Bool
$catan2 :: forall (b :: Nat) (offs :: ZZ) a.
RealFloat a =>
Tet b offs a -> Tet b offs a -> Tet b offs a
atan2 :: Tet b offs a -> Tet b offs a -> Tet b offs a
RealFloat)
instance (Floating a, KnownNat b, KnownInt offs)
=> ConvertibleUnit (Tet b offs) a where
toBaseUnit :: Tet b offs a -> BaseUnitOf (Tet b offs) a
toBaseUnit (Tet a
a) = a -> BaseUnitOf (Tet b offs) a
forall (u :: Unit) a. IsUnit u => a -> u a
quantity (a -> BaseUnitOf (Tet b offs) a) -> a -> BaseUnitOf (Tet b offs) a
forall a b. (a -> b) -> a -> b
$ a
440 a -> a -> a
forall a. Num a => a -> a -> a
* a
2 a -> a -> a
forall a. Floating a => a -> a -> a
** ((a
a a -> a -> a
forall a. Num a => a -> a -> a
+ a
offs) a -> a -> a
forall a. Fractional a => a -> a -> a
/ a
b)
where
b :: a
b = Integer -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> a) -> Integer -> a
forall a b. (a -> b) -> a -> b
$ Proxy b -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy b
forall {k} (t :: k). Proxy t
Proxy :: Proxy b)
offs :: a
offs = Integer -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Proxy offs -> Integer
forall (r :: ZZ) (proxy :: ZZ -> *).
KnownInt r =>
proxy r -> Integer
forall (proxy :: ZZ -> *). proxy offs -> Integer
intVal (Proxy offs
forall {k} (t :: k). Proxy t
Proxy :: Proxy offs)) a -> a -> a
forall a. Fractional a => a -> a -> a
/ a
100
fromBaseUnit :: BaseUnitOf (Tet b offs) a -> Tet b offs a
fromBaseUnit BaseUnitOf (Tet b offs) a
a = a -> Tet b offs a
forall (b :: Nat) (offs :: ZZ) a. a -> Tet b offs a
Tet (a -> Tet b offs a) -> a -> Tet b offs a
forall a b. (a -> b) -> a -> b
$ a
b a -> a -> a
forall a. Num a => a -> a -> a
* a -> a -> a
forall a. Floating a => a -> a -> a
logBase a
2 ((.^.) Second ('Neg 1) a -> a
forall (u :: Unit) a. IsUnit u => u a -> a
unQuantity (.^.) Second ('Neg 1) a
BaseUnitOf (Tet b offs) a
aa -> a -> a
forall a. Fractional a => a -> a -> a
/ a
440) a -> a -> a
forall a. Num a => a -> a -> a
- a
offs
where
b :: a
b = Integer -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> a) -> Integer -> a
forall a b. (a -> b) -> a -> b
$ Proxy b -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy b
forall {k} (t :: k). Proxy t
Proxy :: Proxy b)
offs :: a
offs = Integer -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Proxy offs -> Integer
forall (r :: ZZ) (proxy :: ZZ -> *).
KnownInt r =>
proxy r -> Integer
forall (proxy :: ZZ -> *). proxy offs -> Integer
intVal (Proxy offs
forall {k} (t :: k). Proxy t
Proxy :: Proxy offs)) a -> a -> a
forall a. Fractional a => a -> a -> a
/ a
100
instance IsUnit (Tet b offs) where
type DimOf (Tet b offs) = Time .^- 1
instance (KnownNat b, KnownInt offs) => ShowUnit (Tet b offs) where
type ShowUnitType (Tet b offs) =
Text "tet{b=" :<>: ShowType b
:<>: Text ",offs=" :<>: ShowType offs :<>: Text "}"
showsUnitPrec :: Int -> ShowS
showsUnitPrec Int
d = Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
String -> ShowS
showString String
"Tet " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> ShowS
forall a. Show a => a -> ShowS
shows (Proxy b -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy b
forall {k} (t :: k). Proxy t
Proxy :: Proxy b))
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
" "
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> ShowS
forall a. Show a => a -> ShowS
shows (Proxy offs -> Integer
forall (r :: ZZ) (proxy :: ZZ -> *).
KnownInt r =>
proxy r -> Integer
forall (proxy :: ZZ -> *). proxy offs -> Integer
intVal (Proxy offs
forall {k} (t :: k). Proxy t
Proxy :: Proxy offs))
prettysUnitPrec :: Int -> ShowS
prettysUnitPrec Int
d = Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
String -> ShowS
showString String
"tet " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> ShowS
forall a. Show a => a -> ShowS
shows (Proxy b -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy b
forall {k} (t :: k). Proxy t
Proxy :: Proxy b))
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
" "
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> ShowS
forall a. Show a => a -> ShowS
shows (Proxy offs -> Integer
forall (r :: ZZ) (proxy :: ZZ -> *).
KnownInt r =>
proxy r -> Integer
forall (proxy :: ZZ -> *). proxy offs -> Integer
intVal (Proxy offs
forall {k} (t :: k). Proxy t
Proxy :: Proxy offs))
type MidiPitch = Tet 12 (Neg 6900)
data PitchException = OutOfMidiRange
instance Exception PitchException
instance Show PitchException where
show :: PitchException -> String
show PitchException
OutOfMidiRange = String
"A linear pitch is either negative or higher than 127,\
\ and therefore cannot be converted to MIDI"
safeDecomposePitchCents :: Real a => Tet b offs a -> Maybe (Word8, a)
safeDecomposePitchCents :: forall a (b :: Nat) (offs :: ZZ).
Real a =>
Tet b offs a -> Maybe (Word8, a)
safeDecomposePitchCents Tet b offs a
n =
if Tet b offs a
n Tet b offs a -> Tet b offs a -> Bool
forall a. Ord a => a -> a -> Bool
>= Tet b offs a
128 Bool -> Bool -> Bool
|| Tet b offs a
n Tet b offs a -> Tet b offs a -> Bool
forall a. Ord a => a -> a -> Bool
< Tet b offs a
0 then
Maybe (Word8, a)
forall a. Maybe a
Nothing
else
(Word8, a) -> Maybe (Word8, a)
forall a. a -> Maybe a
Just (a -> a -> (Word8, a)
forall a b. (Real a, Integral b) => a -> a -> (b, a)
divMod' (Tet b offs a -> a
forall (u :: Unit) a. IsUnit u => u a -> a
unQuantity Tet b offs a
n) a
1)
decomposePitchCents :: Real a => Tet b offs a-> (Word8, a)
decomposePitchCents :: forall a (b :: Nat) (offs :: ZZ).
Real a =>
Tet b offs a -> (Word8, a)
decomposePitchCents Tet b offs a
n =
if Tet b offs a
n Tet b offs a -> Tet b offs a -> Bool
forall a. Ord a => a -> a -> Bool
>= Tet b offs a
128 Bool -> Bool -> Bool
|| Tet b offs a
n Tet b offs a -> Tet b offs a -> Bool
forall a. Ord a => a -> a -> Bool
< Tet b offs a
0 then
PitchException -> (Word8, a)
forall a e. Exception e => e -> a
throw PitchException
OutOfMidiRange
else
a -> a -> (Word8, a)
forall a b. (Real a, Integral b) => a -> a -> (b, a)
divMod' (Tet b offs a -> a
forall (u :: Unit) a. IsUnit u => u a -> a
unQuantity Tet b offs a
n) a
1