Re[Haskell-cafe] cursive referencing
 
            Hello! I'm puzzled, if in Haskell it's possible to create a (pure) data structure, consisting of 2 substructures referencing each other: ------------------------- data AA = AA { someData1 :: SomeData1 bb :: BB } data BB = BB { someData2 :: SomeData2 aa :: AA } f :: SomeData1 -> SomeData2 -> AA f somedata1 somedata2 = ?????????? -- Always True: ghci> f == aa $ bb f True ------------------------- Any ideas? Belka -- View this message in context: http://www.nabble.com/Recursive-referencing-tp21722002p21722002.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
 
            Yes.
f somedata1 somedata2 = aa
  where aa = AA somedata1 bb
            bb = BB somedata2 aa
2009/1/29 Belka 
Hello! I'm puzzled, if in Haskell it's possible to create a (pure) data structure, consisting of 2 substructures referencing each other: ------------------------- data AA = AA { someData1 :: SomeData1 bb :: BB }
data BB = BB { someData2 :: SomeData2 aa :: AA }
f :: SomeData1 -> SomeData2 -> AA f somedata1 somedata2 = ??????????
-- Always True: ghci> f == aa $ bb f True ------------------------- Any ideas?
Belka -- View this message in context: http://www.nabble.com/Recursive-referencing-tp21722002p21722002.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Евгений Кирпичев Разработчик Яндекс.Маркета
 
            Yes. f somedata1 somedata2 = aa where aa = AA somedata1 bb bb = BB somedata2 aa
Spasibo, Yevgeny! Originally I was thinking theoretically about a single plain lambda-expression, like (\ somedata1 somedata2 -> (\ aa bb -> aa (bb aa)) (\ b -> AA somedata1 b) (\ a -> BB somedata2 a) ) But in the code "aa (bb aa)" last aa stays lacking an argument, of course, if we don't consider 1st application "aa (" as having a side effect on aa. And that's where "separate and rule" shows up it's power (speaking about "where" and namespacing in general). =) Belka -- View this message in context: http://www.nabble.com/Recursive-referencing-tp21722002p21722503.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
 
            Пожалуйста :)
It's difficult to do this in lambda because it isn't expressible in
simply (or even polymorphically) typed lambda calculus, since it
requires the Y (fix) combinator, which introduces non-terminating
computations, whereas simply- and polymorphically-typed lambda
calcules are strongly normalizing (all computations terminate).
So, you can't write *simple and intuitive* typed code for this in lambda.
To express it, you either need untyped lambda or Haskell, where the
'fix' combinator is typed by kind of a hack :)
With the Y combinator, the code becomes as follows:
f = \somedata1 somedata2 -> fst $ fix (\(aa,bb) -> (AA somedata1 bb,
BB somedata2 aa))
I tried to prove to myself that the structure really turns out cyclic,
but games with reallyUnsafePtrEquality# didn't lead to success; that's
why it's "reallyUnsafe" :-/
2009/1/29 Belka 
Yes. f somedata1 somedata2 = aa where aa = AA somedata1 bb bb = BB somedata2 aa
Spasibo, Yevgeny!
Originally I was thinking theoretically about a single plain lambda-expression, like (\ somedata1 somedata2 -> (\ aa bb -> aa (bb aa)) (\ b -> AA somedata1 b) (\ a -> BB somedata2 a) ) But in the code "aa (bb aa)" last aa stays lacking an argument, of course, if we don't consider 1st application "aa (" as having a side effect on aa. And that's where "separate and rule" shows up it's power (speaking about "where" and namespacing in general). =)
Belka -- View this message in context: http://www.nabble.com/Recursive-referencing-tp21722002p21722503.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Евгений Кирпичев Разработчик Яндекс.Маркета
 
            On Thu, Jan 29, 2009 at 12:44 AM, Eugene Kirpichov 
