module Message where data Message a b = Low a | High b deriving (Message a b -> Message a b -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a forall a b. (Eq a, Eq b) => Message a b -> Message a b -> Bool /= :: Message a b -> Message a b -> Bool $c/= :: forall a b. (Eq a, Eq b) => Message a b -> Message a b -> Bool == :: Message a b -> Message a b -> Bool $c== :: forall a b. (Eq a, Eq b) => Message a b -> Message a b -> Bool Eq, Message a b -> Message a b -> Bool Message a b -> Message a b -> Ordering forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a forall {a} {b}. (Ord a, Ord b) => Eq (Message a b) forall a b. (Ord a, Ord b) => Message a b -> Message a b -> Bool forall a b. (Ord a, Ord b) => Message a b -> Message a b -> Ordering forall a b. (Ord a, Ord b) => Message a b -> Message a b -> Message a b min :: Message a b -> Message a b -> Message a b $cmin :: forall a b. (Ord a, Ord b) => Message a b -> Message a b -> Message a b max :: Message a b -> Message a b -> Message a b $cmax :: forall a b. (Ord a, Ord b) => Message a b -> Message a b -> Message a b >= :: Message a b -> Message a b -> Bool $c>= :: forall a b. (Ord a, Ord b) => Message a b -> Message a b -> Bool > :: Message a b -> Message a b -> Bool $c> :: forall a b. (Ord a, Ord b) => Message a b -> Message a b -> Bool <= :: Message a b -> Message a b -> Bool $c<= :: forall a b. (Ord a, Ord b) => Message a b -> Message a b -> Bool < :: Message a b -> Message a b -> Bool $c< :: forall a b. (Ord a, Ord b) => Message a b -> Message a b -> Bool compare :: Message a b -> Message a b -> Ordering $ccompare :: forall a b. (Ord a, Ord b) => Message a b -> Message a b -> Ordering Ord, Int -> Message a b -> ShowS forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a forall a b. (Show a, Show b) => Int -> Message a b -> ShowS forall a b. (Show a, Show b) => [Message a b] -> ShowS forall a b. (Show a, Show b) => Message a b -> String showList :: [Message a b] -> ShowS $cshowList :: forall a b. (Show a, Show b) => [Message a b] -> ShowS show :: Message a b -> String $cshow :: forall a b. (Show a, Show b) => Message a b -> String showsPrec :: Int -> Message a b -> ShowS $cshowsPrec :: forall a b. (Show a, Show b) => Int -> Message a b -> ShowS Show) isHigh :: Message a b -> Bool isHigh (High b _) = Bool True isHigh Message a b _ = Bool False isLow :: Message a b -> Bool isLow (Low a _) = Bool True isLow Message a b _ = Bool False stripHigh :: Message a a -> Maybe a stripHigh (High a a) = forall a. a -> Maybe a Just a a stripHigh Message a a _ = forall a. Maybe a Nothing stripLow :: Message a b -> Maybe a stripLow (Low a b) = forall a. a -> Maybe a Just a b stripLow Message a b _ = forall a. Maybe a Nothing mapMessage :: (t -> a) -> (t -> b) -> Message t t -> Message a b mapMessage t -> a fl t -> b fh' (Low t l) = forall a b. a -> Message a b Low (t -> a fl t l) mapMessage t -> a fl t -> b fh' (High t h) = forall a b. b -> Message a b High (t -> b fh' t h) message :: (t -> t) -> (t -> t) -> Message t t -> t message t -> t fl t -> t fh (Low t l) = t -> t fl t l message t -> t fl t -> t fh (High t h) = t -> t fh t h aLow :: (t -> a) -> Message t b -> Message a b aLow t -> a f (Low t l) = forall a b. a -> Message a b Low (t -> a f t l) aLow t -> a f (High b h) = forall a b. b -> Message a b High b h aHigh :: (t -> b) -> Message a t -> Message a b aHigh t -> b f (High t h) = forall a b. b -> Message a b High (t -> b f t h) aHigh t -> b f (Low a l) = forall a b. a -> Message a b Low a l pushMsg :: Message (f a) (f a) -> f (Message a a) pushMsg (High f a xs) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap forall a b. b -> Message a b High f a xs pushMsg (Low f a xs) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap forall a b. a -> Message a b Low f a xs instance Functor (Message a) where fmap :: forall a b. (a -> b) -> Message a a -> Message a b fmap = forall {t} {b} {a}. (t -> b) -> Message a t -> Message a b aHigh