module Control.Invertible.Monoidal
(
(>$<)
, (>$), ($<)
, Monoidal(..)
, (>*), (*<)
, liftI2
, liftI3
, liftI4
, liftI5
, (>*<<)
, (>*<<<)
, (>*<<<<)
, (>>*<)
, (>>>*<)
, (>>>>*<)
, (>>*<<)
, pureI
, sequenceI_
, mapI_
, forI_
, sequenceMaybesI
, mapMaybeI
, MonoidalAlt(..)
, (>|), (|<)
, optionalI
, defaulting
, manyI
, msumIndex
, msumFirst, msumLast
, oneOfI
) where
import Prelude
import Control.Arrow ((&&&), (***))
import Data.Invertible.Bijection
import qualified Data.Invertible as I
(>$<) :: I.Functor f => a <-> b -> f a -> f b
(>$<) = I.fmap
infixl 4 $<, >$<, >$
(>$) :: I.Functor f => a -> f a -> f ()
(>$) a = I.fmap $ I.consts a ()
($<) :: I.Functor f => f a -> a -> f ()
($<) = flip (>$)
class I.Functor f => Monoidal f where
unit :: f ()
(>*<) :: f a -> f b -> f (a, b)
(>*) :: Monoidal f => f a -> f () -> f a
(>*) = liftI2 I.fst
(*<) :: Monoidal f => f () -> f a -> f a
(*<) = liftI2 I.snd
infixl 4 >*, >*<, *<
liftI2 :: Monoidal f => ((a, b) <-> c) -> f a -> f b -> f c
liftI2 f a b = f >$< (a >*< b)
liftI3 :: Monoidal f => ((a, b, c) <-> d) -> f a -> f b -> f c -> f d
liftI3 f a b c = f >$< (a >*< b >>*< c)
liftI4 :: Monoidal f => ((a, b, c, d) <-> e) -> f a -> f b -> f c -> f d -> f e
liftI4 f a b c d = f >$< (a >*< b >>*< c >>>*< d)
liftI5 :: Monoidal f => ((a, b, c, d, e) <-> g) -> f a -> f b -> f c -> f d -> f e -> f g
liftI5 f a b c d e = f >$< (a >*< b >>*< c >>>*< d >>>>*< e)
(>>*<) :: Monoidal f => f (a, b) -> f c -> f (a, b, c)
(>>*<) = liftI2 I.flatten2_1
(>>>*<) :: Monoidal f => f (a, b, c) -> f d -> f (a, b, c, d)
(>>>*<) = liftI2 I.flatten3_1
(>>>>*<) :: Monoidal f => f (a, b, c, d) -> f e -> f (a, b, c, d, e)
(>>>>*<) = liftI2 I.flatten4_1
infixl 4 >>*<, >>>*<, >>>>*<
(>*<<) :: Monoidal f => f a -> f (b, c) -> f (a, b, c)
(>*<<) = liftI2 I.flatten1_2
(>*<<<) :: Monoidal f => f a -> f (b, c, d) -> f (a, b, c, d)
(>*<<<) = liftI2 I.flatten1_3
(>*<<<<) :: Monoidal f => f a -> f (b, c, d, e) -> f (a, b, c, d, e)
(>*<<<<) = liftI2 I.flatten1_4
infixr 3 >*<<, >*<<<, >*<<<<
(>>*<<) :: Monoidal f => f (a, b) -> f (c, d) -> f (a, b, c, d)
(>>*<<) = liftI2 I.flatten2_2
infix 3 >>*<<
pureI :: Monoidal f => a -> f a
pureI a = I.const a >$< unit
sequenceI_ :: (Foldable t, Monoidal f) => t (f ()) -> f ()
sequenceI_ = foldr (*<) unit
mapI_ :: (Foldable t, Monoidal f) => (a -> f ()) -> t a -> f ()
mapI_ f = foldr ((*<) . f) unit
forI_ :: (Foldable t, Monoidal f) => t a -> (a -> f ()) -> f ()
forI_ = flip mapI_
sequenceMaybesI :: Monoidal f => [f (Maybe a)] -> f [a]
sequenceMaybesI [] = pureI []
sequenceMaybesI (x:l) = liftI2 I.consMaybe x (sequenceMaybesI l)
mapMaybeI :: Monoidal f => (a -> f (Maybe b)) -> [a] -> f [b]
mapMaybeI = (sequenceMaybesI .) . map
class Monoidal f => MonoidalAlt f where
(>|<) :: f a -> f b -> f (Either a b)
(>|) :: MonoidalAlt f => f a -> f a -> f a
a >| b = (either id id :<->: Left) >$< (a >|< b)
(|<) :: MonoidalAlt f => f a -> f a -> f a
a |< b = (either id id :<->: Right) >$< (a >|< b)
infixl 3 >|, >|<, |<
optionalI :: MonoidalAlt f => f a -> f (Maybe a)
optionalI f = I.lft >$< (f >|< unit)
defaulting :: (MonoidalAlt f, Eq a) => a -> f a -> f a
defaulting a f = I.fromMaybe a >$< optionalI f
manyI :: MonoidalAlt f => f a -> f [a]
manyI f = I.cons >$< optionalI (f >*< manyI f)
msumIndex :: MonoidalAlt f => [f ()] -> f Int
msumIndex [] = error "msumIndex: empty list"
msumIndex [x] = ( (\() -> 0) :<->: which) >$< x where
which i = case compare i 0 of
LT -> error "msumIndex: negative index"
EQ -> ()
GT -> error "msumIndex: index too large"
msumIndex (x:l) = (either (\() -> 0) succ :<->: which) >$< (x >|< msumIndex l) where
which i = case compare i 0 of
LT -> error "msumIndex: negative index"
EQ -> Left ()
GT -> Right (pred i)
msumFirst, msumLast :: (MonoidalAlt f, Traversable t) => t (f a) -> f a
msumFirst = foldr1 (>|)
msumLast = foldl1 (|<)
oneOfI :: (MonoidalAlt f, Eq a) => (a -> f ()) -> [a] -> f a
oneOfI _ [] = error "oneOfI: empty list"
oneOfI f [x] = ((\() -> x) I.:<->: (\y -> if x == y then () else error "oneOfI: invalid option")) >$< f x
oneOfI f (x:l) = (I.fromMaybe x I.. I.rgt) >$< (f x >|< oneOfI f l)
instance Monoidal (Bijection (->) ()) where
unit = I.id
(ua :<->: au) >*< (ub :<->: bu) = ua &&& ub :<->: uncurry mappend . (au *** bu)