Commit 38592e99 authored by Alfredo Di Napoli's avatar Alfredo Di Napoli Committed by Alfredo Di Napoli

Introduce the ToCustomAttribute typeclass

This will allow us to render properly some Phylo attributes into the
graphviz `.dot` in the PhyloExport.
parent af9d1345
Pipeline #5607 failed with stages
in 33 minutes and 48 seconds
...@@ -13,7 +13,6 @@ import GHC.IO.Encoding ...@@ -13,7 +13,6 @@ import GHC.IO.Encoding
import GHC.Stack import GHC.Stack
import Paths_gargantext import Paths_gargantext
import Prelude import Prelude
import qualified Data.Text as T
import Shelly import Shelly
import System.Directory import System.Directory
......
...@@ -10,6 +10,9 @@ Portability : POSIX ...@@ -10,6 +10,9 @@ Portability : POSIX
{-# OPTIONS_GHC -fno-warn-deprecations #-} {-# OPTIONS_GHC -fno-warn-deprecations #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module Gargantext.Core.Viz.Phylo.PhyloExport where module Gargantext.Core.Viz.Phylo.PhyloExport where
...@@ -33,6 +36,48 @@ import Gargantext.Core.Viz.Phylo ...@@ -33,6 +36,48 @@ import Gargantext.Core.Viz.Phylo
import Gargantext.Core.Viz.Phylo.PhyloTools import Gargantext.Core.Viz.Phylo.PhyloTools
import Gargantext.Core.Viz.Phylo.TemporalMatching (filterDocs, filterDiago, reduceDiagos, toSimilarity, getNextPeriods) import Gargantext.Core.Viz.Phylo.TemporalMatching (filterDocs, filterDiago, reduceDiagos, toSimilarity, getNextPeriods)
import Gargantext.Prelude hiding (empty, scale, toList) import Gargantext.Prelude hiding (empty, scale, toList)
import qualified Prelude
-- | Temporary compat shim for older Phylo attributes which we still export
-- \"the old way\", i.e. via their 'Show' instance.
newtype ShowableAsIs a = ShowableAsIs a
deriving stock Eq
deriving newtype Show
-- | A typeclass to render the input type into a suitable
-- representation for the Graphviz graph. This avoids mindlessly
-- calling 'show' on types like 'Maybe' which would otherwise
-- render badly.
class ToCustomAttribute a where
toCustomAttribute :: a -> Text.Text
instance ToCustomAttribute Lazy.Text where
toCustomAttribute = Lazy.toStrict
instance ToCustomAttribute Text where
toCustomAttribute = identity
instance ToCustomAttribute Int where
toCustomAttribute = toCustomAttribute . Text.pack. Prelude.show
instance ToCustomAttribute Double where
toCustomAttribute = toCustomAttribute . Text.pack . Prelude.show
instance ToCustomAttribute Char where
toCustomAttribute = toCustomAttribute . Text.singleton
instance ToCustomAttribute a => ToCustomAttribute [a] where
toCustomAttribute xs = "[" <> Text.intercalate "," (map toCustomAttribute xs) <> "]"
instance ToCustomAttribute a => ToCustomAttribute (Vector a) where
toCustomAttribute = toCustomAttribute . Vector.toList
instance Show a => ToCustomAttribute (ShowableAsIs a) where
toCustomAttribute = toCustomAttribute . Text.pack . show
-- FIXME(adinapoli) The following are derived using 'deriving via' and
-- defaults to the old style.
deriving via (ShowableAsIs Cooc) instance ToCustomAttribute Cooc
-------------------- --------------------
-- | Dot export | -- -- | Dot export | --
...@@ -61,8 +106,15 @@ pickLabelColor lst ...@@ -61,8 +106,15 @@ pickLabelColor lst
toDotLabel :: Text.Text -> Label toDotLabel :: Text.Text -> Label
toDotLabel lbl = StrLabel $ fromStrict lbl toDotLabel lbl = StrLabel $ fromStrict lbl
toAttr :: AttributeName -> Lazy.Text -> CustomAttribute toAttr :: ToCustomAttribute a => AttributeName -> a -> CustomAttribute
toAttr k v = customAttribute k v toAttr k = customAttribute k . Lazy.fromStrict . toCustomAttribute
-- | Monomorphic version of 'toAttr' that works on (strict) 'Text'.
toTextAttr :: AttributeName -> Text.Text -> CustomAttribute
toTextAttr = toAttr
toAttrDefault :: ToCustomAttribute a => a -> AttributeName -> Maybe a -> CustomAttribute
toAttrDefault def k mb_v = customAttribute k . Lazy.fromStrict $ toCustomAttribute (fromMaybe def mb_v)
metaToAttr :: Map Text.Text [Double] -> [CustomAttribute] metaToAttr :: Map Text.Text [Double] -> [CustomAttribute]
metaToAttr meta = map (\(k, v) -> toAttr (fromStrict k) $ (fromStrict . unwords) $ map show v) $ toList meta metaToAttr meta = map (\(k, v) -> toAttr (fromStrict k) $ (fromStrict . unwords) $ map show v) $ toList meta
...@@ -85,13 +137,13 @@ branchToDotNode b bId = ...@@ -85,13 +137,13 @@ branchToDotNode b bId =
, FontSize 40 , FontSize 40
, Shape Egg , Shape Egg
, Style [SItem Bold []] ] , Style [SItem Bold []] ]
<> (metaToAttr $ b ^. branch_meta) <> metaToAttr (b ^. branch_meta)
<> [ toAttr "nodeType" "branch" <> [ toAttr @Lazy.Text "nodeType" "branch"
, toAttr "bId" (show bId) , toAttr "bId" bId
, toAttr "branchId" (fromStrict $ unwords (map show $ snd $ b ^. branch_id)) , toAttr "branchId" (fromStrict $ unwords (map show $ snd $ b ^. branch_id))
, toAttr "branch_x" (fromStrict $ show $ b ^. branch_x) , toAttr "branch_x" (b ^. branch_x)
, toAttr "branch_y" (fromStrict $ show $ b ^. branch_y) , toAttr "branch_y" (b ^. branch_y)
, toAttr "label" (show $ b ^. branch_label) , toAttr "label" (b ^. branch_label)
]) ])
periodToDotNode :: (Date,Date) -> (Text.Text,Text.Text) -> Dot DotId periodToDotNode :: (Date,Date) -> (Text.Text,Text.Text) -> Dot DotId
...@@ -100,58 +152,76 @@ periodToDotNode prd prd' = ...@@ -100,58 +152,76 @@ periodToDotNode prd prd' =
[ Shape BoxShape [ Shape BoxShape
, FontSize 50 , FontSize 50
, Label $ toDotLabel $ Text.pack $ show (fst prd) <> " " <> show (snd prd) ] , Label $ toDotLabel $ Text.pack $ show (fst prd) <> " " <> show (snd prd) ]
<> [ toAttr "nodeType" "period" <> [ toAttr @Text.Text "nodeType" "period"
, toAttr "strFrom" $ fromStrict $ show $ fst prd' , toAttr "strFrom" $ fst prd'
, toAttr "strTo" $ fromStrict $ show $ snd prd' , toAttr "strTo" $ snd prd'
, toAttr "from" $ fromStrict $ show $ fst prd , toAttr "from" $ fst prd
, toAttr "to" $ fromStrict $ show $ snd prd ] , toAttr "to" $ snd prd ]
groupToDotNode :: Vector Ngrams -> PhyloGroup -> Int -> Dot DotId groupToDotNode :: Vector Ngrams -> PhyloGroup -> Int -> Dot DotId
groupToDotNode fdt g bId = groupToDotNode fdt g bId =
node (groupIdToDotId $ getGroupId g) node (groupIdToDotId $ getGroupId g)
([FontName "Arial", Shape Square, penWidth 4] ([FontName "Arial", Shape Square, penWidth 4]
<> [ toAttr "nodeType" "group" <> [ toAttr @Text.Text "nodeType" "group"
, toAttr "gid" (groupIdToDotId $ getGroupId g) , toAttr "gid" (groupIdToDotId $ getGroupId g)
, toAttr "from" (show (fst $ g ^. phylo_groupPeriod)) , toAttr "from" (fst $ g ^. phylo_groupPeriod)
, toAttr "to" (show (snd $ g ^. phylo_groupPeriod)) , toAttr "to" (snd $ g ^. phylo_groupPeriod)
, toAttr "strFrom" (show (fst $ g ^. phylo_groupPeriod')) , toAttr "strFrom" (fst $ g ^. phylo_groupPeriod')
, toAttr "strTo" (show (snd $ g ^. phylo_groupPeriod')) , toAttr "strTo" (snd $ g ^. phylo_groupPeriod')
, toAttr "branchId" (fromStrict $ unwords (init $ map show $ snd $ g ^. phylo_groupBranchId)) , toAttr "branchId" (fromStrict $ unwords (init $ map show $ snd $ g ^. phylo_groupBranchId))
, toAttr "bId" (show bId) , toAttr "bId" bId
, toAttr "support" (show (g ^. phylo_groupSupport)) , toAttr "support" (g ^. phylo_groupSupport)
, toAttr "weight" (show (g ^. phylo_groupWeight)) , toAttrDefault 1.0 "weight" (g ^. phylo_groupWeight)
, toAttr "source" (show (nub $ g ^. phylo_groupSources)) , toAttr "source" (nub $ g ^. phylo_groupSources)
, toAttr "sourceFull" (show (g ^. phylo_groupSources)) , toAttr "sourceFull" (g ^. phylo_groupSources)
, toAttr "density" (show (g ^. phylo_groupDensity)) , toAttr "density" (g ^. phylo_groupDensity)
, toAttr "cooc" (show (g ^. phylo_groupCooc)) , toAttr "cooc" (g ^. phylo_groupCooc)
, toAttr "lbl" (show (ngramsToLabel fdt (g ^. phylo_groupNgrams))) , toAttr "lbl" (ngramsToLabel fdt (g ^. phylo_groupNgrams))
, toAttr "foundation" (show (idxToLabel (g ^. phylo_groupNgrams))) , toAttr "foundation" (idxToLabel (g ^. phylo_groupNgrams))
, toAttr "role" (show (idxToLabel' ((g ^. phylo_groupMeta) ! "dynamics"))) , toAttr "role" (idxToLabel' ((g ^. phylo_groupMeta) ! "dynamics"))
, toAttr "frequence" (show (idxToLabel' ((g ^. phylo_groupMeta) ! "frequence"))) , toAttr "frequence" (idxToLabel' ((g ^. phylo_groupMeta) ! "frequence"))
, toAttr "seaLvl" (show ((g ^. phylo_groupMeta) ! "seaLevels")) , toAttr "seaLvl" ((g ^. phylo_groupMeta) ! "seaLevels")
]) ])
toDotEdge' :: DotId -> DotId -> [Char] -> [Char] -> EdgeType -> Dot DotId
toDotEdge' source target thr w edgeType = edge source target
(case edgeType of
GroupToGroup -> undefined
GroupToGroupMemory -> [ Width 3, penWidth 4, Color [toWColor Black], Constraint True] <> [toAttr "edgeType" "memoryLink", toAttr "thr" (pack thr), toAttr "weight" (pack w)]
BranchToGroup -> undefined
BranchToBranch -> undefined
GroupToAncestor -> undefined
PeriodToPeriod -> undefined)
toDotEdge :: DotId -> DotId -> [Char] -> EdgeType -> Dot DotId toDotEdge :: DotId -> DotId -> [Char] -> EdgeType -> Dot DotId
toDotEdge source target lbl edgeType = edge source target toDotEdge source target lbl edgeType = edge source target $ case edgeType of
(case edgeType of GroupToGroup
GroupToGroup -> [ Width 3, penWidth 4, Color [toWColor Black], Constraint True] <> [toAttr "edgeType" "link", toAttr "lbl" (pack lbl), toAttr "source" source, toAttr "target" target] -> [ Width 3
GroupToGroupMemory -> undefined , penWidth 4
BranchToGroup -> [ Width 3, Color [toWColor Black], ArrowHead (AType [(ArrMod FilledArrow RightSide,DotArrow)])] <> [toAttr "edgeType" "branchLink" ] , Color [toWColor Black]
BranchToBranch -> [ Width 2, Color [toWColor Black], Style [SItem Dashed []], ArrowHead (AType [(ArrMod FilledArrow BothSides,DotArrow)])] , Constraint True
GroupToAncestor -> [ Width 3, Color [toWColor Red], Style [SItem Dashed []], ArrowHead (AType [(ArrMod FilledArrow BothSides,NoArrow)]), PenWidth 4] <> [toAttr "edgeType" "ancestorLink", toAttr "lbl" (pack lbl), toAttr "source" source, toAttr "target" target] ] <> [ toTextAttr "edgeType" "link"
PeriodToPeriod -> [ Width 5, Color [toWColor Black]]) , toAttr "lbl" (pack lbl)
, toAttr "source" source
, toAttr "target" target
]
GroupToGroupMemory
-> undefined
BranchToGroup
-> [ Width 3
, Color [toWColor Black]
, ArrowHead (AType [(ArrMod FilledArrow RightSide,DotArrow)])
] <> [toTextAttr "edgeType" "branchLink" ]
BranchToBranch
-> [ Width 2
, Color [toWColor Black]
, Style [SItem Dashed []]
, ArrowHead (AType [(ArrMod FilledArrow BothSides,DotArrow)])
]
GroupToAncestor
-> [ Width 3
, Color [toWColor Red]
, Style [SItem Dashed []]
, ArrowHead (AType [(ArrMod FilledArrow BothSides,NoArrow)])
, PenWidth 4
] <> [ toTextAttr "edgeType" "ancestorLink"
, toAttr "lbl" (pack lbl)
, toAttr "source" source
, toAttr "target" target
]
PeriodToPeriod
-> [ Width 5, Color [toWColor Black]]
mergePointers :: [PhyloGroup] -> Map (PhyloGroupId,PhyloGroupId) Double mergePointers :: [PhyloGroup] -> Map (PhyloGroupId,PhyloGroupId) Double
...@@ -193,18 +263,18 @@ exportToDot phylo export = ...@@ -193,18 +263,18 @@ exportToDot phylo export =
-- , Ratio AutoRatio -- , Ratio AutoRatio
, Style [SItem Filled []],Color [toWColor White]] , Style [SItem Filled []],Color [toWColor White]]
{-- home made attributes -} {-- home made attributes -}
<> [ toAttr (fromStrict "phyloFoundations") $ show (length $ Vector.toList $ getRoots phylo) <> [ toAttr "phyloFoundations" $ (length $ Vector.toList $ getRoots phylo)
, toAttr (fromStrict "phyloTerms") $ show (length $ nub $ concat $ map (^. phylo_groupNgrams) $ export ^. export_groups) , toAttr "phyloTerms" $ (length $ nub $ concat $ map (^. phylo_groupNgrams) $ export ^. export_groups)
, toAttr (fromStrict "phyloDocs") $ show (sum $ elems $ getDocsByDate phylo) , toAttr "phyloDocs" $ (sum $ elems $ getDocsByDate phylo)
, toAttr (fromStrict "phyloPeriods") $ show (length $ elems $ phylo ^. phylo_periods) , toAttr "phyloPeriods" $ (length $ elems $ phylo ^. phylo_periods)
, toAttr (fromStrict "phyloBranches") $ show (length $ export ^. export_branches) , toAttr "phyloBranches" $ (length $ export ^. export_branches)
, toAttr (fromStrict "phyloGroups") $ show (length $ export ^. export_groups) , toAttr "phyloGroups" $ (length $ export ^. export_groups)
, toAttr (fromStrict "phyloSources") $ show (Vector.toList $ getSources phylo) , toAttr "phyloSources" $ (getSources phylo)
, toAttr (fromStrict "phyloTimeScale") $ pack $ getTimeScale phylo , toAttr "phyloTimeScale" $ pack $ getTimeScale phylo
, toAttr (fromStrict "PhyloScale") $ show (getLevel phylo) , toAttr "PhyloScale" $ (getLevel phylo)
, toAttr (fromStrict "phyloQuality") $ show (phylo ^. phylo_quality) , toAttr "phyloQuality" $ (phylo ^. phylo_quality)
, toAttr (fromStrict "phyloSeaRiseStart") $ show (getPhyloSeaRiseStart phylo) , toAttr "phyloSeaRiseStart" $ (getPhyloSeaRiseStart phylo)
, toAttr (fromStrict "phyloSeaRiseSteps") $ show (getPhyloSeaRiseSteps phylo) , toAttr "phyloSeaRiseSteps" $ (getPhyloSeaRiseSteps phylo)
-- ,(toAttr (fromStrict "phyloTermsFreq") $ show (toList $ _phylo_lastTermFreq phylo)) -- ,(toAttr (fromStrict "phyloTermsFreq") $ show (toList $ _phylo_lastTermFreq phylo))
]) ])
......
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