module Data.List.ZigZag
( diagonals
, fromDiagonals
, fromList
, toDiagonals
, toList
, ZigZag()
)
where
import Control.Applicative
( Alternative(empty, (<|>))
, Applicative(pure, (<*>))
)
import Control.Monad
( ap
, join
, Monad(return, (>>=))
, MonadPlus(mzero, mplus)
)
import Data.Data
( Data
)
import Data.Foldable
( concat
, Foldable
)
import Data.Functor.Classes
( Eq1(liftEq)
, Ord1(liftCompare)
, Read1(liftReadList, liftReadsPrec)
, readsData
, readsUnaryWith
, showsUnaryWith
, Show1(liftShowList, liftShowsPrec)
)
import Data.List
( transpose
, unzip
, (++)
)
import Data.Maybe
( catMaybes
, Maybe(Just, Nothing)
)
import Data.Monoid
( Monoid(mappend, mempty)
)
import Data.Semigroup
( Semigroup((<>))
)
import Data.Traversable
( Traversable
)
import Data.Typeable
( Typeable
)
import GHC.Base
( Functor(fmap)
, (.)
, ($)
)
import GHC.Exts
( IsList(Item)
)
import qualified GHC.Exts as IsList
( fromList
, toList
)
import GHC.Generics
( Generic
, Generic1
)
import GHC.Read
( lexP
, parens
, Read(readPrec)
)
import GHC.Show
( Show(showsPrec)
, showParen
, showString
)
import Prelude
( Eq
, Ord((>))
)
import Text.ParserCombinators.ReadPrec
( prec
)
import Text.Read.Lex
( Lexeme(Ident)
)
newtype Diagonal a =
Diagonal
{ unDiagonal :: [a]
}
deriving
( Alternative
, Applicative
, Data
, Eq
, Eq1
, Foldable
, Functor
, Generic
, Generic1
, Monad
, MonadPlus
, Monoid
, Ord
, Ord1
, Read
, Semigroup
, Show
, Show1
, Traversable
, Typeable
)
instance IsList (Diagonal a) where
type (Item (Diagonal a)) = a
fromList = Diagonal
toList = unDiagonal
data These a b =
This a
| That b
| Both a b
newtype ZigZag a =
ZigZag
{ unZigZag :: [Diagonal a]
}
deriving
( Data
, Eq
, Foldable
, Functor
, Generic
, Generic1
, Ord
, Traversable
, Typeable
)
instance Alternative ZigZag where
empty = ZigZag empty
(<|>) (ZigZag xs) (ZigZag ys) = ZigZag (tie f xs ys)
where
f (Both x y) = x <|> y
f (This x) = x
f (That y) = y
instance Applicative ZigZag where
pure = return
(<*>) = ap
instance Eq1 ZigZag where
liftEq eq (ZigZag xs) (ZigZag ys) = liftEq (liftEq eq) xs ys
instance IsList (ZigZag a) where
type (Item (ZigZag a)) = a
fromList = fromList
toList = toList
instance Monad ZigZag where
return = ZigZag . return . return
(>>=) (ZigZag xs) f =
ZigZag (fmap (join . Diagonal) (diagonals (fmap inner xs)))
where
inner =
fmap (Diagonal . concat)
. transpose
. unDiagonal
. fmap (fmap unDiagonal . unZigZag . f)
instance MonadPlus ZigZag where
mzero = empty
mplus = (<|>)
instance Monoid (ZigZag a) where
mempty = empty
mappend = (<|>)
instance Ord1 ZigZag where
liftCompare cmp (ZigZag xs) (ZigZag ys) =
liftCompare (liftCompare cmp) xs ys
instance Read a => Read (ZigZag a) where
readPrec = parens . prec 10 $ do
Ident "fromDiagonals" <- lexP
xs <- readPrec
return (fromDiagonals xs)
instance Read1 ZigZag where
liftReadsPrec rp rl =
readsData $
readsUnaryWith
(liftReadsPrec (liftReadsPrec rp rl) (liftReadList rp rl))
"fromDiagonals"
fromDiagonals
instance Semigroup (ZigZag a) where
(<>) = mappend
instance Show a => Show (ZigZag a) where
showsPrec p xs =
showParen (p > 10)
( showString "fromDiagonals "
. showsPrec 10 (toDiagonals xs)
)
instance Show1 ZigZag where
liftShowsPrec sp sl d m =
showsUnaryWith
(liftShowsPrec (liftShowsPrec sp sl) (liftShowList sp sl))
"fromDiagonals"
d
(toDiagonals m)
diagonals :: [[a]] -> [[a]]
diagonals = h []
where
h rem xxs =
let (heads, tails) = peel rem
in case xxs of
((y:ys):xs) -> (y : heads) : h (ys : tails) xs
([]:xs) -> heads : h tails xs
[] ->
case heads of
(_:_) -> heads : transpose tails
[] -> transpose tails
peel = unzip . catMaybes . fmap uncons
fromDiagonals :: [[a]] -> ZigZag a
fromDiagonals = ZigZag . fmap Diagonal
fromList :: [a] -> ZigZag a
fromList = ZigZag . fmap (Diagonal . return)
tie :: (These a b -> c) -> [a] -> [b] -> [c]
tie f (x:xs) (y:ys) = f (Both x y) : tie f xs ys
tie f (x:xs) [] = f (This x) : tie f xs []
tie f [] (y:ys) = f (That y) : tie f [] ys
tie f [] [] = []
toDiagonals :: ZigZag a -> [[a]]
toDiagonals = fmap unDiagonal . unZigZag
toList :: ZigZag a -> [a]
toList = concat . fmap unDiagonal . unZigZag
uncons :: [a] -> Maybe (a, [a])
uncons (x:xs) = Just (x, xs)
uncons [] = Nothing