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

Safe HaskellNone

Data.CRF.Chain2.Pair.Codec

Synopsis

Documentation

type Codec a b c = (AtomCodec a, AtomCodec (Maybe b), AtomCodec (Maybe c))Source

A codec. The first component is used to encode observations of type a, the second one is used to encode labels of type b, third -- labels of type c from the third level.

type CodecM a b c d = Codec (Codec a b c) dSource

Type synonym for the codec monad. It is important to notice that by a codec we denote here a structure of three AtomCodecs while in the monad-codec package it denotes a monad.

obMax :: Codec a b c -> ObSource

The maximum internal observation included in the codec.

lb1Max :: Codec a b c -> Lb1Source

The maximum internal label included in the codec.

lb2Max :: Codec a b c -> Lb2Source

The maximum internal label included in the codec.

encodeWord'Cu :: (Ord a, Ord b, Ord c) => Word a (b, c) -> CodecM a b c (X Ob Lb)Source

Encode the word and update the codec.

encodeWord'Cn :: (Ord a, Ord b, Ord c) => Word a (b, c) -> CodecM a b c (X Ob Lb)Source

Encode the word and do *not* update the codec.

encodeSent'Cu :: (Ord a, Ord b, Ord c) => Sent a (b, c) -> CodecM a b c (Xs Ob Lb)Source

Encode the sentence and update the codec.

encodeSent'Cn :: (Ord a, Ord b, Ord c) => Sent a (b, c) -> CodecM a b c (Xs Ob Lb)Source

Encode the sentence and do *not* update the codec.

encodeSent :: (Ord a, Ord b, Ord c) => Codec a b c -> Sent a (b, c) -> Xs Ob LbSource

Encode the sentence using the given codec.

encodeWordL'Cu :: (Ord a, Ord b, Ord c) => WordL a (b, c) -> CodecM a b c (X Ob Lb, Y Lb)Source

Encode the labeled word and update the codec.

encodeWordL'Cn :: (Ord a, Ord b, Ord c) => WordL a (b, c) -> CodecM a b c (X Ob Lb, Y Lb)Source

Encodec the labeled word and do *not* update the codec.

encodeSentL'Cu :: (Ord a, Ord b, Ord c) => SentL a (b, c) -> CodecM a b c (Xs Ob Lb, Ys Lb)Source

Encode the labeled sentence and update the codec.

encodeSentL'Cn :: (Ord a, Ord b, Ord c) => SentL a (b, c) -> CodecM a b c (Xs Ob Lb, Ys Lb)Source

Encode the labeled sentence and do *not* update the codec. Substitute the default label for any label not present in the codec.

encodeSentL :: (Ord a, Ord b, Ord c) => Codec a b c -> SentL a (b, c) -> (Xs Ob Lb, Ys Lb)Source

Encode the labeled sentence with the given codec. Substitute the default label for any label not present in the codec.

decodeLabel :: (Ord b, Ord c) => Codec a b c -> Lb -> Maybe (b, c)Source

Decode the label.

decodeLabels :: (Ord b, Ord c) => Codec a b c -> [Lb] -> [Maybe (b, c)]Source

Decode the sequence of labels.

unJust :: (Ord b, Ord c) => Codec a b c -> Word a (b, c) -> Maybe (b, c) -> (b, c)Source

Return the label when Just or one of the unknown values when Nothing.

mkCodec :: (Ord a, Ord b, Ord c) => [SentL a (b, c)] -> (Codec a b c, [(Xs Ob Lb, Ys Lb)])Source

Create the codec on the basis of the labeled dataset, return the resultant codec and the encoded dataset.

encodeData :: (Ord a, Ord b, Ord c) => Codec a b c -> [Sent a (b, c)] -> [Xs Ob Lb]Source

Encode the dataset with the codec.

encodeDataL :: (Ord a, Ord b, Ord c) => Codec a b c -> [SentL a (b, c)] -> [(Xs Ob Lb, Ys Lb)]Source

Encode the labeled dataset using the codec. Substitute the default label for any label not present in the codec.