Re: [Haskell-cafe] Re: Language support for imperative code. Was: Re: monad subexpressions

2007-08-13 Thread Isaac Dupree

Brian Hulley wrote:
Thinking about this a bit more, and just so this thought is recorded for 
posterity (!) and for the benefit of anyone now or in a few hundred 
years time, trying to solve "Fermat's last GUI", the object oriented 
solution allows the buffer object to do anything it wants, so that it 
could negotiate a network connection and implement the interface based 
on a shared network buffer for example, without needing any changes to 
the client code above, so a functional gui would need to have the same 
flexibility to compete with the OO solution.


Probably it would be parametric in the input mechanism, somehow.  (A 
Haskell approach might use type classes, slightly obscuring the 
parametricity..)


Another thing that would be interesting would be to have a formal 
treatment of what is supposed to happen in a gui. For example, when you 
move the mouse over a control which has become dirty (ie needs to be 
re-rendered because its state is now inconsistent), what should the 
control do? Should it respond as if the new state were already visible 
to the user, or should it interpret the mouse position according to the 
last state that was rendered, or should it just ignore all mouse events 
until the next time it gets rendered? This is not a trivial question 
because you could imagine an animated control where the user might 
naturally be following the movement, whereas when the user clicks on a 
cell in a spreadsheet when the cells to the left have now expanded due 
to a change in data thus moving the cell along (but where this updated 
model has not yet been re-rendered) the user might be irritated at the 
wrong cell being selected... It's tricky little issues like this that I 
haven't found any documentation for anywhere, and which would make a 
proper mathematical treatment of interaction with a gui very useful, 
regardless of whether it is implemented in OOP or functional style.


Jef Raskin (late interface designer, author of _The Humane Interface_) 
would probably say that anything with such importance to user decisions, 
should be rendered within a tenth of a second.  Computers fifteen years 
ago could sometimes do it!  Fancy details can be filled in later if it 
takes that long.


Of course that completely dodges the mathematical question... in which 
human response time should really be taken into account too! Humans 
really are not like machines and are not all alike either!  Oh no, do we 
need psychological formalisms?


Firefox suffers the above problems badly, alas - the "Stop" button is 
half useless because it doesn't even noticed you pressed it for such a 
long time, etc...


Reading up on user interface design principles as well as thinking 
functionally, is probably a useful approach - although not everything 
that you read will agree or be right.  The whole concept of GUIs - they 
are very complicated - it is quite arguable that they are just a wrong 
interface - however, some of the world's people are fortunate enough to 
be accustomed to them already, which complicates matters considerably.



Isaac
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Language support for imperative code. Was: Re: monad subexpressions

2007-08-13 Thread Brian Hulley

Brian Hulley wrote:

apfelmus wrote:

Brian Hulley schrieb:

   main = do
   buffer <- createBuffer
   edit1 <- createEdit buffer
   edit2 <- createEdit buffer
   splitter <- createSplitter (wrapWidget edit1) (wrapWidget 
edit2)

   runMessageLoopWith splitter

... Thus the ability to abstract mutable state gives to my mind by 
far the best solution.


I'm not sure whether mutable state is the real goodie here. I think 
it's the ability to indpendently access parts of a compound state.

  http://www.st.cs.ru.nl/papers/2005/eves2005-FFormsIFL04.pdf


This is indeed a real key to the problem.

Of course this is only one aspect of the problem...

Thinking about this a bit more, and just so this thought is recorded for 
posterity (!) and for the benefit of anyone now or in a few hundred 
years time, trying to solve "Fermat's last GUI", the object oriented 
solution allows the buffer object to do anything it wants, so that it 
could negotiate a network connection and implement the interface based 
on a shared network buffer for example, without needing any changes to 
the client code above, so a functional gui would need to have the same 
flexibility to compete with the OO solution.


