{-# LANGUAGE OverloadedStrings #-}
module Codec.Compression.PPM.Utils ( lineToInstance
, revWindows
) where
import qualified Data.Text.Lazy as T
import qualified Data.Sequence as Seq
import Data.Sequence ((|>))
import Data.Foldable (toList)
microFScore :: [a] -> [a] -> Double
microFScore guess gold = error "unimp"
macroFScore :: [a] -> [a] -> Double
macroFScore guess gold = error "unimp"
lineToInstance :: T.Text -> (T.Text, [Char])
lineToInstance l = (label, T.unpack (T.drop 1 text))
where
(id, rest) = T.breakOn "\t" l
(label, text) = T.breakOn "\t" (T.drop 1 rest)
windows :: Int -> [a] -> [[a]]
windows n0 = go 0 Seq.empty
where
go n s (a:as) | n' <= n0 = toList s' : go n' s' as
| otherwise = toList s'' : go n s'' as
where
n' = n + 1
s' = s |> a
s'' = Seq.drop 1 s'
go _ _ [] = []
revWindows :: Int -> [i] -> [[i]]
revWindows n is = is'
where
is' = (map reverse . windows n) is