Copyright | (c) Edward Kmett 2013-2015 |
---|---|
License | BSD3 |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Trustworthy |
Language | Haskell98 |
Documentation
Log
-domain Float
and Double
values.
Instances
Monad Log Source # | |
Functor Log Source # | |
Applicative Log Source # | |
Foldable Log Source # | |
Defined in Numeric.Log fold :: Monoid m => Log m -> m # foldMap :: Monoid m => (a -> m) -> Log a -> m # foldr :: (a -> b -> b) -> b -> Log a -> b # foldr' :: (a -> b -> b) -> b -> Log a -> b # foldl :: (b -> a -> b) -> b -> Log a -> b # foldl' :: (b -> a -> b) -> b -> Log a -> b # foldr1 :: (a -> a -> a) -> Log a -> a # foldl1 :: (a -> a -> a) -> Log a -> a # elem :: Eq a => a -> Log a -> Bool # maximum :: Ord a => Log a -> a # | |
Traversable Log Source # | |
Comonad Log Source # | |
ComonadApply Log Source # | |
Serial1 Log Source # | |
Defined in Numeric.Log serializeWith :: MonadPut m => (a -> m ()) -> Log a -> m () deserializeWith :: MonadGet m => m a -> m (Log a) | |
Distributive Log Source # | |
Apply Log Source # | |
Bind Log Source # | |
Extend Log Source # | |
Defined in Numeric.Log | |
Hashable1 Log Source # | |
Defined in Numeric.Log | |
Foldable1 Log Source # | |
Defined in Numeric.Log | |
Traversable1 Log Source # | |
(RealFloat a, Unbox a) => Vector Vector (Log a) Source # | |
Defined in Numeric.Log basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Log a) -> m (Vector (Log a)) basicUnsafeThaw :: PrimMonad m => Vector (Log a) -> m (Mutable Vector (PrimState m) (Log a)) basicLength :: Vector (Log a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (Log a) -> Vector (Log a) basicUnsafeIndexM :: Monad m => Vector (Log a) -> Int -> m (Log a) basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Log a) -> Vector (Log a) -> m () | |
Unbox a => MVector MVector (Log a) Source # | |
Defined in Numeric.Log basicLength :: MVector s (Log a) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (Log a) -> MVector s (Log a) basicOverlaps :: MVector s (Log a) -> MVector s (Log a) -> Bool basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Log a)) basicInitialize :: PrimMonad m => MVector (PrimState m) (Log a) -> m () basicUnsafeReplicate :: PrimMonad m => Int -> Log a -> m (MVector (PrimState m) (Log a)) basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Log a) -> Int -> m (Log a) basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Log a) -> Int -> Log a -> m () basicClear :: PrimMonad m => MVector (PrimState m) (Log a) -> m () basicSet :: PrimMonad m => MVector (PrimState m) (Log a) -> Log a -> m () basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Log a) -> MVector (PrimState m) (Log a) -> m () basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Log a) -> MVector (PrimState m) (Log a) -> m () basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Log a) -> Int -> m (MVector (PrimState m) (Log a)) | |
(RealFloat a, Enum a) => Enum (Log a) Source # | |
Eq a => Eq (Log a) Source # | |
RealFloat a => Floating (Log a) Source # | |
RealFloat a => Fractional (Log a) Source # | |
Data a => Data (Log a) Source # | |
Defined in Numeric.Log gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Log a -> c (Log a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Log a) # dataTypeOf :: Log a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Log a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Log a)) # gmapT :: (forall b. Data b => b -> b) -> Log a -> Log a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Log a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Log a -> r # gmapQ :: (forall d. Data d => d -> u) -> Log a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Log a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Log a -> m (Log a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Log a -> m (Log a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Log a -> m (Log a) # | |
RealFloat a => Num (Log a) Source # | |
Ord a => Ord (Log a) Source # | |
(Floating a, Read a) => Read (Log a) Source # | |
(RealFloat a, Ord a) => Real (Log a) Source # | |
Defined in Numeric.Log toRational :: Log a -> Rational # | |
RealFloat a => RealFrac (Log a) Source # | |
(Floating a, Show a) => Show (Log a) Source # | |
Generic (Log a) Source # | |
RealFloat a => Semigroup (Log a) Source # | |
RealFloat a => Monoid (Log a) Source # | |
Storable a => Storable (Log a) Source # | |
Binary a => Binary (Log a) Source # | |
NFData a => NFData (Log a) Source # | |
Defined in Numeric.Log | |
Serial a => Serial (Log a) Source # | |
Defined in Numeric.Log serialize :: MonadPut m => Log a -> m () deserialize :: MonadGet m => m (Log a) | |
Hashable a => Hashable (Log a) Source # | |
Defined in Numeric.Log | |
Serialize a => Serialize (Log a) Source # | |
Defined in Numeric.Log | |
(RealFloat a, Unbox a) => Unbox (Log a) Source # | |
Defined in Numeric.Log | |
newtype MVector s (Log a) Source # | |
Defined in Numeric.Log | |
type Rep (Log a) Source # | |
Defined in Numeric.Log | |
newtype Vector (Log a) Source # | |
Defined in Numeric.Log |
sum :: (RealFloat a, Foldable f) => f (Log a) -> Log a Source #
Efficiently and accurately compute the sum of a set of log-domain numbers
While folding with (+)
accomplishes the same end, it requires an
additional n-2
logarithms to sum n
terms. In addition,
here we introduce fewer opportunities for round-off error.
While for small quantities the naive sum accumulates error,
>>>
let xs = Prelude.replicate 40000 (Exp 1e-4) :: [Log Float]
>>>
Prelude.sum xs ~= 4.00e4
True
This sum gives a more accurate result,
>>>
Numeric.Log.sum xs ~= 4.00e4
True
NB: This does require two passes over the data.