Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- toEqLength :: [a] -> [a] -> ([a], [a], Int, Int, Int)
- toEqLengthL :: Int -> Int -> [a] -> [a] -> ([a], [a], Int, Int, Int)
- sumAbsDistNorm :: (Integral a, Ord a) => [a] -> [a] -> Integer
- sumAbsDistNormComp :: Compards -> Compards -> Integer
- sumSqrDistNorm :: (Real a, Fractional a) => [a] -> [a] -> a
- distanceSqr :: (Real a, Floating a, Fractional a) => [a] -> [a] -> a
- distanceSqrG :: (Real a, Floating a, Fractional a) => [a] -> [a] -> a
- distanceSqrG2 :: (Real a, Floating a, Fractional a) => Int -> [a] -> [a] -> a
- data Compards
- isWord8Based :: Compards -> Bool
- isInt8Based :: Compards -> Bool
- fromSmallWord8toInt8Diff :: [Word8] -> [Int8]
- class DoubleFunc a b c d where
- doubleFunc :: (a -> c) -> (b -> c) -> d -> c
Documentation
toEqLength :: [a] -> [a] -> ([a], [a], Int, Int, Int) Source #
toEqLength
changes two given lists into two lists of equal
minimal lengths and also returs its new length and initial lengths of the lists given.
toEqLengthL :: Int -> Int -> [a] -> [a] -> ([a], [a], Int, Int, Int) Source #
toEqLengthL
changes two given lists into two lists of equal
minimal lengths and also returs its new length and initial lengths of the lists given. Is
intended to be used when the length of the lists are known and given as the first and the second parameters
here respectively.
sumAbsDistNorm :: (Integral a, Ord a) => [a] -> [a] -> Integer Source #
Is also a simplified distance between the lists. Intended to be used with Word8
.
sumAbsDistNormComp :: Compards -> Compards -> Integer Source #
Intended to be used with Compards
of the same constructor in both arguments of the function. Otherwise returns -1.
sumSqrDistNorm :: (Real a, Fractional a) => [a] -> [a] -> a Source #
distanceSqr :: (Real a, Floating a, Fractional a) => [a] -> [a] -> a Source #
distanceSqr
is applied on two lists of non-negative Real
numbers (preferably, of type
Double
) and returns a special kind of distance that is similar to the statistical distance used
in the regression analysis. Is intended to be used e. g. for the AFTOVolio approach. The less
is the resulting number, the more 'similar' are the two lists of non-negative numbers in their
distributions. Here, in contrast to the more general distanceSqrG
, the numbers must be normed
to 1.0, so that the largest ones in both listn must be 1.0.
distanceSqrG :: (Real a, Floating a, Fractional a) => [a] -> [a] -> a Source #
distanceSqrG
is applied on two lists of non-negative Real
numbers (preferably, of type
Double
) and returns a special kind of distance that is similar to the statistical distance used
in the regression analysis. Is intended to be used e. g. for the AFTOVolio approach. The less
is the resulting number, the more 'similar' are the two lists of non-negative numbers in their
distributions.
distanceSqrG2 :: (Real a, Floating a, Fractional a) => Int -> [a] -> [a] -> a Source #
distanceSqrG2
is an partially optimized variant of the distanceSqrG
if length of the least
common multiplier of the two lists is known and provided as the first argument, besides if it is
equal to the length of the second argument, and if maximum element of the second argument here is
equal to 1.0.
Instances
Eq Compards Source # | |
DoubleFunc [Word8] [Int8] Compards Compards Source # | |
Defined in Aftovolio.General.Distance | |
DoubleFunc [Word8] [Int8] Integer Compards Source # | |
Defined in Aftovolio.General.Distance | |
DoubleFunc [Word8] [Int8] Bool Compards Source # | |
Defined in Aftovolio.General.Distance | |
DoubleFunc [Word8] [Int8] Int Compards Source # | |
Defined in Aftovolio.General.Distance |
isWord8Based :: Compards -> Bool Source #
isInt8Based :: Compards -> Bool Source #
fromSmallWord8toInt8Diff :: [Word8] -> [Int8] Source #
The elements in the first argument must not be greater than 127 though it is not checked.
class DoubleFunc a b c d where Source #
doubleFunc :: (a -> c) -> (b -> c) -> d -> c Source #
Instances
DoubleFunc [Word8] [Int8] Compards Compards Source # | |
Defined in Aftovolio.General.Distance | |
DoubleFunc [Word8] [Int8] Integer Compards Source # | |
Defined in Aftovolio.General.Distance | |
DoubleFunc [Word8] [Int8] Bool Compards Source # | |
Defined in Aftovolio.General.Distance | |
DoubleFunc [Word8] [Int8] Int Compards Source # | |
Defined in Aftovolio.General.Distance |