
I've been playing a simple idea for creating and editing values, and I'd appreciate some feedback on whether or not this idea is well-explored territory. The idea is to construct functions that direct transformations (functions or other arrow-typed values) to the insides of values. This note is a literate Haskell program briefly demonstrating the idea. It runs under hugs and ghc/ghci.
module Path where import Control.Arrow
Consider, for example, a value of type (a->(f,b->(c,g)),e), and Suppose we'd like to apply a function to the c part. We'd want a transformation path
p1 :: (c->c') -> (a->(f,b->(c ,g)),e) -> (a->(f,b->(c',g)),e)
To define p1, simply list the steps taken to get to the type c in the type (a->(f,b->(c,g)),e), as follows:
p1 = first.result.second.result.first
Function arguments may be edited also. In general, the part-changer (of type c->c' in p1) will need to have its domain and range types swapped if it appears in a negative position.
p2 :: (b'->b) -> (d->(a,b)->c) -> (d->(a,b')->c) p2 = result.argument.second
p3a :: (a->a') -> ((a->b)->c) -> ((a'->b)->c) p3a = argument.argument
p3b :: (a->a') -> ((((e,a)->b),d)->c) -> ((((e,a')->b),d)->c) p3b = argument.first.argument.second
The "first" and "second" path components are simply the Arrow methods of those names. As for "result" and "argument", for functions, we can define
result :: (b->b') -> (a->b)->(a->b') argument :: (a'->a) -> (a->b)->(a'->b)
From the types, you can guess the definitions:
result = (.) argument = flip (.)
(BTW, Fritz Ruehr pointed out in his Feb 20 haskell-cafe note that compositions of (.) can be used to "compose a 1-argument function with an n-argument function".) Generalizing to arrows, look at the types of the "first" and "second" Arrow methods:
class Arrow arrow where first :: arrow a a' -> arrow (a, b) (a', b ) second :: arrow b b' -> arrow (a, b) (a', b ) ...
Similarly, define "result" and "argument" as methods of a new class:
class Arrow arrow => ArrowRA arrow where result :: arrow b b' -> arrow (a->b) (a ->b') argument :: arrow a' a -> arrow (a->b) (a'->b )
instance ArrowRA (->) where result = (.) argument = flip (.)
(I've also defined ArrowRA instances for GUI construction and for Haskell code generation.) Here's a suitable second argument for p1:
has1 :: (Bool -> (Bool, String -> (String, Int)), Bool) has1 = (\ a->(not a, \ b->("hello"++b,3)), True)
To see the result, fill in function arguments
x1 :: (Bool -> (f, String -> cg), e) -> ((f, cg), e) x1 = first (second ($" world") . ($True))
and test:
t1a = x1 $ has1 -- ((False,("hello world",3)),True) t1b = x1 $ p1 reverse has1 -- ((False,("dlrow olleh",3)),True) t1c = x1 $ p1 length has1 -- ((False,(11,3)),True)
Here's a suitable second argument for p2:
has2 :: Bool->(String,Int)->Bool has2 b (str,n) = b && length str == n
To see the result, fill in function arguments
x2 :: (Bool->(String,a)->Bool) -> a ->Bool x2 f a = f True ("string",a)
For testing:
t2a = x2 (p2 length has2) "bow" -- False t2b = x2 (p2 ($ "fiddle") has2) length -- True
These transformation paths allow us to apply a function inside of a value. What about applying a function that itself is inside some value. Transformation paths can do this job also, if we combine them with reverse application. In general, both the function and its argument may be buried inside of values. In that case, we might want the function's context to end up on the outside and the argument's context on the inside, or vice versa.
applyF pathF pathX hasF hasX = pathF (\ f -> pathX (\ x -> f x) hasX) hasF
applyX pathF pathX hasF hasX = pathX (\ x -> pathF (\ f -> f x) hasF) hasX
As an example,
hasF1 = ("square", (^2)) hasX1 = (3,"three")
t3a = applyF second first hasF1 hasX1 -- ("square",(9,"three")) t3b = applyX second first hasF1 hasX1 -- (("square",9),"three")
How about some other type constructors, besides (,) and (->)? Try lists.
class Arrow arrow => ArrowL arrow where elementL :: arrow a a' -> arrow [a] [a']
instance ArrowL (->) where elementL = map
Generalizing from [] to any functor:
class Arrow arrow => ArrowF arrow where elementF :: Functor f => arrow a a' -> arrow (f a) (f a')
instance ArrowF (->) where elementF = fmap
The following example combines all four transformation combinators so far:
p4 :: (b'->b) -> (a->Maybe(b,d)->c) -> (a->Maybe(b',d)->c) p4 = result.argument.elementF.first
Comments? - Conal