| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Freq.Internal
Description
Synopsis
- newtype FreqTrain = FreqTrain {}
- empty :: FreqTrain
- singleton :: Word8 -> Word8 -> Double -> FreqTrain
- tabulate :: FreqTrain -> Freq
- train :: ByteString -> FreqTrain
- trainWith :: FilePath -> IO FreqTrain
- trainWithMany :: Foldable t => t FilePath -> IO FreqTrain
- data Freq = Freq {}
- measure :: Freaky a => a -> ByteString -> Double
- class Freaky a where
- prettyFreqTrain :: FreqTrain -> IO ()
Frequency table type
A is a digram-based frequency table.FreqTrain
One can construct a with FreqTrain,
train, or trainWith.trainWithMany
One can use a trained with FreqTrain
and prob.measure
will add the values of each
of the matching keys.mappend == <>
It is highly recommended to convert a
to a FreqTrain with Freq before using the trained model,
because tabulates have O(1) reads as well as significantly
faster constant-time operations, however keep in mind
that Freqs cannot be neither modified nor converted
back to a Freq.FreqTrain
Instances
| Eq FreqTrain Source # | |
| Data FreqTrain Source # | |
Defined in Freq.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FreqTrain -> c FreqTrain # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FreqTrain # toConstr :: FreqTrain -> Constr # dataTypeOf :: FreqTrain -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FreqTrain) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FreqTrain) # gmapT :: (forall b. Data b => b -> b) -> FreqTrain -> FreqTrain # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FreqTrain -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FreqTrain -> r # gmapQ :: (forall d. Data d => d -> u) -> FreqTrain -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FreqTrain -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FreqTrain -> m FreqTrain # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FreqTrain -> m FreqTrain # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FreqTrain -> m FreqTrain # | |
| Ord FreqTrain Source # | |
| Read FreqTrain Source # | |
| Show FreqTrain Source # | |
| Semigroup FreqTrain Source # | |
| Monoid FreqTrain Source # | |
| NFData FreqTrain Source # | |
Defined in Freq.Internal | |
| Freaky FreqTrain Source # | |
Construction
O(1). A Frequency table with a single entry.
Training
train :: ByteString -> FreqTrain Source #
Given a consisting of training data,
build a Frequency table.ByteString
Using a trained model
A variant of that holds identical information but
is optimised for reads. There are no operations that imbue
a FreqTrain with additional information.Freq
Reading from a is orders of magnitude faster
than reading from a Freq. It is highly
recommended that you use your trained model by first
converting a FreqTrain to a FreqTrain with Freq.tabulate
Constructors
| Freq | |
measure :: Freaky a => a -> ByteString -> Double Source #
Given a Frequency table and a , ByteString
returns the probability that the measure is not
randomised. The accuracy of ByteString is is heavily affected
by your training data.measure
is a typeclass that wraps the Freaky function,
which allows for an extensible definition of prob.measure
It is used internally.