Another thing that would be interesting would be to have a formal 
treatment of what is supposed to happen in a gui. For example, when you 
move the mouse over a control which has become dirty (ie needs to be 
re-rendered because its state is now inconsistent), what should the 
control do? Should it respond as if the new state were already visible 
to the user, or should it interpret the mouse position according to the 
last state that was rendered, or should it just ignore all mouse events 
until the next time it gets rendered? This is not a trivial question 
because you could imagine an animated control where the user might 
naturally be following the movement, whereas when the user clicks on a 
cell in a spreadsheet when the cells to the left have now expanded due 
to a change in data thus moving the cell along (but where this updated 
model has not yet been re-rendered) the user might be irritated at the 
wrong cell being selected... It's tricky little issues like this that I 
haven't found any documentation for anywhere, and which would make a 
proper mathematical treatment of interaction with a gui very useful, 
regardless of whether it is implemented in OOP or functional style.


Anyway just a thought,

Brian.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Language support for imperative code. Was: Re: monad subexpressions

2007-08-13 Thread apfelmus

Isaac Dupree schrieb:

apfelmus wrote:
Mutable data structures in the sense of ephemeral (= not persistent = 
update in-place) data structure indeed do introduce the need to work 
in ST since the old version is - by definition - not available anymore. 


Not in the quantum/information-theoretic sense, not necessarily. Consider

import Control.Monad.ST
import Data.STRef
main = print (runST (do
   r <- newSTRef 1
   notUnavailable <- readSTRef r
   writeSTRef r 5
   return notUnavailable
 ))


I'm not sure what this has to do with quantum mechanics ;) but you're 
right, I forgot that. This means that either STRefs cannot be updated 
in-place or that every read operation copies the contents or something 
like that.


In any case, simple values like Ints or Bools are rather uninteresting, 
update in-place is only important for larger structures like arrays. 
Here, ST does updates in-place and retaining an array will copy it.


Regards,
apfelmus

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Language support for imperative code. Was: Re: monad subexpressions

2007-08-12 Thread Isaac Dupree

apfelmus wrote:

  (3+) :: Int -> Int
  ([1,2]++):: [Int] -> [Int]
  insert "x" 3 :: Map String Int -> Map String Int

Of course, from the purely functional point of view, this is hardly
perceived as mutation since the original value is not changed at all and
still available. In other words, the need to "change" a value doesn't
imply the need to discard (and thus mutate) the old one.


Yes, and pure functions in Haskell often get funny imperative-sounding 
names like "insert" because of it - which is quite nice IMO.  I like 
perceiving it like mutation because 99% of the time these are used in 
the places that mutation normally needs to be used in imperative 
languages.  It is only occasionally that destructive mutation (for lack 
of a better name) is needed - for all I know, those situations may be a 
named "pattern" or something in imperative languages.


type Mutate a = a -> a
--I've also caught myself calling it Mon, Endo, IdF, Change ...
insert :: (Ord k) => k -> v -> Mutate (Map k v)

It's annoying when the arguments are in the wrong order, such as 
Data.Bits.shift. (perhaps for the flimsy excuse that they expected you 
to use it infix...)


Mutable data structures in the sense of ephemeral (= not persistent = 
update in-place) data structure indeed do introduce the need to work in 
ST since the old version is - by definition - not available anymore. 


Not in the quantum/information-theoretic sense, not necessarily. Consider

import Control.Monad.ST
import Data.STRef
main = print (runST (do
   r <- newSTRef 1
   notUnavailable <- readSTRef r
   writeSTRef r 5
   return notUnavailable
 ))

Of course that's something you can do in imperative languages too, but 
it's still easier in Haskell where you don't have to worry about what 
something implicitly refers to, and can pass around anything (any data, 
functions, IO-actions) as first-class citizens :)  (including storing 
them in parametrically-polymorphic state-refs like STRef, and, even for 
non-polymorphic refs, you can get the value out and keep it after the 
mutatable state has changed)


