Why does this work - haskell mysteries?

Petter Egesund pegesund at online.no
Sun Oct 5 12:02:37 EDT 2003


Hi & thanks for answering.

I think I got it - the chaning of the functions lies in the last part of

 (\w -> if v==w then n else sto w)

I am used to higher ordered functions from Scheme, but it was the delayed 
evaluation which played me the trick here. This function is built when 
updating, and not executed before asking value 'x'?!

So then I go on to the next chap. in the tutorial :-)

Cheers,

PE




On Friday 03 October 2003 23:31, you wrote:
> This seems to me like one of those frustrating problems... if you are
> comfortable with the language then why it works is "obvious", but it's
> difficult to explain why it's obvious.  (My mathematical analysis lecturer
> often used to say "if it's obvious then either it's an assumption or it can
> be proven in 3 lines".)
>
> Suppose you have a function -- any function, and I don't care how it's
> implemented -- that maps a Char to an Int, and let's call it InitStore.
>
> So, maybe we have
>
>    initStore 'a'   ==   4
>    initStore 'b'   ==   5
>
> Now, consider what happens if I define:
>
>    myStore :: Char -> Int
>    myStore 'a' = 3
>    myStore x   = initStore x
>
> then:
>
>    myStore 'a'   ==   3
>    myStore 'b'   ==   5
>
> Now suppose that 'initStore' is implemented in a fashion similar to
> 'myStore' ... and I think you start to get an idea about why it works.
>
> I suspect that any difficulty with this is not being entirely used to the
> idea that a function is a datum pretty much like any other datum.  So
> functions that return results based on some other function value value may
> be less familiar than functions that return a value based on a given list?
>
> Another comment:  trying to figure how it all works in memory is probably
> not helping.  Returning to the 'myStore' example above: is there any doubt
> that it  works as claimed?  Maybe it's only when you try to figure out how
> it works operationally that you get confused ... but to understand that I
> think one needs an appreciation of how functional languages are actually
> *implemented*.  When programming in a conventional language like C, one is
> quite prepared to accept the operational behaviour as described, but if you
> try to understand how that works when mapped onto a modern
> performance-optimized hardware architecture, I think it's easily as
> difficult to follow as functional language implementation.
>
> I've no idea if anything here is remotely helpful.
>
> #g
> --
>
> At 23:48 04/10/03 +0000, Petter Egesund wrote:
> >Hi;
> >
> >the proof of the pudding does lies in the eating... but I still wonder why
> >this code is working (it is taken from the book "The Craft of functional
> >programming").
> >
> >The program connects a variable-name to value. The fun initial gives the
> >initial state, update sets a variable & value reads a value).
> >
> >I evaluate
> >
> >                         value my_store 'b' to 5
> >    and                  value my_store 'a' to 3
> >
> >as expected from the text in the book.
> >
> >But I can't see what is happening here. The book has a parallel example
> > where the data is held in a list, and this version is easy to follow, but
> > this trick with storing a lambda-function inside a newtype beats me.
> >
> >The problem is that I do not understand where the accumulated data is
> > stored (not in a list - it seems like something like a chain of functions
> > which can be pattern-matched, but I am not sure).
> >
> >And why does not the lambda-function (\w -> if v==w then n else sto w)
> >start a
> >endless loop?
> >
> >(This is not homework - I am a programmer who is curious about Haskell!)
> >
> >Any clues, anyone?
> >
> >
> >Cheers,
> >
> >Petter
> >
> >
> >-- Var is the type of variables.
> >
> >type Var = Char
> >
> >newtype Store = Sto (Var -> Int)
> >--
> >initial :: Store
> >
> >initial = Sto (\v -> 0)
> >
> >value :: Store -> Var -> Int
> >
> >value (Sto sto) v = sto v
> >
> >update  :: Store -> Var -> Int -> Store
> >
> >update (Sto sto) v n
> >   = Sto (\w -> if v==w then n else sto w)
> >
> >-- testit --
> >
> >my_store = update (update (update initial 'a' 4) 'b' 5) 'a' 3)
> >
> >
> >
> >_______________________________________________
> >Haskell-Cafe mailing list
> >Haskell-Cafe at haskell.org
> >http://www.haskell.org/mailman/listinfo/haskell-cafe
>
> ------------
> Graham Klyne
> GK at NineByNine.org



More information about the Haskell-Cafe mailing list