ConClusion-0.0.1: Cluster algorithms, PCA, and chemical conformere analysis
CopyrightPhillip Seeber 2021
LicenseAGPL-3
Maintainerphillip.seeber@googlemail.com
Stabilityexperimental
PortabilityPOSIX, Windows
Safe HaskellNone
LanguageHaskell2010

ConClusion.Numeric.Data

Description

 
Synopsis
  • newtype IndexException = IndexException String
  • vecH2M :: (Element e, Mutable r Ix1 e) => Vector e -> Vector r e
  • vecM2H :: (Manifest r Ix1 e, Element e) => Vector r e -> Vector e
  • matH2M :: (Mutable r Ix1 e, Element e) => Matrix e -> Matrix r e
  • matM2H :: (Manifest r Ix1 e, Element e, Resize r Ix2, Load r Ix2 e) => Matrix r e -> Matrix e
  • magnitude :: (Numeric r e, Source r Ix1 e, Floating e) => Vector r e -> e
  • normalise :: (Numeric r e, Source r Ix1 e, Floating e) => Vector r e -> Vector r e
  • angle :: (Numeric r e, Source r Ix1 e, Floating e) => Vector r e -> Vector r e -> e
  • minDistAt :: (Manifest r Ix2 e, MonadThrow m, Ord e) => Matrix r e -> m (e, Ix2)
  • minDistAtVec :: (Manifest r Ix1 e, MonadThrow m, Ord e) => Ix1 -> Vector r e -> m (e, Ix1)
  • iMinimumM :: (Manifest r ix a, MonadThrow m, Ord a) => Array r ix a -> m (a, ix)
  • printMat :: (Source r Ix2 e, Real e) => Matrix r e -> Matrix D Text
  • data BinTree e
  • root :: BinTree e -> e
  • takeBranchesWhile :: (a -> Bool) -> BinTree a -> Vector DL a
  • takeLeafyBranchesWhile :: (a -> Bool) -> BinTree a -> Vector DL a

Conversion of array types.

newtype IndexException Source #

Exception regarding indexing in some kind of aaray.

Constructors

IndexException String 

Instances

Instances details
Show IndexException Source # 
Instance details

Defined in ConClusion.Numeric.Data

Methods

showsPrec :: Int -> IndexException -> ShowS

show :: IndexException -> String

showList :: [IndexException] -> ShowS

Exception IndexException Source # 
Instance details

Defined in ConClusion.Numeric.Data

Methods

toException :: IndexException -> SomeException

fromException :: SomeException -> Maybe IndexException

displayException :: IndexException -> String

vecH2M :: (Element e, Mutable r Ix1 e) => Vector e -> Vector r e Source #

Converts a vector from the HMatrix package to the Massiv representation.

vecM2H :: (Manifest r Ix1 e, Element e) => Vector r e -> Vector e Source #

Converts a vector from the Massiv representation to the HMatrix representation.

matH2M :: (Mutable r Ix1 e, Element e) => Matrix e -> Matrix r e Source #

Converts a matrix from the HMatrix representation to the Massiv representation.

matM2H :: (Manifest r Ix1 e, Element e, Resize r Ix2, Load r Ix2 e) => Matrix r e -> Matrix e Source #

Converts a matrix from Massiv to HMatrix representation.

Array Processing

magnitude :: (Numeric r e, Source r Ix1 e, Floating e) => Vector r e -> e Source #

Magnitude of a vector (length).

normalise :: (Numeric r e, Source r Ix1 e, Floating e) => Vector r e -> Vector r e Source #

Normalise a vector.

angle :: (Numeric r e, Source r Ix1 e, Floating e) => Vector r e -> Vector r e -> e Source #

Angle between two vectors.

minDistAt :: (Manifest r Ix2 e, MonadThrow m, Ord e) => Matrix r e -> m (e, Ix2) Source #

Find the minimal distance in a distance matrix, which is not the main diagonal.

minDistAtVec :: (Manifest r Ix1 e, MonadThrow m, Ord e) => Ix1 -> Vector r e -> m (e, Ix1) Source #

Find the minimal element of a vector, which is at a larger than the supplied index.

iMinimumM :: (Manifest r ix a, MonadThrow m, Ord a) => Array r ix a -> m (a, ix) Source #

Like minimumM but also returns the index of the minimal element.

Utilities

printMat :: (Source r Ix2 e, Real e) => Matrix r e -> Matrix D Text Source #

Quickly print a matrix with numerical values

Binary Trees

data BinTree e Source #

A binary tree.

Constructors

Leaf e 
Node e (BinTree e) (BinTree e) 

Instances

Instances details
Functor BinTree Source # 
Instance details

Defined in ConClusion.Numeric.Data

Methods

fmap :: (a -> b) -> BinTree a -> BinTree b

(<$) :: a -> BinTree b -> BinTree a

Eq e => Eq (BinTree e) Source # 
Instance details

Defined in ConClusion.Numeric.Data

Methods

(==) :: BinTree e -> BinTree e -> Bool

(/=) :: BinTree e -> BinTree e -> Bool

Show e => Show (BinTree e) Source # 
Instance details

Defined in ConClusion.Numeric.Data

Methods

showsPrec :: Int -> BinTree e -> ShowS

show :: BinTree e -> String

showList :: [BinTree e] -> ShowS

Generic (BinTree e) Source # 
Instance details

Defined in ConClusion.Numeric.Data

Associated Types

type Rep (BinTree e) :: Type -> Type

Methods

from :: BinTree e -> Rep (BinTree e) x

to :: Rep (BinTree e) x -> BinTree e

FromJSON e => FromJSON (BinTree e) Source # 
Instance details

Defined in ConClusion.Numeric.Data

Methods

parseJSON :: Value -> Parser (BinTree e)

parseJSONList :: Value -> Parser [BinTree e]

ToJSON e => ToJSON (BinTree e) Source # 
Instance details

Defined in ConClusion.Numeric.Data

Methods

toJSON :: BinTree e -> Value

toEncoding :: BinTree e -> Encoding

toJSONList :: [BinTree e] -> Value

toEncodingList :: [BinTree e] -> Encoding

type Rep (BinTree e) Source # 
Instance details

Defined in ConClusion.Numeric.Data

type Rep (BinTree e) = D1 ('MetaData "BinTree" "ConClusion.Numeric.Data" "ConClusion-0.0.1-inplace" 'False) (C1 ('MetaCons "Leaf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :+: C1 ('MetaCons "Node" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (BinTree e)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (BinTree e)))))

root :: BinTree e -> e Source #

Look at the root of a binary tree.

takeBranchesWhile :: (a -> Bool) -> BinTree a -> Vector DL a Source #

Steps down each branch of a tree until some criterion is satisfied or the end of the branch is reached. Each end of the branch is added to a result.

takeLeafyBranchesWhile :: (a -> Bool) -> BinTree a -> Vector DL a Source #

Takes the first value in each branch, that does not fullfill the criterion anymore and adds it to the result. Terminal leafes of the branches are always taken.