
Might have not been clear, but i will try illustrate . f:: a-> b -> c -> (b,(c,a)) f1 :: c -> a -> d input type: A B C ---------- | f | | _____ | output (B,(C,A)) C A ---------- | f1 | | _____ | output D If i want compose f and f1, i need to do a correct input to f1 from the output of f. So i want one function to convert the output of "f" to input off "f!". In this case, we do f1 fst (snd (t,(t1,t2))) snd (snd (t,(t1,t2))) But i want do this automaticaly, for type of any two function. I search for the "glue". I don't have any concern about what the function does, i only have interess on input and output types. Cheers, André No dia 9 de Outubro de 2010 22:38, André Batista Martins < andre_bm@netcabo.pt> escreveu:
Hello, exists any algorithm to determine how terms can be changed to safisty the type of one function?
example:
f:: a-> b -> c -> (b,c,a)
f1 :: c -> a -> d
In my first function "f" i want assign the output "c" and "a" for to input of function "f1". I searched for any solution, but i didn't find any anything.
One clue i have found is "minimal edit distance algorithm" for 2 strings. Perhaps if i convert de output type of "f" to one string, and de input of "f1" to another string and then use this algorithm , i will get one "dirty" solution...
I'm open to any sugestion.

On Oct 9, 2010, at 4:17 PM, André Batista Martins wrote:
If i want compose f and f1, i need to do a correct input to f1 from the output of f. So i want one function to convert the output of "f" to input off "f!". In this case, we do f1 fst (snd (t,(t1,t2))) snd (snd (t, (t1,t2))) But i want do this automaticaly, for type of any two function. I search for the "glue".
You have to write the glue. There is no way to do it automatically, for all cases. If there was a way to derive the glue, they wouldn't be separate cases. Type classes are a common approach for writing glue functions. The Functor and Monad type classes are good examples. (And there is a nice algebra of functors in the small category of functors, too) I wrote a weird little functorial type class yesterday, specifically to handle newtypes as functors over their underlying datatype/category. class Transform obj functor where transform :: (obj -> obj) -> functor -> functor instance Functor f => Transform obj (f obj) where transform = fmap

2010/10/9 André Batista Martins
Might have not been clear, but i will try illustrate .
f:: a-> b -> c -> (b,(c,a)) f1 :: c -> a -> d
-----------------------------
I think I would attack this with glue consisting of:
comb f f1 a b c = arr (\(a,b,c) -> f a b c) >>> arr (\(b,(c,a))) ->f1 c a) $ (a,b,c) and yes, have to agree that easier to roll your own if only a few functions are like this.. but should be able to parse the type signatures of the functions involved and write a program to automate this process.. using this format as a template.. Actually if you just set it to take all the variables prior to last (->) in sig you can put them put them together in an uncurried format.. for instance the "a -> b -> c" portion would become always \(a,b,c) -> then the function so arr (\(a,b,c) -> f a b c) then the term (output) would be the last term in this case (b,(c,a) add that with a "->" between to give that to first part of another lambda construction (\(c,a) -> f1 c a) ... arrowizing the whole thing with arr (first lambda) >>> arr (second lambda) $ and a tuple from all but the last variables in all cases of first function ... so for f it would be (a,b,c). if for some odd reason it was a single it would just become ((a)) an added parenthesis, which would not hurt a thing for the case where it was a sig like f :: a -> b So for your case it becomes as shown above: comb f f1 a b c = arr (\(a,b,c) -> f a b c) >>> arr (\(b,(c,a))) ->f1 c a) $ (a,b,c) and say for: f :: a -> (b,c) f1:: b -> d (\(a) -> f a) >>> (\(b,c) -> f1 b) $ (a) <- it just harmlessly adds the '( ' and ')' around the 'a' even though it doesn't need it as the only parameter prior to the last '->'. This is probably clear as mud, on first look, but I think a way forward in automating from this is possible.. I am sure of it.. but it would be at the source code level and a string parse and output from that .. cheers, gene

