crf-chain2-generic-0.3.0: Second-order, generic, constrained, linear conditional random fields

Safe HaskellNone

Data.CRF.Chain2.Generic.Model

Synopsis

Documentation

data FeatGen o t f Source

Feature generation specification.

Constructors

FeatGen 

Fields

obFeats :: o -> t -> [f]
 
trFeats1 :: t -> [f]
 
trFeats2 :: t -> t -> [f]
 
trFeats3 :: t -> t -> t -> [f]
 

type FeatSel o t f = FeatGen o t f -> Xs o t -> Ys t -> [f]Source

A feature selection function type.

selectPresent :: FeatSel o t fSource

The presentFeats adapted to fit feature selection specs.

selectHidden :: FeatSel o t fSource

The hiddenFeats adapted to fit feature selection specs.

data Model m o t f Source

A conditional random field.

Constructors

Model 

Fields

values :: Vector Double
 
ixMap :: m f
 
featGen :: FeatGen o t f
 

mkModel :: (Ord f, FeatMap m f) => FeatGen o t f -> FeatSel o t f -> [(Xs o t, Ys t)] -> Model m o t fSource

data Core m f Source

A core of the model with no feature generation function. Unlike the Model, the core can be serialized.

Constructors

Core 

Fields

valuesC :: Vector Double
 
ixMapC :: m f
 

Instances

Binary (m f) => Binary (Core m f) 

core :: Model m o t f -> Core m fSource

Extract the model core.

withCore :: Core m f -> FeatGen o t f -> Model m o t fSource

Construct model with the given core and feature generation function.

phi :: FeatMap m f => Model m o t f -> f -> LogFloatSource

Potential assigned to the feature -- exponential of the corresonding parameter.

index :: FeatMap m f => Model m o t f -> f -> Maybe FeatIxSource

Index of the feature.

presentFeats :: FeatGen o t f -> Xs o t -> Ys t -> [(f, LogFloat)]Source

Features present in the dataset element together with corresponding occurence probabilities.

hiddenFeats :: FeatGen o t f -> Xs o t -> [f]Source

Features hidden in the dataset element.

obFeatsOn :: FeatGen o t f -> Xs o t -> Int -> LbIx -> [f]Source

trFeatsOn :: FeatGen o t f -> Xs o t -> Int -> LbIx -> LbIx -> LbIx -> [f]Source

onWord :: FeatMap m f => Model m o t f -> Xs o t -> Int -> LbIx -> LogFloatSource

onTransition :: FeatMap m f => Model m o t f -> Xs o t -> Int -> LbIx -> LbIx -> LbIx -> LogFloatSource

lbNum :: Xs o t -> Int -> IntSource

Number of potential labels at the given position of the sentence. Function extended to indices outside the positions' domain.

lbOn :: Xs o t -> Int -> LbIx -> Maybe tSource

Potential label at the given position and at the given index. Return Nothing for positions outside the domain.

lbIxs :: Xs o t -> Int -> [LbIx]Source

List of label indices at the given position. Function extended to indices outside the positions' domain.