Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- type CodecM a b c = Codec (Codec a b) c
- type Codec a b = (AtomCodec a, AtomCodec (Maybe b))
- obMax :: Codec a b -> Ob
- lbMax :: Codec a b -> Lb
- empty :: Ord b => Codec a b
- encodeWordL'Cu :: (Ord a, Ord b) => WordL a b -> CodecM a b (X, Y)
- encodeWordL'Cn :: (Ord a, Ord b) => WordL a b -> CodecM a b (X, Y)
- encodeWord'Cu :: (Ord a, Ord b) => Word a b -> CodecM a b X
- encodeWord'Cn :: (Ord a, Ord b) => Word a b -> CodecM a b X
- encodeLabels :: Ord b => Codec a b -> [b] -> AVec Lb
- encodeLabel :: Ord b => Codec a b -> b -> Lb
- decodeLabel :: Ord b => Codec a b -> Lb -> Maybe b
- decodeLabels :: Ord b => Codec a b -> [Lb] -> [Maybe b]
- unJust :: Ord b => Codec a b -> Word a b -> Maybe b -> b
- unJusts :: Ord b => Codec a b -> Word a b -> [Maybe b] -> [b]
- type Xs = DAG () X
- type XYs = DAG () (X, Y)
- encodeSent'Cu :: (Ord a, Ord b) => Sent a b -> CodecM a b Xs
- encodeSent'Cn :: (Ord a, Ord b) => Sent a b -> CodecM a b Xs
- encodeSent :: (Ord a, Ord b) => Codec a b -> Sent a b -> Xs
- encodeSentL'Cu :: (Ord a, Ord b) => SentL a b -> CodecM a b XYs
- encodeSentL'Cn :: (Ord a, Ord b) => SentL a b -> CodecM a b XYs
- encodeSentL :: (Ord a, Ord b) => Codec a b -> SentL a b -> XYs
- encodeData :: (Ord a, Ord b) => Codec a b -> [Sent a b] -> [Xs]
- encodeDataL :: (Ord a, Ord b) => Codec a b -> [SentL a b] -> [XYs]
- mkCodec :: (Ord a, Ord b) => [SentL a b] -> Codec a b
Documentation
type CodecM a b c = Codec (Codec a b) c Source #
Type synonym for the codec monad. It is important to notice that by a
codec we denote here a structure of two AtomCodec
s while in the
monad-codec package it denotes a monad.
type Codec a b = (AtomCodec a, AtomCodec (Maybe b)) 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.
empty :: Ord b => Codec a b Source #
The empty codec. The label part is initialized with Nothing
member, which represents unknown labels. It is taken on account
in the model implementation because it is assigned to the
lowest label code and the model assumes that the set of labels
is of the {0, ..., lbMax
} form.
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.
encodeLabels :: Ord b => Codec a b -> [b] -> AVec Lb Source #
Encode labels into an ascending vector of distinct label codes.
unJusts :: Ord b => Codec a b -> Word a b -> [Maybe b] -> [b] Source #
Replace Nothing
labels with all unknown labels from
the set of potential interpretations.
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.
encodeSentL'Cu :: (Ord a, Ord b) => SentL a b -> CodecM a b XYs Source #
Encode the labeled sentence and update the codec.
encodeSentL'Cn :: (Ord a, Ord b) => SentL a b -> CodecM a b XYs 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) => Codec a b -> SentL a b -> XYs Source #
Encode the labeled sentence with the given codec. Substitute the default label for any label not present in the codec.
encodeData :: (Ord a, Ord b) => Codec a b -> [Sent a b] -> [Xs] Source #
Encode the dataset with the codec.