| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Units.NonStd.Frequency
Synopsis
- newtype Tet (b :: Nat) (offs :: ZZ) a = Tet a
- type MidiPitch = Tet 12 ('Neg 6900)
- data PitchException = OutOfMidiRange
- safeDecomposePitchCents :: forall a (b :: Nat) (offs :: ZZ). Real a => Tet b offs a -> Maybe (Word8, a)
- decomposePitchCents :: forall a (b :: Nat) (offs :: ZZ). Real a => Tet b offs a -> (Word8, a)
Documentation
newtype Tet (b :: Nat) (offs :: ZZ) a Source #
Frequency in Tone Equal Temperament
Constructors
| Tet a |
Instances
| IsUnit (Tet b offs) Source # | |||||
Defined in Data.Units.NonStd.Frequency | |||||
| (KnownNat b, KnownInt offs) => ShowUnit (Tet b offs) Source # | |||||
Defined in Data.Units.NonStd.Frequency Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
| (Floating a, KnownNat b, KnownInt offs) => ConvertibleUnit (Tet b offs) a Source # | |||||
Defined in Data.Units.NonStd.Frequency Methods toBaseUnit :: Tet b offs a -> BaseUnitOf (Tet b offs) a Source # fromBaseUnit :: BaseUnitOf (Tet b offs) a -> Tet b offs a Source # | |||||
| Floating a => Floating (Tet b offs a) Source # | |||||
Defined in Data.Units.NonStd.Frequency Methods exp :: Tet b offs a -> Tet b offs a log :: Tet b offs a -> Tet b offs a sqrt :: Tet b offs a -> Tet b offs 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 sin :: Tet b offs a -> Tet b offs a cos :: Tet b offs a -> Tet b offs a tan :: Tet b offs a -> Tet b offs a asin :: Tet b offs a -> Tet b offs a acos :: Tet b offs a -> Tet b offs a atan :: Tet b offs a -> Tet b offs a sinh :: Tet b offs a -> Tet b offs a cosh :: Tet b offs a -> Tet b offs a tanh :: Tet b offs a -> Tet b offs a asinh :: Tet b offs a -> Tet b offs a acosh :: Tet b offs a -> Tet b offs a atanh :: Tet b offs a -> Tet b offs a log1p :: Tet b offs a -> Tet b offs a expm1 :: Tet b offs a -> Tet b offs a | |||||
| RealFloat a => RealFloat (Tet b offs a) Source # | |||||
Defined in Data.Units.NonStd.Frequency Methods floatRadix :: Tet b offs a -> Integer floatDigits :: Tet b offs a -> Int floatRange :: Tet b offs a -> (Int, Int) decodeFloat :: Tet b offs a -> (Integer, Int) encodeFloat :: Integer -> Int -> Tet b offs a exponent :: Tet b offs a -> Int significand :: Tet b offs a -> Tet b offs a scaleFloat :: Int -> Tet b offs a -> Tet b offs a isInfinite :: Tet b offs a -> Bool isDenormalized :: Tet b offs a -> Bool isNegativeZero :: Tet b offs a -> Bool | |||||
| Num a => Num (Tet b offs a) Source # | |||||
Defined in Data.Units.NonStd.Frequency Methods (+) :: 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 negate :: Tet b offs a -> Tet b offs a abs :: Tet b offs a -> Tet b offs a signum :: Tet b offs a -> Tet b offs a fromInteger :: Integer -> Tet b offs a | |||||
| Fractional a => Fractional (Tet b offs a) Source # | |||||
Defined in Data.Units.NonStd.Frequency | |||||
| Real a => Real (Tet b offs a) Source # | |||||
Defined in Data.Units.NonStd.Frequency Methods toRational :: Tet b offs a -> Rational | |||||
| RealFrac a => RealFrac (Tet b offs a) Source # | |||||
| Show a => Show (Tet b offs a) Source # | |||||
| Eq a => Eq (Tet b offs a) Source # | |||||
| Ord a => Ord (Tet b offs a) Source # | |||||
Defined in Data.Units.NonStd.Frequency | |||||
| type DimOf (Tet b offs) Source # | |||||
Defined in Data.Units.NonStd.Frequency | |||||
| type ShowUnitType (Tet b offs) Source # | |||||
data PitchException Source #
Constructors
| OutOfMidiRange |
Instances
| Exception PitchException Source # | |
Defined in Data.Units.NonStd.Frequency Methods toException :: PitchException -> SomeException fromException :: SomeException -> Maybe PitchException displayException :: PitchException -> String | |
| Show PitchException Source # | |
Defined in Data.Units.NonStd.Frequency Methods showsPrec :: Int -> PitchException -> ShowS show :: PitchException -> String showList :: [PitchException] -> ShowS | |
safeDecomposePitchCents :: forall a (b :: Nat) (offs :: ZZ). Real a => Tet b offs a -> Maybe (Word8, a) Source #
decomposePitchCents :: forall a (b :: Nat) (offs :: ZZ). Real a => Tet b offs a -> (Word8, a) Source #