With the Y combinator, the code becomes as follows:
f = \somedata1 somedata2 -> fst $ fix (\(aa,bb) -> (AA somedata1 bb, BB somedata2 aa))
I tried to prove to myself that the structure really turns out cyclic, but games with reallyUnsafePtrEquality# didn't lead to success; that's why it's "reallyUnsafe" :-/
Your definition with "fix" isn't lazy enough, so it goes into an infinite loop. You need to match lazily on the pair; here's a better body for "fix": fix (\p -> (AA somedata1 $ snd p, BB somedata2 $ fst p)) To prove that the structure really turns out cyclic, you can use Debug.Trace: import Debug.Trace (trace) import Data.Function (fix) data AA = AA Int BB deriving Show data BB = BB Int AA deriving Show f = \data1 data2 -> fst $ fix $ \p -> (trace "eval_aa" $ AA data1 $ snd p, trace "eval_bb" $ BB data2 $ fst p) sumAA 0 _ = 0 sumAA n (AA v bb) = trace "sumAA" (v + sumBB (n-1) bb) sumBB 0 _ = 0 sumBB n (BB v aa) = trace "sumBB" (v + sumAA (n-1) aa) main = print $ sumAA 10 $ f 1 2 *Main> main eval_aa sumAA eval_bb sumBB sumAA sumBB sumAA sumBB sumAA sumBB sumAA sumBB 15 -- ryan
 
            Thanks, that clarifies things a lot; I must improve my laziness-fu!
(to Belka: Also, lazy matching may be performed as .... fix
(\(~(aa,bb)) -> ...) - the tilde does the trick)
2009/1/29 Ryan Ingram 
On Thu, Jan 29, 2009 at 12:44 AM, Eugene Kirpichov
wrote: With the Y combinator, the code becomes as follows:
f = \somedata1 somedata2 -> fst $ fix (\(aa,bb) -> (AA somedata1 bb, BB somedata2 aa))
I tried to prove to myself that the structure really turns out cyclic, but games with reallyUnsafePtrEquality# didn't lead to success; that's why it's "reallyUnsafe" :-/
Your definition with "fix" isn't lazy enough, so it goes into an infinite loop. You need to match lazily on the pair; here's a better body for "fix":
fix (\p -> (AA somedata1 $ snd p, BB somedata2 $ fst p))
To prove that the structure really turns out cyclic, you can use Debug.Trace:
import Debug.Trace (trace) import Data.Function (fix)
data AA = AA Int BB deriving Show data BB = BB Int AA deriving Show
f = \data1 data2 -> fst $ fix $ \p -> (trace "eval_aa" $ AA data1 $ snd p, trace "eval_bb" $ BB data2 $ fst p)
sumAA 0 _ = 0 sumAA n (AA v bb) = trace "sumAA" (v + sumBB (n-1) bb) sumBB 0 _ = 0 sumBB n (BB v aa) = trace "sumBB" (v + sumAA (n-1) aa)
main = print $ sumAA 10 $ f 1 2
*Main> main eval_aa sumAA eval_bb sumBB sumAA sumBB sumAA sumBB sumAA sumBB sumAA sumBB 15
-- ryan
 
            Great thanks, Ryan and Yevgeny! 1. For "sumAA 10 $ f 1 2" and for "sumAA 1000 $ f 1 2" - does the used memory amounts differ? 2. Does it create in memory only 2 data objects, or creates 10s and 1000s and garbage collects unneeded? ------ Also consider fix (\p -> (AA somedata1 $ snd p, BB somedata2 $ fst p)) and my mod (added "some_very_expensive_f") fix (\p -> (AA (some_very_expensive_f somedata1) $ snd p, BB (some_very_expensive_f somedata2) $ fst p)) 2. Does the sumAA evaluates this "some_very_expensive_f" every iteration of recursion, or is it evaluated only once? Belka ----------------------------