I thanks for the answers.
On this paper, i found this example
"The student has accidental given the arguments of map in the wrong
order. Again, the logged student programs show that this is indeed
a common mistake.
(1,8): Type error in application
expression : map [1 .. 10] even
term : map
type : (a -> b) -> [a] -> [b]
does not match : [Int] -> (Int -> Bool) -> c
probable fix : re-order arguments
"
The solution i think was in reordering of function arguments and the
elements of a tuple, and the insertion or removal of function arguments.
In general, this problem appears also in sequence of functions. So if we do
the bridge between the functions, and that bridge was one function to
re-order the elements of output to the correct input of next function.
I think that work has been done, in helium compiler. But i can't identify
the algorithm for this propose.
How i can find the type of one function that i was done, on code, not on
compiler?
Cheers,
André
No dia 10 de Outubro de 2010 07:58, Gene A
2010/10/9 André Batista Martins
Said: Might have not been clear, but i will try illustrate .
f:: a-> b -> c -> (b,(c,a)) f1 :: c -> a -> d
-----------------------------
I think I would attack this with glue consisting of:
comb f f1 a b c = arr (\(a,b,c) -> f a b c) >>> arr (\(b,(c,a))) ->f1 c a) $ (a,b,c)
and yes, have to agree that easier to roll your own if only a few functions are like this.. but should be able to parse the type signatures of the functions involved and write a program to automate this process.. using this format as a template..
Actually if you just set it to take all the variables prior to last (->) in sig you can put them put them together in an uncurried format.. for instance the "a -> b -> c" portion would become always \(a,b,c) -> then the function so arr (\(a,b,c) -> f a b c) then the term (output) would be the last term in this case (b,(c,a) add that with a "->" between to give that to first part of another lambda construction (\(c,a) -> f1 c a) ... arrowizing the whole thing with arr (first lambda) >>> arr (second lambda) $ and a tuple from all but the last variables in all cases of first function ... so for f it would be (a,b,c). if for some odd reason it was a single it would just become ((a)) an added parenthesis, which would not hurt a thing for the case where it was a sig like f :: a -> b
So for your case it becomes as shown above: comb f f1 a b c = arr (\(a,b,c) -> f a b c) >>> arr (\(b,(c,a))) ->f1 c a) $ (a,b,c) and say for:
f :: a -> (b,c) f1:: b -> d
(\(a) -> f a) >>> (\(b,c) -> f1 b) $ (a) <- it just harmlessly adds the '( ' and ')' around the 'a' even though it doesn't need it as the only parameter prior to the last '->'.
This is probably clear as mud, on first look, but I think a way forward in automating from this is possible.. I am sure of it.. but it would be at the source code level and a string parse and output from that ..
cheers, gene

Sorry, i don't refer the paper on other email. But the paper was "Helium, for Learning Haskell" No dia 10 de Outubro de 2010 12:22, André Batista Martins < andre_bm@netcabo.pt> escreveu:
I thanks for the answers. On this paper, i found this example "The student has accidental given the arguments of map in the wrong order. Again, the logged student programs show that this is indeed a common mistake. (1,8): Type error in application expression : map [1 .. 10] even term : map type : (a -> b) -> [a] -> [b] does not match : [Int] -> (Int -> Bool) -> c probable fix : re-order arguments " The solution i think was in reordering of function arguments and the elements of a tuple, and the insertion or removal of function arguments.
In general, this problem appears also in sequence of functions. So if we do the bridge between the functions, and that bridge was one function to re-order the elements of output to the correct input of next function.
I think that work has been done, in helium compiler. But i can't identify the algorithm for this propose.
How i can find the type of one function that i was done, on code, not on compiler?
Cheers, André
No dia 10 de Outubro de 2010 07:58, Gene A
escreveu: 2010/10/9 André Batista Martins
Said: Might have not been clear, but i will try illustrate .
f:: a-> b -> c -> (b,(c,a)) f1 :: c -> a -> d
-----------------------------
I think I would attack this with glue consisting of:
comb f f1 a b c = arr (\(a,b,c) -> f a b c) >>> arr (\(b,(c,a))) ->f1 c a) $ (a,b,c)
and yes, have to agree that easier to roll your own if only a few functions are like this.. but should be able to parse the type signatures of the functions involved and write a program to automate this process.. using this format as a template..
Actually if you just set it to take all the variables prior to last (->) in sig you can put them put them together in an uncurried format.. for instance the "a -> b -> c" portion would become always \(a,b,c) -> then the function so arr (\(a,b,c) -> f a b c) then the term (output) would be the last term in this case (b,(c,a) add that with a "->" between to give that to first part of another lambda construction (\(c,a) -> f1 c a) ... arrowizing the whole thing with arr (first lambda) >>> arr (second lambda) $ and a tuple from all but the last variables in all cases of first function ... so for f it would be (a,b,c). if for some odd reason it was a single it would just become ((a)) an added parenthesis, which would not hurt a thing for the case where it was a sig like f :: a -> b
So for your case it becomes as shown above: comb f f1 a b c = arr (\(a,b,c) -> f a b c) >>> arr (\(b,(c,a))) ->f1 c a) $ (a,b,c) and say for:
f :: a -> (b,c) f1:: b -> d
(\(a) -> f a) >>> (\(b,c) -> f1 b) $ (a) <- it just harmlessly adds the '( ' and ')' around the 'a' even though it doesn't need it as the only parameter prior to the last '->'.
This is probably clear as mud, on first look, but I think a way forward in automating from this is possible.. I am sure of it.. but it would be at the source code level and a string parse and output from that ..
cheers, gene

