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

Safe HaskellNone

Data.CRF.Chain2.Generic.Codec

Synopsis

Documentation

type CodecM c a = Codec c aSource

A codec monad.

data Codec a b c o e Source

An abstract codec representation with external observation type a, external label type b, codec data type c, internal observation type o and internal label type e.

Constructors

Codec 

Fields

empty :: c

Empty codec.

encodeObU :: a -> CodecM c o

Encode the observation and update the codec (only in the encoding direction).

encodeObN :: a -> CodecM c (Maybe o)

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

encodeLbU :: b -> CodecM c e

Encode the label and update the codec.

encodeLbN :: b -> CodecM c e

Encode the label and do *not* update the codec. In case the label is not a member of the codec, return the label code assigned to Nothing label.

decodeLbC :: e -> CodecM c (Maybe b)

Decode the label within the codec monad.

hasLabel :: c -> b -> Bool

Is label a member of the codec?

encodeWord'Cu :: (Ord e, Ord o) => Codec a b c o e -> Word a b -> CodecM c (X o e)Source

Encode the word and update the codec.

encodeWord'Cn :: (Ord e, Ord o) => Codec a b c o e -> Word a b -> CodecM c (X o e)Source

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

encodeSent'Cu :: (Ord e, Ord o) => Codec a b c o e -> Sent a b -> CodecM c (Xs o e)Source

Encode the sentence and update the codec.

encodeSent'Cn :: (Ord e, Ord o) => Codec a b c o e -> Sent a b -> CodecM c (Xs o e)Source

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

encodeSent :: (Ord e, Ord o) => Codec a b c o e -> c -> Sent a b -> Xs o eSource

Encode the sentence using the given codec.

encodeWordL'Cu :: (Ord e, Ord o) => Codec a b c o e -> WordL a b -> CodecM c (X o e, Y e)Source

Encode the labeled word and update the codec.

encodeWordL'Cn :: (Ord e, Ord o) => Codec a b c o e -> WordL a b -> CodecM c (X o e, Y e)Source

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

encodeSentL'Cu :: (Ord e, Ord o) => Codec a b c o e -> SentL a b -> CodecM c (Xs o e, Ys e)Source

Encode the labeled sentence and update the codec.

encodeSentL'Cn :: (Ord e, Ord o) => Codec a b c o e -> SentL a b -> CodecM c (Xs o e, Ys e)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 e, Ord o) => Codec a b c o e -> c -> SentL a b -> (Xs o e, Ys e)Source

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

decodeLabel :: Codec a b c o e -> c -> e -> Maybe bSource

Decode the label.

decodeLabels :: Codec a b c o e -> c -> [e] -> [Maybe b]Source

Decode the sequence of labels.

unJust :: Codec a b c o e -> c -> Word a b -> Maybe b -> bSource

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

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

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

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

Encode the dataset with the codec.

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

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