Your definition with "fix" isn't lazy enough, so it goes into an infinite loop. You need to match lazily on the pair; here's a better body for "fix":
fix (\p -> (AA somedata1 $ snd p, BB somedata2 $ fst p))
To prove that the structure really turns out cyclic, you can use Debug.Trace:
import Debug.Trace (trace) import Data.Function (fix)
data AA = AA Int BB deriving Show data BB = BB Int AA deriving Show
f = \data1 data2 -> fst $ fix $ \p -> (trace "eval_aa" $ AA data1 $ snd p, trace "eval_bb" $ BB data2 $ fst p)
sumAA 0 _ = 0 sumAA n (AA v bb) = trace "sumAA" (v + sumBB (n-1) bb) sumBB 0 _ = 0 sumBB n (BB v aa) = trace "sumBB" (v + sumAA (n-1) aa)
main = print $ sumAA 10 $ f 1 2
*Main> main eval_aa sumAA eval_bb sumBB sumAA sumBB sumAA sumBB sumAA sumBB sumAA sumBB 15 -- View this message in context: http://www.nabble.com/Recursive-referencing-tp21722002p21756221.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
 
            1) yes, but that's sumAA's fault, not the data structure; sumAA isn't
tail recursive so it has to build a much bigger stack:
x + (y + (z + (...)))
whereas it could run in constant space if it did this instead:
(...((x + y) + z) + ...)
Usually this transformation is done by passing an accumulator holding
the "result so far" at each iteration.
2) That was the point of using Debug.Trace in my example.  Notice that
"eval_aa" and "eval_bb" only get printed once; they get output during
the construction of the AA and BB objects during evaluation.  Since
you only see them once, you know that there isn't any further creation
of data; it's really just a circular data structure with pointers back
and forth.
  -- ryan
On Fri, Jan 30, 2009 at 1:48 PM, Belka 
Great thanks, Ryan and Yevgeny!
1. For "sumAA 10 $ f 1 2" and for "sumAA 1000 $ f 1 2" - does the used memory amounts differ? 2. Does it create in memory only 2 data objects, or creates 10s and 1000s and garbage collects unneeded?
------
Also consider fix (\p -> (AA somedata1 $ snd p, BB somedata2 $ fst p)) and my mod (added "some_very_expensive_f") fix (\p -> (AA (some_very_expensive_f somedata1) $ snd p, BB (some_very_expensive_f somedata2) $ fst p))
2. Does the sumAA evaluates this "some_very_expensive_f" every iteration of recursion, or is it evaluated only once?
Belka
----------------------------
Your definition with "fix" isn't lazy enough, so it goes into an infinite loop. You need to match lazily on the pair; here's a better body for "fix":
fix (\p -> (AA somedata1 $ snd p, BB somedata2 $ fst p))
To prove that the structure really turns out cyclic, you can use Debug.Trace:
import Debug.Trace (trace) import Data.Function (fix)
data AA = AA Int BB deriving Show data BB = BB Int AA deriving Show
f = \data1 data2 -> fst $ fix $ \p -> (trace "eval_aa" $ AA data1 $ snd p, trace "eval_bb" $ BB data2 $ fst p)
sumAA 0 _ = 0 sumAA n (AA v bb) = trace "sumAA" (v + sumBB (n-1) bb) sumBB 0 _ = 0 sumBB n (BB v aa) = trace "sumBB" (v + sumAA (n-1) aa)
main = print $ sumAA 10 $ f 1 2
*Main> main eval_aa sumAA eval_bb sumBB sumAA sumBB sumAA sumBB sumAA sumBB sumAA sumBB 15 -- View this message in context: http://www.nabble.com/Recursive-referencing-tp21722002p21756221.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
 
            By the way, more advanced stuff of this kind is called "Tying the
knot"; you can do doubly linked lists with it and much more.
http://www.haskell.org/haskellwiki/Tying_the_Knot
2009/1/29 Belka 
Hello! I'm puzzled, if in Haskell it's possible to create a (pure) data structure, consisting of 2 substructures referencing each other: ------------------------- data AA = AA { someData1 :: SomeData1 bb :: BB }
data BB = BB { someData2 :: SomeData2 aa :: AA }
f :: SomeData1 -> SomeData2 -> AA f somedata1 somedata2 = ??????????
-- Always True: ghci> f == aa $ bb f True ------------------------- Any ideas?
Belka -- View this message in context: http://www.nabble.com/Recursive-referencing-tp21722002p21722002.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Евгений Кирпичев Разработчик Яндекс.Маркета
participants (3)
- 
                 Belka Belka
- 
                 Eugene Kirpichov Eugene Kirpichov
- 
                 Ryan Ingram Ryan Ingram