-- | -- Module : Data.OI.Combinator -- Copyright : (c) Nobuo Yamashita 2011-2012 -- License : BSD3 -- Author : Nobuo Yamashita -- Maintainer : nobsun@sampou.org -- Stability : experimental -- {-# LANGUAGE TypeOperators ,BangPatterns #-} module Data.OI.Combinator ( -- * Utility functions (|>) ,choice -- * Interaction Combinators ,(|:|) ,(|>|),(|/|) ,(|><|) -- * Iteration ,mapOI ,zipWithOI ,zipWithOI' -- * Conditional Choice ,ifOI ,choiceOI -- * Sequencing ,seqsOI ,seqsOI' ) where import Data.OI.Base (|>) :: (a -> b) -> (b -> c) -> (a -> c) (|>) = flip (.) choice :: a -> a -> Bool -> a choice t f c = if c then t else f -- | Connect two interactions into an interaction infixl 3 |:| infixl 2 |>|,|/| infixl 1 |><| (|:|) :: (a :-> c) -> (b :-> d) -> ((a,b) :-> (c,d)) (f |:| g) o = case dePair o of (a,b) -> (f a, g b) (|>|) :: (a :-> (p,c)) -> (b :-> (p -> d)) -> ((a,b) :-> (c,d)) (f |>| g) o = case dePair o of (a,b) -> (c, g b p) where (p,c) = f a (|/|) :: (a :-> c) -> (c -> (b :-> d)) -> ((a,b) :-> d) (f |/| g) o = case dePair o of (a,b) -> g (f a) b (|><|) :: (a :-> (p -> (q,c))) -> (b :-> (q -> (p,d))) -> ((a,b) :-> (c,d)) (f |><| g) o = case dePair o of (a,b) -> (c,d) where (q,c) = f a p; (p,d) = g b q -- | Iteration mapOI :: (a :-> b) -> ([a] :-> [b]) mapOI f os = case deList os of Just (x,xs) -> f x : mapOI f xs _ -> [] zipWithOI :: (a :-> (b -> c)) -> ([a] :-> ([b] -> [c])) zipWithOI _ _ [] = [] zipWithOI f os (b:bs) = case deList os of Just (x,xs) -> f x b : zipWithOI f xs bs _ -> [] zipWithOI' :: (a -> (b :-> c)) -> ([a] -> ([b] :-> [c])) zipWithOI' = flip . zipWithOI . flip -- | Conditional branching ifOI :: Bool -> (a :-> c) -> (b :-> c) -> (Either a b :-> c) ifOI True t _ o = case deLeft o of Left x -> t x _ -> error "ifOI: Left expected but Right" ifOI False _ e o = case deRight o of Right y -> e y _ -> error "ifOI: Right expected but Left" choiceOI :: (a :-> c) -> (b :-> c) -> Bool -> (Either a b :-> c) choiceOI = flip . flip ifOI -- | Sequencing seqsOI :: [a] :-> ([a :-> b] -> ()) seqsOI os is = case dropWhile (()==) $ map force $ zipWithOI (flip id) os is of [] -> () _ -> error "seqsOI: Impossible!" seqsOI' :: [a :-> b] -> ([a] :-> ()) seqsOI' = flip seqsOI