See, the imperative paradigm has trouble scaling down to the quantum 
level, where information cannot be copied at will, too!  This proves why 
computers generate heat(entropy) from the unprincipled destruction of 
information.  Of course, computation near the quantum scale is a subject 
that has not nearly been thoroughly explored yet, but I suspect that 
(purely) functional languages are a little more likely to be easier to 
compile to such a type of machine, some decades from now...



Playfully,

Isaac
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Language support for imperative code. Was: Re: monad subexpressions

2007-08-12 Thread Brian Hulley

apfelmus wrote:

Brian Hulley schrieb:

   main = do
   buffer <- createBuffer
   edit1 <- createEdit buffer
   edit2 <- createEdit buffer
   splitter <- createSplitter (wrapWidget edit1) (wrapWidget 
edit2)

   runMessageLoopWith splitter

... Thus the ability to abstract mutable state gives to my mind by 
far the best solution.


I'm not sure whether mutable state is the real goodie here. I think 
it's the ability to indpendently access parts of a compound state. In 
other words, the IORef created by  buffer  is a part of the total 
program state but you can access it independently. There is a 
functional idiom for that, see also


  Sander Evers, Peter Achten, and Jan Kuper. "A Functional Programming
  Technique for Forms in Graphical User Interfaces".
  http://www.st.cs.ru.nl/papers/2005/eves2005-FFormsIFL04.pdf


Thanks for this reference. This is indeed a real key to the problem. 
(Though a possible downside with compositional references might be 
efficiency as the modified sub-state needs to be injected back into a 
new composite state but perhaps the solution here would be to have 
uniqueness typing as in Clean so that these injections could hopefully 
be erased at compile time.)


I think one of the issues with Haskell is that there are so many 
features to choose from it is difficult to know how to approach a 
problem eg for streams you can have


1) A lazy list
2) A typeclass with get and pushBack methods
3) An object using an existential to wrap (2)
4) A record containing get and pushBack methods
5) A monad with get and pushBack actions
6) A simple function wrapped in a newtype:

 newtype Stream a = Stream (() -> Maybe (a, Stream a))

and I tend to only discover a simple solution like (6) (which works 
equally well for both strict and lazy languages) after spending an 
enormous amount of time on 1,2,3,4,5... ;-)


- For Graphics, I want to build a graphic from smaller ones and then 
draw it. I don't want to know how drawing is implemented and what 
mutable state might be involved.
- For a GUI, I want to write down the data dependencies and a library 
converts this to a mesh of mutable state.


That's what I mean with "higher level functional model".
I agree this would be ideal. A challenge I don't yet know how to solve, 
when dealing with 3d graphics, is that it seems that for efficiency it 
is necessary to consider a mesh of triangles to be an object with 
identity in order to be able to display an updated mesh (eg as the user 
drags a vertex with the mouse) in real time. This is because the 
representation of a mesh is constrained by the low level details of the 
graphics system eg vertices might need to be represented by a contiguous 
array of unboxed positions and normals, and triangles by a contiguous 
array of vertex indices, and it is too expensive to copy these arrays on 
each frame. Perhaps though this is another case where some form of 
uniqueness typing as in Clean could come to the rescue so one could write:


   createMesh :: [Vertex] -> [[VertIndex]] -> Mesh
   moveVertex :: Vertex -> *Mesh -> *Mesh

instead of

   createMesh :: [Vertex] -> [[VertIndex]] -> IO Mesh
   moveVertex :: Vertex -> Mesh -> IO ()

Best regards, Brian.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Language support for imperative code. Was: Re: monad subexpressions

2007-08-11 Thread apfelmus

Brian Hulley schrieb:

apfelmus wrote:

However, most "genuinely imperative" things are often just a building
block for a higher level functional model. The ByteString library is a
good example: the interface is purely functional, the internals are
explicit memory control. It's a bad idea to let the internal memory
control leak out and pollute an otherwise purely functional program with
IO-types.


