{-# OPtIONS_HADDOCK show-extensions #-} {-# LANGUAGE BangPatterns #-} {-| Module : GVTI.Formatting Description : GraphViz Tabular Interface formatting functionality to be used with the @gvti -g@. Copyright : (c) Oleksandr Zhabenko, 2017-2023 License : MIT Maintainer : oleksandr.zhabenko@yahoo.com Stability : Experimental Some functions used for formatting of the data for further GraphViz processment. -} {-# LANGUAGE NoImplicitPrelude #-} module GVTI.Formatting where import GHC.Base import GHC.List import GHC.Num ((+), (-)) import Text.Read (readMaybe) import Data.Maybe (fromMaybe) import Data.Char (isDigit) formatBStr :: Int -> Char -> String -> String formatBStr n x xs | n > 0 = (iterate (x:) xs) !! n | otherwise = xs formatEStr :: Int -> Char -> String -> String formatEStr m x xs | m > 0 = xs `mappend` replicate m x | otherwise = xs formatBothStr :: Int -> Int -> Char -> String -> String formatBothStr m n x = formatBStr m x . formatEStr n x {-# INLINE formatBothStr #-} -- | Applies needed formatting for the data to be acceptable for GraphViz. formatLines :: Char -> [String] -> [String] formatLines x xss = map (\(xs,n,m) -> formatBothStr n m x $ xs) . zip3 ws j2s $ ms where (!js,!rs) = unzip . map (span isDigit) $ xss ws = map (dropWhile (== ',')) rs ll1s = map (length . filter (== x)) $ xss !j2s = map (\wws -> fromMaybe 0 (readMaybe wws::Maybe Int)) js lls = zipWith (+) ll1s j2s !mx = maximum lls !ms = zipWith (\x k -> mx - x - k) ll1s j2s {-# INLINE formatLines #-}