
Josef Svenningsson wrote:
On 9/18/07, Benjamin Franksen
wrote: Twan van Laarhoven wrote:
Other functions for which Arrow is often unnecessarily used are first and second
first :: (a -> b) -> (a,c) -> (b,c) first f (x, y) = (f x, y) second :: (a -> b) -> (c,a) -> (c,b) second f (x, y) = (x, f y)
I think these should be added as well. I don't really like these names, but they are the names from Control.Arrow. The problem is that 'fst' and 'first' are essentially the same, but they do different things. Maybe 'mapFst' or 'updateFst' is a better name. 'onFst' and 'onSnd' look nice to me:
onFst (+1) (1,'a') ==> (2,'a')
I omitted first and second from my proposal exactly because I didn't like the names. But onFst and onSnd sounds really nice. I'd be willing to include them in the patch if there is a general agreement about it.
I think I support these as library functions... I've written them myself, but standard names may make them much more comprehensible (I gave up on using them because they were too confusing)... mapFst, setFst::a'->(a,b)->(a',b), and a bunch of Functor and Monad -related ones... never mind, I'll just attach the .lhs file for your amusement. Tuple? Pair? Tuple seems better - then we can have leftAssociativelyPaired :: (a,b,c) -> ((a,b),c) etc if we want
module Tuple where
addFst :: a -> b -> (a,b) addFst a = \b -> (a,b) addSnd :: b -> a -> (a,b) addSnd b = \a -> (a,b)
--"commutePair"?
swapPair :: (a,b) -> (b,a) swapPair = \(a,b) -> (b,a)
associateLeft :: (a,(b,c)) -> ((a,b),c) associateLeft = \(a,(b,c)) -> ((a,b),c) associateRight :: ((a,b),c) -> (a,(b,c)) associateRight = \((a,b),c) -> (a,(b,c))
-- fstIntoSnd :: (a,(b,c)) -> (b,(a,c)) -- fstIntoSnd = mapSnd addFst (fst p) $ snd p -- fstFstToSndFst :: ((annotation,b),c) -> (b,(annotation,c))
type Context = (,) contextFstToSnd :: (Context ctx a, b) -> (a, Context ctx b) contextFstToOut :: (Context ctx a, b) -> Context ctx (a,b) ... or, class Context? (here??) which is no more than tupling? class (Functor c) => Context c where get :: c a -> a -- not even any "return"... transfer :: c a -> b -> c b {- class Pair (p :: * -> * -> *) where pFst :: p a b -> a pSnd :: p a b -> b pMake :: a -> b -> p a b newtype FlippedPair b a = (a,b) -}
mapFst :: (a -> a') -> (a,b) -> (a',b) mapFst f = \(a,b) -> (f a,b) setFst :: a' -> (a,b) -> (a',b) setFst = \a' (a,b) -> (a',b)
changeFst :: ((a,b) -> a') -> (a,b) -> (a',b) changeFst f p@(a,b) = (f p,b)
mapSnd :: (b -> b') -> (a,b) -> (a,b') mapSnd f = \(a,b) -> (a,f b)
runFst :: (Functor m) => ((m a),b) -> m (a,b) runFst = \(ma,b) -> fmap (addSnd b) ma runMapFst :: (Functor m) => (a -> m a') -> (a,b) -> m (a',b) runMapFst f = runFst . mapFst f runChangeFst :: (Functor m) => ((a,b) -> m a') -> (a,b) -> m (a',b) runChangeFst f = runFst . changeFst f
joinByFst :: (Monad m, Functor m) => m ((m a),b) -> m (a,b) joinByFst = (>>= runFst) joinMapFst :: (Monad m, Functor m) => (a -> m a') -> m (a,b) -> m (a',b) joinMapFst f = (>>= runMapFst f) {-= joinByFst . mapFst f-} -- joinChangeFst :: ((a,b) -> m a') -> m (a,b) -> m (a',b) -- joinChangeFst f = (>>= changeFst f) {-runSnd . -- bindByFst :: (Monad m, Functor m) => m (a,b) -> (a -> m a') -> m (a',b) -- bindByFst = flip joinMapFst