Regarding the quote above, if the API must hide explicit memory control 
from the user the only way I can see of doing this would be to use 
(unsafePerformIO), which really is unsafe since Haskell relies on the 
fact that mutable operations can't escape from the IO monad in order to 
get away with not having to impose a value restriction as in ML.


Indeed, Data.ByteString makes heavy use of unsafePerformIO and
inlinePerformIO. This is safe since it's just used for efficient memory
access and (de-)allocation, the ByteStrings themselves are immutable.

If you don't use (unsafePerformIO), then the slightest need for mutable 
data structures pollutes the entire interface.


Well, any code that wants to mutate or read this data structure has to
announce so in the type signature. However, it's debatable whether
certain forms of "mutation" count as pollution. In fact, the simplest
"mutation" is just a function  s -> s  . Haskell is throughly "polluted"
by such "mutations":

  (3+) :: Int -> Int
  ([1,2]++):: [Int] -> [Int]
  insert "x" 3 :: Map String Int -> Map String Int

Of course, from the purely functional point of view, this is hardly
perceived as mutation since the original value is not changed at all and
still available. In other words, the need to "change" a value doesn't
imply the need to discard (and thus mutate) the old one.

Mutable data structures in the sense of ephemeral (= not persistent = 
update in-place) data structure indeed do introduce the need to work in 
ST since the old version is - by definition - not available anymore. 
This may be the right thing to do when the data structure is inherently 
used in a single-threaded fashion. However, most used-to-be ephemeral 
data structures have very good persistent counterparts in Haskell. In 
the end, the type just reflects the inherent difficulty of reasoning 
about ephemeral data structures. And that's what the quoted paper 
illustrates: persistent data structures are much easier to deal with.



For example in the excellent paper you quoted

 N. Ramsey and J. Dias.
 An Applicative Control-Flow Graph Based on Huet's Zipper
 http://www.eecs.harvard.edu/~nr/pubs/zipcfg-abstract.html 



the authors are pleased to have found an "Applicative" solution, and 
indeed their solution has many useful and instructive aspects. However 
on page 111, hidden away in the definition of their API function to 
create a label, is a call to (ref 0)  ;-) The equivalent 
implementation in Haskell would completely destroy all hope of using 
this in a pure context and force all use of the API into the IO monad.


I don't know enough ML or have the background to judge whether this  ref 
 is really necessary, but I doubt that it can't be designed away.



Haskell is designed so that any attempt at abstracting mutable

> local state will infect the entire program

Depends on "local". In general, I think is a good thing. The type 
reflects how difficult your program really is, nothing more, nothing 
less. That's how it is: persistent data and prue functions are sooo much 
easier to reason about. Implicit side effects just sweep the difficulty 
under the carpet. (I imagine a tool that makes implicit side effects 
explicitly visible in the types of say C or ML programs. I guess that 
people would scream whole nights when seeing the output of this tool on 
their programs and thus discovering how complicated the code really is 
... Well, maybe not since they're used to it during debugging anyway.)


But if the state is really local, no infection of the entire program 
takes place! The best example is probably indeed the Haskell Graphics 
library. The are pure functions for constructing graphics


  over:: Graphic -> Graphic -> Graphic
  polygon :: [Point] -> Graphic

and some IO-infected functions to draw those onto the screen

  drawInWindow :: Window -> Graphic -> IO ()

Now,  Graphic  may be implemented as an abstract data type and 
drawInWindow  does the workload of interpreting it. Or, and that's how 
HGL currently implementes it, it can be an IO-action that encodes how to 
draw it


  type Graphics = Draw ()
   ~= (Brush,Font,Pen) -> IO ()

That is, every graphic is "infested" with IO but that doesn't spread to 
the API. (It does a bit with  selectBrush  but that can be corrected.)


> (modulo use of a highly dangerous function whose
semantics is entirely unclear, depending on the vagaries of evaluation 
strategy of the particular compiler)


(yes, unsafePerformIO clearly isn't for ep