2010/10/10 André Batista Martins
I think that work has been done, in helium compiler. But i can't identify the algorithm for this propose.
It may be a "hand written" hint that generates the very precise help "probable fix : re-order arguments". See the paper "Scripting the Type Inference Process" Bastiaan Heeren, Jurriaan Hage, S. Doaitse Swierstra. S. Doaitse Swierstra often contributes to this list, though in the case that he misses this thread you might want to ask him directly about it.

"The student has accidental given the arguments of map in the wrong order"
I am using "for = flip map" a lot, in code like for [ 1 .. 10 ] $ \ i -> ... in fact that's one of my "most dearly missed" Prelude functions. Note that we have Control.Monad.forM forM [ 1 .. 10 ] $ \ i -> do ... Oh, and while we're at it - are there standard notations for "forward" function composition and application? I mean instead of h . g . f $ x I'd sometimes prefer x ? f ? g ? h but what are the "?" J.W.

On Sun, Oct 10, 2010 at 6:32 PM, Johannes Waldmann
Oh, and while we're at it - are there standard notations for "forward" function composition and application?
I mean instead of h . g . f $ x I'd sometimes prefer x ? f ? g ? h but what are the "?"
import Control.Arrow something = f >>> g >>> h $ x -- Felipe.

On 10 October 2010 22:32, Johannes Waldmann
Oh, and while we're at it - are there standard notations for "forward" function composition and application?
I mean instead of h . g . f $ x I'd sometimes prefer x ? f ? g ? h but what are the "?"
While asking you use the same symbol for function composition, and something like inverse function application. I don't think there exists an operator ?, such that h . g . f $ x is equivalent to x ? f ? g ? h. But you can simply define an inverse function application like the following and have a close enough alternative, ($$) :: a -> (a -> b) -> b ($$) = flip ($) infixl 5 $$ Now the following two expression are identical, I suppose: h . g . f $ x x $$ f . g . h Cheers, Ozgur

No, wrong. I am speaking nonsense here.
Of course one also needs to define a *forward* function composition operator
to get the effect you originally wanted.
My point was: you need to find/define two operators, not just one. That
still holds :)
Best,
On 10 October 2010 23:47, Ozgur Akgun
On 10 October 2010 22:32, Johannes Waldmann
wrote: Oh, and while we're at it - are there standard notations for "forward" function composition and application?
I mean instead of h . g . f $ x I'd sometimes prefer x ? f ? g ? h but what are the "?"
While asking you use the same symbol for function composition, and something like inverse function application. I don't think there exists an operator ?, such that h . g . f $ x is equivalent to x ? f ? g ? h.
But you can simply define an inverse function application like the following and have a close enough alternative,
($$) :: a -> (a -> b) -> b ($$) = flip ($) infixl 5 $$
Now the following two expression are identical, I suppose:
h . g . f $ x x $$ f . g . h
Cheers, Ozgur
-- Ozgur Akgun

On 10/10/10 7:00 PM, Johannes Waldmann wrote:
My point was: you need to find/define two operators, not just one.
Sure, I need flip ($) and flip (.)
Since the Prelude forgot to define these (and flip map), the question was: are there established names for these two operators?
I don't know how established it is, but ($>) is a common name for flip($). Common, as in, I've seen three or so different people use it. IIRC, the F# name is (|>) but triangles are far too nice of a name and are often used for other things (e.g., cons and snoc). For what it's worth, this is the T combinator--- in case thrushes give you any ideas for names. Personally I'm more likely to use T as a prefix combinator rather than as infix, and for that the ($ _) section is good enough for me. As for flip(.) we have (>>>) in Control.Arrow. -- Live well, ~wren

