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

Safe HaskellNone
LanguageHaskell98

Data.CRF.Chain2.Tiers.DAG.Dataset.Codec

Synopsis

Documentation

type CodecM a b c = Codec (Codec a b) c Source #

Type synonym for the codec monad.

type Codec a b = (AtomCodec a, Vector (AtomCodec (Maybe b))) Source #

Codec internal data. The first component is used to encode observations of type a, the second one is used to encode labels of type [b].

obMax :: Codec a b -> Ob Source #

The maximum internal observation included in the codec.

lbMax :: Codec a b -> [Lb] Source #

The maximum internal labels included in the codec.

empty :: Ord b => Int -> Codec a b Source #

The empty codec. The label parts are initialized with Nothing members, which represent unknown labels. It is taken in the model implementation into account because it is assigned to the lowest label code and the model assumes that the set of labels is of the {0, ..., lbMax} form.

Codec depends on the number of layers.

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

Encode the labeled word and update the codec.

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

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

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

Encode the word and update the codec.

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

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

decodeLabel :: Ord b => Codec a b -> Cb -> Maybe [b] Source #

Decode the label.

decodeLabels :: Ord b => Codec a b -> [Cb] -> [Maybe [b]] Source #

Decode the sequence of labels.

unJust :: Ord b => Codec a b -> Word a b -> Maybe [b] -> [b] Source #

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

type Xs = DAG () X Source #

Utility types.

type XYs = DAG () (X, Y) Source #

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

Encode the sentence and update the codec.

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

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

encodeSent :: (Ord a, Ord b) => Codec a b -> Sent a b -> Xs Source #

Encode the sentence using the given codec.

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

Encode the dataset with the codec.

encodeDataL :: (Ord a, Ord b) => Codec a b -> [SentL a b] -> [XYs] Source #

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

mkCodec Source #

Arguments

:: (Ord a, Ord b) 
=> Int

The number of layers

-> [SentL a b] 
-> Codec a b 

Create codec on the basis of the labeled dataset.