85 lines
3.3 KiB
Haskell

{-# LANGUAGE TupleSections #-}
module Diagonal where
import Colonnade
import Data.Profunctor
import Data.Bifunctor
-- Row numbers, as integers with two extra values at the end
data RowNumber = RN Int | Ellipsis | Omega deriving Eq
instance Show RowNumber where
show (RN n) = show n
show Ellipsis = "..."
show Omega = "ω"
-- Rendered cell data, along with its row number and an optional value to show instead
data RenderCell a = RC {
cellRow :: Maybe RowNumber, -- Nothing if this is a header; Just . RC otherwise
cellData :: Either String a -- Left if fixed display data, a otherwise
} deriving Functor
-- If a forced value is availaible, use it; otherwise, show the inside
instance Show a => Show (RenderCell a) where
show (RC _ (Left s)) = s
show (RC _ (Right x)) = show x
-- Lift a RenderCell over Either to an Either over RenderCells
-- If the force-string is set (cellData is a Left), then a `Left` version is produced
liftRC :: RenderCell (Either a b) -> Either (RenderCell a) (RenderCell b)
liftRC (RC rn (Left x)) = Left $ RC rn $ Left x
liftRC (RC rn (Right (Left v))) = Left $ RC rn $ Right v
liftRC (RC rn (Right (Right v))) = Right $ RC rn $ Right v
-- Single column with a fixed header and data coming from a row number
newColumn header f = columns f (\_ -> Headed $ RC Nothing (Left header)) [()]
-- Numbered rows of data, as opposed to data for rendering
data DiagRow a = DR {
rowNumber :: RowNumber,
rowData :: [a]
} deriving Functor
-- Same as `newColumn`, but reads into a DiagRow's row numberRows
-- The display function `f` is used to convert the value to a String
newColumnR header f = newColumn header (\_ c -> RC (Just $ rowNumber c) (Left $ f $ rowNumber c))
-- Number rows with the title "Sequence"
numberColumn = newColumnR "Sequence" show
-- Column of ellipses
ellipsisColumn = newColumnR "..." (const "...")
-- Create a Colonnade over DiagRows by mapping them into lists
-- The ellipsis row is mapped to a cells which always display as ellipses
-- The remaining rows are `Right` if they lie on the main diagonal, or `Left` otherwise
diagBox' n = columns cell headCell [0..n]
where cell _ (DR Ellipsis _) = RC (Just Ellipsis) (Left "...")
cell i (DR rn rd) = RC (Just rn) $ Right $ (if RN i == rn then Right else Left) (rd !! i)
headCell i = Headed $ RC Nothing (Left $ show i)
diagBox n = numberColumn <> diagBox' n <> ellipsisColumn
displayRows f = (displayTable .) . tagRows'
where -- Tag rows by (predicate function, extra value) tuples
tagRows' [] r@(RC rn _) = Left r -- Tag missing things as left
tagRows' ((p, f):ps) r@(RC rn _) = if p == rn then Right (f, r) else tagRows' ps r -- Match found, tag right
displayTable row = case bimap liftRC (fmap liftRC) row of
(Left (Left r)) -> Left r
(Left (Right r)) -> Right $ f r
(Right (g, r)) -> Right $ g $ either id id r
rowsOmega :: [[a]] -> [a] -> [DiagRow a]
rowsOmega xs y = zipWith (\x n -> DR (RN n) x) xs [0..] ++ [DR Ellipsis [], DR Omega y]
diagData = rowsOmega [
[1, 2, 3, 4, 5, 6],
[9, 2, 4, 8, 3, 7],
[2, 2, 8, 2, 2, 2],
[2, 3, 9, 3, 9, 9],
[9, 4, 9, 4, 9, 4],
[8, 1, 2, 5, 7, 9]
]
[2, 3, 9, 4, 0, 0]
displayDiagTable ps = rmap style . diagBox
where style = either show id . displayRows (("Red " ++) . show) (map (, ("Green " ++). show) ps)