{-# LANGUAGE NoMonomorphismRestriction #-}
module NLP.Sequor.Config 
    ( Config (..), Flags(..) )
where
import Data.Char
import Helper.Atom (AtomTable)
import qualified Data.Binary as B
import Control.Monad (ap)
import NLP.Sequor.FeatureTemplate (Feature)


data Flags = Flags { flagRate          :: !Float
                   , flagBeam          :: !Int
                   , flagIter          :: !Int
                   , flagMinFeatCount  :: !Int
                   , flagHeldout       :: Maybe FilePath
                   , flagHash          :: !Bool
                   , flagHashSample    :: !Int
                   , flagHashMaxSize   :: Maybe Int
                   , flagStopWinSize   :: !Int
                   , flagStopThreshold :: !Double
                   } 

data Config = Config { atomTable :: Maybe AtomTable 
                     , featureTemplate :: Feature
                     , flags :: Flags
                     , fieldNum :: !Int
                     }

instance B.Binary Flags where
    get = do (f1,f2,f3,f4,f5,f6,f7,f8,f9,f10) <- B.get
             return $ Flags f1 f2 f3 f4 f5 f6 f7 f8 f9 f10
    put (Flags f1 f2 f3 f4 f5 f6 f7 f8 f9 f10) = B.put (f1,f2,f3,f4,f5,f6,f7,f8,f9,f10)

instance B.Binary Config where
    get = let g = B.get
          in return Config `ap` g `ap` g `ap` g `ap` g

    put (Config a b c d) =
        let p = B.put 
        in p a >> p b >> p c >> p d