crf-chain2-tiers-0.4.0: Second-order, tiered, constrained, linear conditional random fields

Safe HaskellNone
LanguageHaskell98

Data.CRF.Chain2.Tiers.DAG.Inference

Contents

Synopsis

Documentation

tag :: Model -> DAG a X -> DAG a CbIx Source #

Find the most probable label sequence (with probabilities of individual lables determined with respect to marginal distributions) satisfying the constraints imposed over label values.

tag' :: Model -> DAG a X -> DAG a Cb Source #

Similar to tag but directly returns complex labels and not just their CbIx indexes.

tagK :: Int -> Model -> DAG a X -> DAG a [(CbIx, LogFloat)] Source #

Get (at most) k best tags for each word and return them in descending order. TODO: Tagging with respect to marginal distributions might not be the best idea. Think of some more elegant method.

fastTag :: Model -> DAG a X -> DAG a (Maybe CbIx) Source #

A version of tag which should be, roughly, twice as efficient, since it only performs one forward and no backward computation. The downside is that probabilities cannot be retrieved.

fastTag' :: Model -> DAG a X -> DAG a (Maybe Cb) Source #

Similar to fastTag but directly returns complex labels and not just their CbIx indexes.

marginals :: Model -> DAG a X -> DAG a [(CbIx, LogFloat)] Source #

Tag potential labels with marginal probabilities.

marginals' :: Model -> DAG a X -> DAG a [(Cb, LogFloat)] Source #

Tag potential labels with marginal probabilities.

data ProbType Source #

Type of resulting probabilities.

Constructors

Marginals

Marginal probabilities

MaxProbs

TODO

probs :: ProbType -> Model -> DAG a X -> DAG a [(CbIx, LogFloat)] Source #

Tag potential labels with alternative probabilities. TODO: explain what is that exactly.

probs' :: ProbType -> Model -> DAG a X -> DAG a [(Cb, LogFloat)] Source #

Tag potential labels with alternative probabilities. TODO: explain what is that exactly.

accuracy :: Model -> [DAG a (X, Y)] -> Double Source #

Compute the accuracy of the model with respect to the labeled dataset.

expectedFeaturesIn :: Model -> DAG a X -> [(Feat, LogFloat)] Source #

A list of features defined within the context of the sentence accompanied by expected probabilities determined on the basis of the model.

One feature can occur multiple times in the output list.

zx :: Model -> DAG a X -> LogFloat Source #

Normalization factor computed for the sentence using the forward computation.

zx' :: Model -> DAG a X -> LogFloat Source #

Normalization factor computed for the sentence using the backward computation.

Internals (used by Probs) (TODO: move elsewhere)

type AccF = [LogFloat] -> LogFloat Source #

Accumulation function.

type ProbArray = Pos -> Pos -> LogFloat Source #

First argument represents the current EdgeIx (Nothing if out of bounds), the next argument represents the previous EdgeIx.

data Pos Source #

Position in the sentence.

Constructors

Beg

Before the beginning of the sentence

Mid EdgeIx

Actual edge

End

After the end of the sentence

Instances
Eq Pos Source # 
Instance details

Defined in Data.CRF.Chain2.Tiers.DAG.Inference

Methods

(==) :: Pos -> Pos -> Bool #

(/=) :: Pos -> Pos -> Bool #

Ord Pos Source # 
Instance details

Defined in Data.CRF.Chain2.Tiers.DAG.Inference

Methods

compare :: Pos -> Pos -> Ordering #

(<) :: Pos -> Pos -> Bool #

(<=) :: Pos -> Pos -> Bool #

(>) :: Pos -> Pos -> Bool #

(>=) :: Pos -> Pos -> Bool #

max :: Pos -> Pos -> Pos #

min :: Pos -> Pos -> Pos #

Show Pos Source # 
Instance details

Defined in Data.CRF.Chain2.Tiers.DAG.Inference

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

simplify :: Pos -> Maybe EdgeIx Source #

Simplify the position by conflating Beg and End to Nothing.

complicate :: Pos -> Maybe EdgeIx -> Pos Source #

Inverse operation of simplify, with the default position value.

Memoization