Commit 34bcbffd authored by Alexandre Delanoë's avatar Alexandre Delanoë

[DEV] Flow + Main + cosmetics on Learn.

parent e923bba5
...@@ -50,7 +50,7 @@ main = do ...@@ -50,7 +50,7 @@ main = do
let let
--tt = (Unsupervised EN 6 0 Nothing) --tt = (Unsupervised EN 6 0 Nothing)
tt = (Multi EN) tt = (Multi EN)
format = CsvHalFormat --WOS -- CsvGargV3 format = CsvGargV3 -- CsvHalFormat --WOS
cmd :: forall m. FlowCmdM DevEnv GargError m => m CorpusId cmd :: forall m. FlowCmdM DevEnv GargError m => m CorpusId
cmd = flowCorpusFile (cs user) (Left (cs name :: Text)) (read limit :: Int) tt format corpusPath cmd = flowCorpusFile (cs user) (Left (cs name :: Text)) (read limit :: Int) tt format corpusPath
{- {-
......
...@@ -18,7 +18,7 @@ Portability : POSIX ...@@ -18,7 +18,7 @@ Portability : POSIX
-} -}
{-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE RankNTypes #-} {-# LANGUAGE RankNTypes #-}
...@@ -195,12 +195,11 @@ flowCorpusUser l userName corpusName ctype ids = do ...@@ -195,12 +195,11 @@ flowCorpusUser l userName corpusName ctype ids = do
printDebug "userListId" userListId printDebug "userListId" userListId
-- User Graph Flow -- User Graph Flow
_ <- mkTexts userCorpusId userId _ <- mkTexts userCorpusId userId
--_ <- mkGraph userCorpusId userId _ <- mkDashboard userCorpusId userId
--_ <- mkPhylo userCorpusId userId _ <- mkGraph userCorpusId userId
_ <- mkPhylo userCorpusId userId
--} --}
-- User Dashboard Flow
--_ <- mkDashboard userCorpusId userId
-- Annuaire Flow -- Annuaire Flow
-- _ <- mkAnnuaire rootUserId userId -- _ <- mkAnnuaire rootUserId userId
......
...@@ -9,10 +9,8 @@ Portability : POSIX ...@@ -9,10 +9,8 @@ Portability : POSIX
TODO: TODO:
- generalize to byteString - generalize to byteString
- Stop words and (how to learn it).
Stop words and (how to learn it). - Main type here is String check if Chars on Text would be optimized
Main type here is String.
-} -}
...@@ -68,6 +66,19 @@ data CatWord a = CatWord a Word ...@@ -68,6 +66,19 @@ data CatWord a = CatWord a Word
type CatProb a = Map a Double type CatProb a = Map a Double
type Events a = Map a EventBook type Events a = Map a EventBook
------------------------------------------------------------------------
data EventBook = EventBook { events_freq :: Map String Freq
, events_n :: Map StringSize TotalFreq
}
deriving (Show, Generic)
instance Serialise EventBook
instance (Serialise a, Ord a) => SaveFile (Events a) where
saveFile' f d = BSL.writeFile f (serialise d)
instance (Serialise a, Ord a) => ReadFile (Events a) where
readFile' filepath = deserialise <$> BSL.readFile filepath
------------------------------------------------------------------------ ------------------------------------------------------------------------
detectStopDefault :: Text -> Maybe Bool detectStopDefault :: Text -> Maybe Bool
...@@ -174,20 +185,6 @@ toEvents e ns n = foldl' (opEvent (+)) (emptyEvent e ns n) . map (toEvent ns n) ...@@ -174,20 +185,6 @@ toEvents e ns n = foldl' (opEvent (+)) (emptyEvent e ns n) . map (toEvent ns n)
opEvent f = DM.unionWith (op f) opEvent f = DM.unionWith (op f)
------------------------------------------------------------------------ ------------------------------------------------------------------------
------------------------------------------------------------------------
data EventBook = EventBook { events_freq :: Map String Freq
, events_n :: Map StringSize TotalFreq
}
deriving (Show, Generic)
instance Serialise EventBook
instance (Serialise a, Ord a) => SaveFile (Events a) where
saveFile' f d = BSL.writeFile f (serialise d)
instance (Serialise a, Ord a) => ReadFile (Events a) where
readFile' filepath = deserialise <$> BSL.readFile filepath
emptyEventBook :: [Int] -> Int -> EventBook emptyEventBook :: [Int] -> Int -> EventBook
emptyEventBook ns n = wordToBook ns n " " emptyEventBook ns n = wordToBook ns n " "
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment