[Haskell-cafe] Plain lambda inside banana brackets in the arrow notation

Ross Paterson ross at soi.city.ac.uk
Mon Jul 16 00:30:29 CEST 2012


Silly me -- that code works with the current GHC (module attached).
I still think the generalization is worth doing, though.
-------------------------------------------------------------------------
{-# LANGUAGE Arrows #-}
module ArrowTest where

import Control.Applicative
import Control.Arrow
import Control.Category
import Prelude hiding (id, (.), repeat)

-- copied from Control.Arrow.Transformer.Static (in the arrows package)
newtype StaticArrow f a b c = StaticArrow (f (a b c))

instance (Category a, Applicative f) => Category (StaticArrow f a) where
    id = StaticArrow (pure id)
    StaticArrow f . StaticArrow g = StaticArrow ((.) <$> f <*> g)

instance (Arrow a, Applicative f) => Arrow (StaticArrow f a) where
    arr f = StaticArrow (pure (arr f))
    first (StaticArrow f) = StaticArrow (first <$> f)

newtype MyArr b c = MyArr (b -> c)

instance Category MyArr
instance Arrow MyArr

repeat :: Int -> (Int -> MyArr e a) -> MyArr e a
repeat = undefined

func1 :: [Double] -> Double
func1 = undefined

job1 :: MyArr [Double] Double
job1 = undefined

job3 :: Int -> MyArr Double String
job3 = undefined

repeat' :: Int -> StaticArrow ((->) Int) MyArr e a -> MyArr e a
repeat' n (StaticArrow f) = repeat n f

test2 :: MyArr [Double] String
test2 = proc xs -> do
    let y = func1 xs
    z <- job1 -< xs
    (|(repeat' 100) (do
        i <- StaticArrow (arr . const) -< ()
        StaticArrow (\i -> job3 (i * 2)) -< xs !! i + y + z)|)



More information about the Haskell-Cafe mailing list