{-# LANGUAGE OverloadedStrings #-}
module NLP.Sequor.FeatureTemplate 
    ( Feature(..) 
    , Row
    , Col
    , parse
    , maybeParse
    )
where
import Data.Binary 
import Helper.Text(Txt)
import qualified Helper.Text as Text
import qualified Data.List as List
import qualified Data.Char as Char

type Row = Int
type Col = Int

data Feature =
          Cell Row Col
        | Rect Row Col Row Col
        | Row Row
        | Index Feature
        | MarkNull Feature
        | Cat [Feature]
        | Cart Feature Feature
        | Lower Feature
        | Suffix Int Feature
        | Prefix Int Feature
        | WordShape Feature
    deriving (Show,Read)

parse :: Txt -> Feature
parse =  maybe (error $ "FeatureTemplate.parse: no parse") id . maybeParse 

maybeParse :: Txt -> Maybe Feature
maybeParse s = 
    case 
      Text.reads
    . Text.unwords
    . map uncomment
    . Text.lines
    $ s
    of 
      (f,r):_ | Text.all Char.isSpace r -> Just f
      _                                 -> Nothing

uncomment :: Txt -> Txt 
uncomment s = let splits = map (flip Text.splitAt s) 
                               [1..fromIntegral . Text.length $ s]
              in case List.find (("--"`Text.isPrefixOf`) . snd) splits of
                   Nothing -> s
                   Just (prefix,_) -> prefix

instance Binary Feature where
    put f = put $ Text.show f
    get = do
      f <- get
      return $ Text.read f