module Data.Invertible.List
( cons
, uncons
, consMaybe
, repLen
, map
, reverse
, transpose
, lookup
, index
, zip
, zip3
, zip4
, zip5
, zip6
, zip7
, zipWith
, interleave
, lines
, words
) where
import Prelude hiding (map, reverse, lookup, zip, zip3, unzip, zipWith, lines, words)
import Control.Arrow ((***))
import qualified Data.List as L
import Data.Tuple (swap)
import Data.Invertible.Bijection
import Data.Invertible.TH
import Data.Invertible.Internal
cons :: Maybe (a, [a]) <-> [a]
cons =
[biCase|
Just (a, l) <-> a:l
Nothing <-> []
|]
uncons :: [a] <-> Maybe (a, [a])
uncons = invert cons
consMaybe :: (Maybe a, [a]) <-> [a]
consMaybe =
[biCase|
(Just a, l) <-> a:l
(Nothing, l) <-> l
|]
repLen :: Int <-> [()]
repLen = (`L.replicate` ()) :<->: L.length
map :: (a <-> b) -> [a] <-> [b]
map (f :<->: g) = L.map f :<->: L.map g
reverse :: [a] <-> [a]
reverse = involution L.reverse
transpose :: [[a]] <-> [[a]]
transpose = involution L.transpose
lookup :: (Eq a, Eq b) => [(a, b)] -> Maybe a <-> Maybe b
lookup l = (flip L.lookup l =<<) :<->: (flip L.lookup (L.map swap l) =<<)
index :: Eq a => [a] -> Maybe a <-> Maybe Int
index l = (flip L.elemIndex l =<<) :<->: (idx l =<<) where
idx _ i | i < 0 = Nothing
idx [] _ = Nothing
idx (x:_) 0 = Just x
idx (_:r) i = idx r $ pred i
zip :: ([a], [b]) <-> [(a, b)]
zip = uncurry L.zip :<->: L.unzip
zip3 :: ([a], [b], [c]) <-> [(a, b, c)]
zip3 = (\(a,b,c) -> L.zip3 a b c) :<->: L.unzip3
zip4 :: ([a], [b], [c], [d]) <-> [(a, b, c, d)]
zip4 = (\(a,b,c,d) -> L.zip4 a b c d) :<->: L.unzip4
zip5 :: ([a], [b], [c], [d], [e]) <-> [(a, b, c, d, e)]
zip5 = (\(a,b,c,d,e) -> L.zip5 a b c d e) :<->: L.unzip5
zip6 :: ([a], [b], [c], [d], [e], [f]) <-> [(a, b, c, d, e, f)]
zip6 = (\(a,b,c,d,e,f) -> L.zip6 a b c d e f) :<->: L.unzip6
zip7 :: ([a], [b], [c], [d], [e], [f], [g]) <-> [(a, b, c, d, e, f, g)]
zip7 = (\(a,b,c,d,e,f,g) -> L.zip7 a b c d e f g) :<->: L.unzip7
zipWith :: (a, b) <-> c -> ([a], [b]) <-> [(c)]
zipWith (f :<->: g) = uncurry (L.zipWith (curry f)) :<->: L.unzip . L.map g
interleave :: ([a], [a]) <-> [a]
interleave = uncurry f :<->: g where
f (x:xl) (y:yl) = x:y:f xl yl
f [] l = l
f l [] = l
g (x:y:l) = (x:) *** (y:) $ g l
g l = (l, [])
lines :: String <-> [String]
lines = L.lines :<->: L.unlines
words :: String <-> [String]
words = L.words :<->: L.unwords