| Safe Haskell | None |
|---|
Data.CRF.Chain2.Tiers
- data CRF a b = CRF {
- numOfLayers :: Int
- codec :: Codec a b
- model :: Model
- size :: CRF a b -> Int
- prune :: Double -> CRF a b -> CRF a b
- train :: (Ord a, Ord b) => Int -> FeatSel -> SgdArgs -> Bool -> IO [SentL a b] -> IO [SentL a b] -> IO (CRF a b)
- reTrain :: (Ord a, Ord b) => CRF a b -> SgdArgs -> Bool -> IO [SentL a b] -> IO [SentL a b] -> IO (CRF a b)
- tag :: (Ord a, Ord b) => CRF a b -> Sent a b -> [[b]]
- marginals :: (Ord a, Ord b) => CRF a b -> Sent a b -> [[Double]]
- module Data.CRF.Chain2.Tiers.Dataset.External
- module Data.CRF.Chain2.Tiers.Feature
CRF
CRF model data.
Instances
| (Ord a, Ord b, Binary a, Binary b) => Binary (CRF a b) |
prune :: Double -> CRF a b -> CRF a bSource
Discard model features with absolute values (in log-domain) lower than the given threshold.
Training
Arguments
| :: (Ord a, Ord b) | |
| => Int | Number of layers (tiers) |
| -> FeatSel | Feature selection |
| -> SgdArgs | SGD parameters |
| -> Bool | Store dataset on a disk |
| -> IO [SentL a b] | Training data |
| -> IO [SentL a b] | Evaluation data |
| -> IO (CRF a b) | Resulting model |
Train the CRF using the stochastic gradient descent method.
Arguments
| :: (Ord a, Ord b) | |
| => CRF a b | Existing CRF model |
| -> SgdArgs | SGD parameters |
| -> Bool | Store dataset on a disk |
| -> IO [SentL a b] | Training data |
| -> IO [SentL a b] | Evaluation data |
| -> IO (CRF a b) | Resulting model |
Re-train the CRF using the stochastic gradient descent method.
Tagging
marginals :: (Ord a, Ord b) => CRF a b -> Sent a b -> [[Double]]Source
Tag labels with marginal probabilities.