On 11 October 2010 00:00, Johannes Waldmann
My point was: you need to find/define two operators, not just one.
Sure, I need flip ($) and flip (.)
Since the Prelude forgot to define these (and flip map), the question was: are there established names for these two operators?
(#) was quite "established" for flip ($) around 2000 - its in a couple of papers that appeared at the PADL conferences - one written by Erik Meijer, Daan Leijen and (I think) James Hook on scripting Microsoft Agents with COM. The authors noted reverse application with (#) gave code a nice OO-like reading. The other was Peter Thiemann's Wash - (#) is again flip ($) and (##) is flipped compose. Typographically I think these are a good fit, unfortunately they now might play badly with GHC's magic hash operator. Best wishes Stephen

Stephen Tetley schrieb:
On 11 October 2010 00:00, Johannes Waldmann
wrote: My point was: you need to find/define two operators, not just one. Sure, I need flip ($) and flip (.)
Since the Prelude forgot to define these (and flip map), the question was: are there established names for these two operators?
(#) was quite "established" for flip ($) around 2000 - its in a couple of papers that appeared at the PADL conferences - one written by Erik Meijer, Daan Leijen and (I think) James Hook on scripting Microsoft Agents with COM. The authors noted reverse application with (#) gave code a nice OO-like reading.
The other was Peter Thiemann's Wash - (#) is again flip ($) and (##) is flipped compose.
also in Functional Metapost.

On Mon, Oct 11, 2010 at 00:51, Ozgur Akgun
My point was: you need to find/define two operators, not just one. That still holds :)
No it doesn't. f $ g $ h $ x == f (g (h x)) == f . g . h $ x == x $$ h $$ g $$ f if you have the correct associativity for ($$) --Max

On Sun, Oct 10, 2010 at 4:47 PM, Ozgur Akgun
On 10 October 2010 22:32, Johannes Waldmann
wrote: Oh, and while we're at it - are there standard notations for "forward" function composition and application?
I mean instead of h . g . f $ x I'd sometimes prefer x ? f ? g ? h but what are the "?"
While asking you use the same symbol for function composition, and something like inverse function application. I don't think there exists an operator ?, such that h . g . f $ x is equivalent to x ? f ? g ? h.
infixl 9 ? x ? f = f x h . g . f $ x = h (g (f x)) = h (g (x ? f)) = h (x ? f ? g) = x ? f ? g ? h Luke

On Sunday 10 October 2010 5:32:16 pm Johannes Waldmann wrote:
I mean instead of h . g . f $ x I'd sometimes prefer x ? f ? g ? h but what are the "?"
Note, before anyone gets too excited about this, there are some built-in things about the language that make forward chaining less nice. For instance: (f $ \x -> ...) /= (\x -> ... ? f) (f $ do ...) /= (do ... ? f) You need to add parentheses for the right sides, which defeats at least part of the point of ($). The second is even incompatible in two ways, because left-to-right impredicative instantiation seems to be back in GHC 7, and so: runST $ do ... will work, while (do ...) ? runST will be a type error, assuming it's just flip ($) with the usual type. -- Dan

Dan Doel schrieb:
On Sunday 10 October 2010 5:32:16 pm Johannes Waldmann wrote:
I mean instead of h . g . f $ x I'd sometimes prefer x ? f ? g ? h but what are the "?"
Note, before anyone gets too excited about this, there are some built-in things about the language that make forward chaining less nice. For instance:
(f $ \x -> ...) /= (\x -> ... ? f) (f $ do ...) /= (do ... ? f)

djinn[1] can derive some glue functions for you. you tell it something like
glue :: (x -> y -> z -> (b,(c,a)) -> (c -> a -> d) -> x -> y -> z -> d and it tells you something like glue f g x y z = let (b,(c,a)) = f x y z in g c a I changed the type of f slightly to avoid the trivial answer glue _ g a _ c = g c a
[1] http://hackage.haskell.org/package/djinn
2010/10/9 André Batista Martins
Might have not been clear, but i will try illustrate .
f:: a-> b -> c -> (b,(c,a))
f1 :: c -> a -> d
input type: A B C ---------- | f | | _____ |
output (B,(C,A))
C A ---------- | f1 | | _____ |
output D
If i want compose f and f1, i need to do a correct input to f1 from the output of f. So i want one function to convert the output of "f" to input off "f!". In this case, we do f1 fst (snd (t,(t1,t2))) snd (snd (t,(t1,t2))) But i want do this automaticaly, for type of any two function. I search for the "glue".
I don't have any concern about what the function does, i only have interess on input and output types.
Cheers, André
No dia 9 de Outubro de 2010 22:38, André Batista Martins
escreveu: Hello, exists any algorithm to determine how terms can be changed to safisty the type of one function?
example:
f:: a-> b -> c -> (b,c,a)
f1 :: c -> a -> d
In my first function "f" i want assign the output "c" and "a" for to input of function "f1". I searched for any solution, but i didn't find any anything.
One clue i have found is "minimal edit distance algorithm" for 2 strings. Perhaps if i convert de output type of "f" to one string, and de input of "f1" to another string and then use this algorithm , i will get one "dirty" solution...
I'm open to any sugestion.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (13)
-
Alexander Solla
-
André Batista Martins
-
Dan Doel
-
Felipe Lessa
-
Gene A
-
Henning Thielemann
-
Johannes Waldmann
-
Luke Palmer
-
Max Rabkin
-
Ozgur Akgun
-
Ryan Ingram
-
Stephen Tetley
-
wren ng thornton