roc-cluster-0.1.0.0: ROC online clustering algorithm

Safe HaskellNone
LanguageHaskell2010

Data.Cluster.ROC

Contents

Synopsis

Algorithm configuration

data ROCConfig Source #

Configuration of ROC clusterization

Instances

Data ROCConfig Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ROCConfig -> c ROCConfig #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ROCConfig #

toConstr :: ROCConfig -> Constr #

dataTypeOf :: ROCConfig -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ROCConfig) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ROCConfig) #

gmapT :: (forall b. Data b => b -> b) -> ROCConfig -> ROCConfig #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ROCConfig -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ROCConfig -> r #

gmapQ :: (forall d. Data d => d -> u) -> ROCConfig -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ROCConfig -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ROCConfig -> m ROCConfig #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ROCConfig -> m ROCConfig #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ROCConfig -> m ROCConfig #

Generic ROCConfig Source # 

Associated Types

type Rep ROCConfig :: * -> * #

type Rep ROCConfig Source # 
type Rep ROCConfig = D1 (MetaData "ROCConfig" "Data.Cluster.ROC" "roc-cluster-0.1.0.0-3vI6Kqa7JFYrjkID78s2x" False) (C1 (MetaCons "ROCConfig" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "rocThreshold") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)) (S1 (MetaSel (Just Symbol "rocMaxClusters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))))

rocThreshold :: ROCConfig -> Double Source #

If weight of prototype is less than the value, it is removed at final step.

rocMaxClusters :: ROCConfig -> Int Source #

Maximum count of clusters, could be less

defaultROCConfig :: ROCConfig Source #

Default configuration: ROCConfig { rocThreshold = 0 , rocMaxClusters = 10 }

Cluster definition

data Prototype a Source #

Cluster information

Instances

Functor Prototype Source # 

Methods

fmap :: (a -> b) -> Prototype a -> Prototype b #

(<$) :: a -> Prototype b -> Prototype a #

Eq a => Eq (Prototype a) Source # 

Methods

(==) :: Prototype a -> Prototype a -> Bool #

(/=) :: Prototype a -> Prototype a -> Bool #

Show a => Show (Prototype a) Source # 
Generic (Prototype a) Source # 

Associated Types

type Rep (Prototype a) :: * -> * #

Methods

from :: Prototype a -> Rep (Prototype a) x #

to :: Rep (Prototype a) x -> Prototype a #

ClusterSpace a => Monoid (Prototype a) Source # 
type Rep (Prototype a) Source # 
type Rep (Prototype a) = D1 (MetaData "Prototype" "Data.Cluster.ROC" "roc-cluster-0.1.0.0-3vI6Kqa7JFYrjkID78s2x" False) (C1 (MetaCons "Prototype" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "prototypeValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a)) (S1 (MetaSel (Just Symbol "prototypeWeight") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double))))

newPrototype :: a -> Prototype a Source #

Create prototype with given point as center and zero weight

API

class ClusterSpace a where Source #

Operations that value has to support to use in ROC clusterisation

Minimal complete definition

pointZero, pointAdd, pointScale, pointKernel

Methods

pointZero :: a Source #

Zero point in space

pointAdd :: a -> a -> a Source #

Addition of vectors in space

pointScale :: Double -> a -> a Source #

Scaling by a scalar

pointKernel :: a -> a -> Double Source #

Kernel function

pointDistanceSquared :: a -> a -> Double Source #

Square of distance between of points (defined via kernel) and exposed only for possible optimizations as for Gaussian kernel (2 - 2 * pointKernel x y)

data ROCContext a Source #

Internal context of algorithm

Instances

Functor ROCContext Source # 

Methods

fmap :: (a -> b) -> ROCContext a -> ROCContext b #

(<$) :: a -> ROCContext b -> ROCContext a #

Generic (ROCContext a) Source # 

Associated Types

type Rep (ROCContext a) :: * -> * #

Methods

from :: ROCContext a -> Rep (ROCContext a) x #

to :: Rep (ROCContext a) x -> ROCContext a #

type Rep (ROCContext a) Source # 
type Rep (ROCContext a) = D1 (MetaData "ROCContext" "Data.Cluster.ROC" "roc-cluster-0.1.0.0-3vI6Kqa7JFYrjkID78s2x" False) (C1 (MetaCons "ROCContext" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "cntxPrototypes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Vector (Prototype a)))) (S1 (MetaSel (Just Symbol "cntxConfig") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ROCConfig))))

emptyROCContext :: ROCConfig -> ROCContext a Source #

Create new context for clusterization from scratch

loadROCContext :: Foldable f => ROCConfig -> f (Prototype a) -> ROCContext a Source #

Load context from set of prototypes

rocPrototypes :: ROCContext a -> [Prototype a] Source #

Get collection of prototypes from ROC context

clusterize Source #

Arguments

:: (ClusterSpace a, Foldable f) 
=> f a

Set of data that need to be added to clusters

-> ROCContext a

Context with current prototypes

-> ROCContext a

Updated context

Perform clusterization of next part of data

Fine grain API

clusterizeAddMerge Source #

Arguments

:: ClusterSpace a 
=> a

Single point

-> ROCContext a

Context with current prototypes

-> ROCContext a

Updated context

Cluster a single value (step 2-6 in original paper). Moves existing clusters, creates new clusters and merges close clusters.

clusterizeSingle Source #

Arguments

:: ClusterSpace a 
=> a

Single point

-> ROCContext a

Context with current prototypes

-> ROCContext a

Updated context

Cluster a single value (step 2 in original paper). This step updates only existing clusters.

clusterizeMerge Source #

Arguments

:: ClusterSpace a 
=> ROCContext a

Context with current prototypes

-> ROCContext a

Updated context

Merge the most closest clusters (step 4 in original paper).

clusterizeNewPrototype Source #

Arguments

:: ClusterSpace a 
=> a

Point

-> ROCContext a

Context with current prototypes

-> ROCContext a

Updated context

Form a new prototype from single point (step 5 in original paper)

clusterizePostprocess Source #

Arguments

:: ClusterSpace a 
=> ROCContext a

Context with current prototypes

-> ROCContext a

Updated context

Remove clusters that have negligible weights (step 6 in original paper)