[Haskell-cafe] Linking to third party libraries in windows
Brian Hulley
brianh at metamilk.com
Sat May 27 17:06:06 EDT 2006
Matthew Bromberg wrote:
> That's an interesting statement that bears further scrutiny. I've
> been viewing monads as a kind of encapsulation in a quasi-hidden
> world state.
The IO monad can be viewed as encapsulating a function from a
world state to a pair consisting of an updated world state and a "return
value" as follows:
data IO a = IO (RealWorld -> (RealWorld, a))
> Yes a monad is a function that would give you an output
> if you had access to the input world. That is the picture drawn in
> Simon Peyton Jones' tutorial. I've been thinking of actions in terms
> of the functions x -> IO(a), but Simon calls these IO actions and
> calls monads actions as you do.
So the function is contained *inside* the representation of the IO action so
it's IO (x -> (x,a)) not x -> IO a
>
> Is it your claim that whenever an 'IO action' is performed on
> something like IO (x) with x <- newListArray a l
> that the newListArray function will be called ?
If I write:
do
let n = newListArray a l
p <- n
q <- n
two separate arrays will be created, because n is the action of creating a
new array, and this action is executed twice in the body of the do.
However, if I instead wrote:
do
x <- newListArray a l
let r = return x
p <- r
q <- r
only one array would be created, and this would be shared between x, p, and
q, because the action (newListArray a l) is now only executed once (x is the
result of the action ie the array, not the action itself)
> So with the old
> paradigm, where Rmatrix was stored as
> (Int, Int, IO(StorableArry Int CDouble)). A typical matrix operation,
> that calls out to a BLAS C routine cside_effect() looks something
> like this under the old scheme
>
> matfunc A = (u,v, arr) where
> u = f1 (getrows A) (getcols B)
> v = f2 (getrows A) (getcols B)
> arr = do
> arrA <- getarr A
> withStorableArray arrA (\vara -> cside_effect vara )
> return arrA
>
> Now when one uses this code
> do
> A <- getAfromSomewhere
> fA = matfunc A
> B <- anotherfunc A
>
> fA has been changed by the cside_effect function, but A has not! Is
> it your contention that the array in A is essentially copied or
> created anew for every getarr A call?
matfunc A never actually calls getarr A. It just sets up a tuple where the
3rd element is an IO action that, when that 3rd element is actually
executed, would execute the 3rd element of the original A, and pass the
array that was returned by it to your C function, and then return that
array.
I think the essence of the confusion is that there are two kinds of actions
that the 3rd element of A might be bound to:
1) An action which just returns an array that was previously created
2) An action which creates a new array and returns that
And both of these have the same type!!! because all the type system knows is
that these two actions "do something (maybe nothing) then return an array"
Case 2 was what you were doing right at the beginning, when the 3rd element
was (newListArray a l), and case 1 was what I pointed out you could have
used ie using the action (return arr) where arr was allocated during the
construction of Rmatrix.
> I think getarr A looked
> something like
> getarr (Rmatrix (r,c,arr)) = arr
>
> in the old technique, but now looks like
>
> getarr (Rmatrix (r,c,arr)) = return arr
>
> Is this perhaps an effect of lazy evaluation? When does one actually
> need to evaluate the constructor for the storable array contained in
> A? Hmmm. Is it that the rules specify that an IO action forces the
> evaluation of the value in the monad, but otherwise this value may be
> unevaluated?
No. An action, when executed, returns a value, but this doesn't imply that
all actions have values stored in them.
Bulat's illustration of getChar is a perfect example of this, since getChar
has type IO Char but does not store the Char inside it, and executing it
multiple times will in general give different characters back depending on
your input stream...
However the action (return 'q') also has type IO Char but this time, the 'q'
is stored inside the action (return 'q').
So it matters exactly what action it is, since they can't be distinguished
just by looking at the types.
> So return x doesn't evaluate x but (return x) >> = \z -> IOfunc z
> does?
If you executed (return x), what first happens is that the *function*
return:: a-> IO a is applied to its argument value 'x' to get an *action*
which, when executed, will be able to supply the result value x, then this
action *is* executed, and x is available as the result.
Depending on the particular monad, x may or may not be evaluated. AFAIK for
the IO monad, it would not be, but I think it is possible to conceive of a
monad where the return function would need to evaluate its argument.
Also, even if x was unevaluated by it's journey through the return function
and executed action which hands it onto the input of iofunc, iofunc may or
may not evaluate it.
The short answer is: lazyness is a separate issue.
A longer answer (given near the end of the thread referenced below) is that
it depends on the fact that evaluation never happens under a lambda ie \x ->
exp prevents exp being looked at until the function is applied, and that the
sequence operator >> is defined in terms of >>= so that the second action is
always lifted into a function.
>
> This would actually make sense in the end. The IO action of
> A <- getAfromSomewhere would not evaluate the monad that is the third
> element of the tuple A, since there is no real 'need' to do so. So in
> fact no constructor of A's array would ever get evaluated until a
> function was applied to it, which would have to be in the form of an
> IO action. That's a nice mind twister. Clean's uniqueness types are
> a little easier to grasp I think. Ahh I think I understand now. It
> has to work that way or else you cannot guarantee the sequential
> execution property of monads. Thus if y :: IO (a) and you evaluate
> z <- func (f1 y) (f2 y), the evaluation order of y is controlled by
> what is implemented in func (and f1 and f2), not by evaluation rules
> for arguments. The value wrapped in y MUST remain unevaluated until IO
> 'actions' are performed on it.
You're *very* close to understanding it. You're right that in Haskell
arguments are never evaluated eagerly by some generic evaluation rule - the
function application is just replaced by the body of the function with that
unevaluated argument expression replacing all occurrences of the argument
variable ie lazy evaluation.
You just need to distinguish between the concepts of evaluation and
execution, so in your example above, where y has been bound to some
expression that evaluates to an action, depending on func, f1, f2, the
expression y is bound to may be evaluated zero or more times (depending on
whether or not y is used polymorphically within the function(s)), and the
resulting action(s) may be executed multiple times.
Personally I found it easier to underastand monads by looking at a simple
state monad first so it's very clear what is happening, because then you can
look inside the implementation of >>= and return and see that these are just
quite simple functions. It is impossible to understand monads just by
considering the types alone.
The IO monad is extremely tricky to fully understand because you can't see
how it is implemented, and as explained above, the types are not enough to
distinguish between quite different behaviours whereas a state monad reveals
exactly what's happening.
(There was a long discussion beginning
http://www.haskell.org//pipermail/haskell-cafe/2006-May/015605.html about
how best to understand IO but certainly before trying to do so, a state
monad is *infinitely* easier to understand and then provides a good basis
for understanding IO)
The first monad I understood was the state monad on page 261 of Paul Hudak's
book "The Haskell School of Expression", and there are also some tutorials
on the wiki at
http://www.haskell.org/haskellwiki/Books_and_tutorials#Using_Monads
Regards, Brian.
--
Logic empowers us and Love gives us purpose.
But societal laws, and religious dogma,
empower the dead,
to destroy us.
http://www.metamilk.com
More information about the Haskell-Cafe
mailing list