module System.Console.Ansigraph.Internal.Horizontal (
displayRV
, displayCV
, simpleRender
, simpleRenderR
) where
import System.Console.Ansigraph.Internal.Core
import Data.Complex
barChars = "█▇▆▅▄▃▂▁"
barVals :: [Double]
barVals = (+ 0.0625) . (/8) <$> [7,6..0]
bars, barsR :: [(Double,Char)]
bars = zipWith (,) barVals barChars
barsR = zipWith (,) barVals (reverse barChars)
selectBar, selectBarR :: Double -> Char
selectBar x = let l = filter (\p -> fst p < x) bars in case l of
[] -> ' '
(p:ss) -> snd p
selectBarR x = let l = filter (\p -> fst p < x) barsR in case l of
[] -> '█'
(p:ss) -> snd p
simpleRender :: [Double] -> String
simpleRender xs = let mx = maximum xs in
(selectBar . (/mx)) <$> xs
simpleRenderR :: [Double] -> String
simpleRenderR xs = let mx = maximum xs in
(selectBarR . (/mx)) <$> xs
renderCV :: [Complex Double] -> (String,String,String,String)
renderCV l = let rp = realPart <$> l
rm = negate <$> rp
ip = imagPart <$> l
im = negate <$> ip
mx = maximum $ rp ++ rm ++ ip ++ im
in (selectBar . (/mx) <$> rp,
selectBarR . (/mx) <$> rm,
selectBar . (/mx) <$> ip,
selectBarR . (/mx) <$> im)
renderRV :: [Double] -> (String,String)
renderRV l = let rp = l
rm = negate <$> rp
mx = maximum $ rp ++ rm
in (selectBar . (/mx) <$> rp,
selectBarR . (/mx) <$> rm)
displayCV :: AGSettings -> [Complex Double] -> IO ()
displayCV s l = let (rp,rm,ip,im) = renderCV l
(rcol,icol) = colorSets s
in do withColoring rcol $ putStr rp
withColoring (invert rcol) $ putStr rm
withColoring icol $ putStr ip
withColoring (invert icol) $ putStr im
displayRV :: AGSettings -> [Double] -> IO ()
displayRV s l = let (rp,rm) = renderRV l
rcol = realColors s
in do withColoring rcol $ putStr rp
withColoring (invert rcol) $ putStr rm