Commit afcac0ef authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski Committed by Alexandre Delanoë

[phylo] some refactoring

parent 26d9c2d5
...@@ -46,6 +46,8 @@ import Gargantext.Database.Schema.Ngrams (NgramsType(..)) ...@@ -46,6 +46,8 @@ import Gargantext.Database.Schema.Ngrams (NgramsType(..))
import Gargantext.Database.Schema.Node import Gargantext.Database.Schema.Node
import Gargantext.Prelude import Gargantext.Prelude
import Prelude import Prelude
import System.FilePath ((</>))
import System.IO.Temp (withTempDirectory)
import System.Process as Shell import System.Process as Shell
import qualified Data.ByteString.Lazy as Lazy import qualified Data.ByteString.Lazy as Lazy
import qualified Data.List as List import qualified Data.List as List
...@@ -67,30 +69,35 @@ savePhylo = undefined ...@@ -67,30 +69,35 @@ savePhylo = undefined
-------------------------------------------------------------------- --------------------------------------------------------------------
phylo2dot2json :: Phylo -> IO Value phylo2dot2json :: Phylo -> IO Value
phylo2dot2json phylo = do phylo2dot2json phylo = do
withTempDirectory "/tmp" "phylo" $ \dirPath -> do
let fileFrom = dirPath </> "phyloFrom.dot"
fileDot = dirPath </> "phylo.dot"
fileToJson = dirPath </> "output.json"
let dotToFile fileFrom (toPhyloExport phylo)
file_from = "/tmp/fromPhylo.json"
file_dot = "/tmp/tmp.dot" Shell.callProcess "dot" ["-Tdot", "-o", fileDot, fileFrom]
file_to_json = "/tmp/toPhylo.json" Shell.callProcess "dot" ["-Txdot_json", "-o", fileToJson, fileDot]
_ <- dotToFile file_from (toPhyloExport phylo) ffrom <- readFile fileFrom
_ <- Shell.callProcess "dot" ["-Tdot", "-o", file_dot, file_from] writeFile "/tmp/fileFrom.json" ffrom
_ <- Shell.callProcess "dot" ["-Txdot_json", "-o", file_to_json, file_dot] fdot <- readFile fileDot
writeFile "/tmp/file.dot" fdot
fto <- readFile fileToJson
writeFile "/tmp/fileTo.json" fto
maybeValue <- decodeFileStrict file_to_json maybeValue <- decodeFileStrict fileToJson
print maybeValue print maybeValue
_ <- Shell.callProcess "/bin/rm" ["-rf", file_from, file_to_json, file_dot]
case maybeValue of case maybeValue of
Nothing -> panic "[G.C.V.Phylo.API.phylo2dot2json] Error no file" Nothing -> panic "[G.C.V.Phylo.API.phylo2dot2json] Error no file"
Just v -> pure v Just v -> pure v
flowPhyloAPI :: PhyloConfig -> CorpusId -> GargNoServer Phylo flowPhyloAPI :: PhyloConfig -> CorpusId -> GargNoServer Phylo
flowPhyloAPI config cId = do flowPhyloAPI config cId = do
(_, corpus) <- corpusIdtoDocuments (timeUnit config) cId (_, corpus) <- corpusIdtoDocuments (timeUnit config) cId
phyloWithCliques <- pure $ toPhyloWithoutLink corpus config let phyloWithCliques = toPhyloWithoutLink corpus config
-- writePhylo phyloWithCliquesFile phyloWithCliques -- writePhylo phyloWithCliquesFile phyloWithCliques
pure $ toPhylo (setConfig config phyloWithCliques) pure $ toPhylo (setConfig config phyloWithCliques)
...@@ -172,19 +179,15 @@ toDays y m d = fromIntegral ...@@ -172,19 +179,15 @@ toDays y m d = fromIntegral
toPhyloDate :: Int -> Int -> Int -> TimeUnit -> Date toPhyloDate :: Int -> Int -> Int -> TimeUnit -> Date
toPhyloDate y m d tu = case tu of toPhyloDate y m d tu = case tu of
Year _ _ _ -> y Year {} -> y
Month _ _ _ -> toMonths (Prelude.toInteger y) m d Month {} -> toMonths (Prelude.toInteger y) m d
Week _ _ _ -> div (toDays (Prelude.toInteger y) m d) 7 Week {} -> div (toDays (Prelude.toInteger y) m d) 7
Day _ _ _ -> toDays (Prelude.toInteger y) m d Day {} -> toDays (Prelude.toInteger y) m d
_ -> panic "[G.C.V.Phylo.API] toPhyloDate" _ -> panic "[G.C.V.Phylo.API] toPhyloDate"
toPhyloDate' :: Int -> Int -> Int -> TimeUnit -> Text toPhyloDate' :: Int -> Int -> Int -> TimeUnit -> Text
toPhyloDate' y m d tu = case tu of toPhyloDate' y _m _d (Epoch {}) = pack $ show $ posixSecondsToUTCTime $ fromIntegral y
Epoch _ _ _ -> pack $ show $ posixSecondsToUTCTime $ fromIntegral y toPhyloDate' y m d _ = pack $ showGregorian $ fromGregorian (toInteger y) m d
Year _ _ _ -> pack $ showGregorian $ fromGregorian (toInteger y) m d
Month _ _ _ -> pack $ showGregorian $ fromGregorian (toInteger y) m d
Week _ _ _ -> pack $ showGregorian $ fromGregorian (toInteger y) m d
Day _ _ _ -> pack $ showGregorian $ fromGregorian (toInteger y) m d
-- Utils -- Utils
...@@ -204,4 +207,4 @@ readPhylo path = do ...@@ -204,4 +207,4 @@ readPhylo path = do
-- | To read and decode a Json file -- | To read and decode a Json file
readJson :: FilePath -> IO Lazy.ByteString readJson :: FilePath -> IO Lazy.ByteString
readJson path = Lazy.readFile path readJson = Lazy.readFile
...@@ -652,7 +652,7 @@ toHorizon phylo = ...@@ -652,7 +652,7 @@ toHorizon phylo =
Adaptative _ -> 0 Adaptative _ -> 0
Evolving _ -> 0 Evolving _ -> 0
-- in headsToAncestors nbDocs diago Similarity heads groups [] -- in headsToAncestors nbDocs diago Similarity heads groups []
in map (\ego -> toAncestor nbDocs diago sim step noHeads ego) in map (toAncestor nbDocs diago sim step noHeads)
$ headsToAncestors nbDocs diago sim step heads [] $ headsToAncestors nbDocs diago sim step heads []
) periods ) periods
-- | 3) process this task concurrently -- | 3) process this task concurrently
...@@ -684,17 +684,18 @@ toPhyloExport phylo = exportToDot phylo ...@@ -684,17 +684,18 @@ toPhyloExport phylo = exportToDot phylo
let seaLvl = (g ^. phylo_groupMeta) ! "seaLevels" let seaLvl = (g ^. phylo_groupMeta) ! "seaLevels"
breaks = (g ^. phylo_groupMeta) ! "breaks" breaks = (g ^. phylo_groupMeta) ! "breaks"
canonId = take (round $ (last' "export" breaks) + 2) (snd $ g ^. phylo_groupBranchId) canonId = take (round $ (last' "export" breaks) + 2) (snd $ g ^. phylo_groupBranchId)
in PhyloBranch (g ^. phylo_groupBranchId) in PhyloBranch { _branch_id = g ^. phylo_groupBranchId
canonId , _branch_canonId = canonId
seaLvl , _branch_seaLevel = seaLvl
0 , _branch_x = 0
(last' "export" (take (round $ (last' "export" breaks) + 1) seaLvl)) , _branch_y = last' "export" $ take (round $ (last' "export" breaks) + 1) seaLvl
0 , _branch_w = 0
0 , _branch_t = 0
"" empty) , _branch_label = ""
$ map (\gs -> head' "export" gs) , _branch_meta = empty })
$ map (head' "export")
$ groupBy (\g g' -> g ^. phylo_groupBranchId == g' ^. phylo_groupBranchId) $ groupBy (\g g' -> g ^. phylo_groupBranchId == g' ^. phylo_groupBranchId)
$ sortOn (\g -> g ^. phylo_groupBranchId) groups $ sortOn (^. phylo_groupBranchId) groups
-------------------------------------- --------------------------------------
groups :: [PhyloGroup] groups :: [PhyloGroup]
groups = traceExportGroups groups = traceExportGroups
...@@ -724,4 +725,3 @@ traceExportGroups groups = trace ("\n" <> "-- | Export " ...@@ -724,4 +725,3 @@ traceExportGroups groups = trace ("\n" <> "-- | Export "
<> show(length groups) <> " groups and " <> show(length groups) <> " groups and "
<> show(length $ nub $ concat $ map (\g -> g ^. phylo_groupNgrams) groups) <> " terms" <> show(length $ nub $ concat $ map (\g -> g ^. phylo_groupNgrams) groups) <> " terms"
) groups ) groups
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