{- |
Various ways of shuffling input and output components. Function types are mostly autogenerated.
-}
module Control.Arrow.Mix.Utilities where
import Control.Arrow
swap :: (t1, t) -> (t, t1)
swap ~(a, b) = (b, a)
twist :: (t1, (t, t2)) -> (t, (t1, t2))
twist ~(a, (b, c)) = (b, (a, c))
assocLtoR :: ((t, t1), t2) -> (t, (t1, t2))
assocLtoR ~((a, b), c) = (a, (b, c))
assocRtoL :: (t1, (t2, t)) -> ((t1, t2), t)
assocRtoL ~(a, (b, c)) = ((a, b), c)
arrSwap :: Arrow a => a (t, t1) (t2, t3) -> a (t1, t) (t3, t2)
arrSwap a = swap ^>> a >>^ swap
arrTwist
  :: Arrow a =>
     a (t, (t1, t2)) (t4, (t3, t5)) -> a (t1, (t, t2)) (t3, (t4, t5))
arrTwist a = twist ^>> a >>^ twist
pack :: Either (y, c) (y, d) -> (y, Either c d)
pack (Left (y, c)) = (y, Left c)
pack (Right (y, d)) = (y, Right d)
unpack :: (x, Either b d) -> Either (x, b) (x, d)
unpack (x, Left b) = Left (x, b)
unpack (x, Right d) = Right (x, d)
arrAssocLtoR
  :: Arrow a =>
     a ((t1, t2), t) ((t3, t4), t5) -> a (t1, (t2, t)) (t3, (t4, t5))
arrAssocLtoR a = assocRtoL ^>> a >>^ assocLtoR
arrAssocRtoL
  :: Arrow a =>
     a (t, (t1, t2)) (t3, (t4, t5)) -> a ((t, t1), t2) ((t3, t4), t5)
arrAssocRtoL a = assocLtoR ^>> a >>^ assocRtoL
arrCancelUnit :: Arrow a => a (b, ()) (d, ()) -> a b d
arrCancelUnit a = (,()) ^>> a >>^ fst
arrUnpack :: Arrow a => a (Either (x, b) (x, d)) (Either (y, c) (y, d)) -> a (x, Either b d) (y, Either c d)
arrUnpack a = unpack ^>> a >>^ pack
(->>) :: Arrow a => a (i1, input) (o1, middle) -> a (i2, middle) (o2, output) -> a (i2, (i1, input)) (o2, (o1, output))
a1 ->> a2 = second a1 >>> arrTwist (second a2)