Re: [Haskell-cafe] Sequencing Operations in a Monad

2007-09-21 Thread SevenThunders



Al Falloon wrote:
> 
> SevenThunders wrote:
>> Well it certainly requires some thought here.  As I see it, I now have
>> two
>> reasonable choices.  Either I pull all my matrix operations back inside
>> the
>> IO monad and avoid the matrix action as a matrix variable paradigm  (due
>> to
>> the loss of referential transparency)  or I devise some way to guarantee
>> 'safety' and use unsafePerformIO.  I suppose I can use a somewhat
>> generalized version of safety where if I can guarantee that the order of
>> operations doesn't matter to the final output then I'm OK.  In this case
>> if
>> I can make it so that reording the computations only reorders the
>> locations
>> of my matrices on the stack, but otherwise doesn't affect the contents of
>> the matrices I think I am golden. 
>> 
>> I believe I got burned by following a nice tutorial interpretation of the
>> IO
>> monad as a way of carrying around an undeclared state variable,  the
>> world. 
>> But my little matrix IO variable is not just a world state with some
>> matrix
>> data in it, rather it appears to be a world state with a chain of
>> unapplied
>> function evaluations.  This is due to laziness I believe.  If I had a
>> data
>> structure that looked more like a world state with a reference to a
>> variable
>> in that world state, I could find a way to achieve my goals I think.
> 
> I know that you have already made your decision and moved on, but I 
> think that there is still another alternative that you can consider: 
> make an abstract interpreter for your matrix operations.
> 
> The basic idea is to use the normal Num et. al. type classes to write 
> your matrix calculations. However, instead of actually performing the 
> calculations it instead builds a data structure that represents the 
> calculations. You then 'interpret' the data structure in a separate 
> function in the IO monad.
> 
> The advantage of the approach is that you can pre-process the abstract 
> data structure to recognize intermediate matrices that can be consumed 
> without copying and other optimizations.
> 
> The other advantage is that the matrix math itself doesn't need to be in 
> the IO monad, only the interpretation, so you can use all the functional 
> goodness when writing the matrix operations.
> 
> I was going to whip up a small example, but I am pressed for time. So 
> here is a post from Oleg that shows the idea. 
> http://www.haskell.org/pipermail/haskell/2007-January/019012.html
> As usual his post is mind-expanding and probably a bit of overkill for 
> your problem, but I was the best I could come up with, google was not my 
> friend. You might have better luck (try "higher order abstract syntax" 
> and "abstract interpretation" and go from there)
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 


That's an interesting approach.  However if performance is a main concern
(in addition to 'elegance'), I would be concerned about having an
interpreter in an inner loop of some operation.  I quite frequently write
functions that do hundreds of matrix multiplies using hundreds of different
indexed matrices, where the function iterates over the matrix index.

When I first designed my Matrix library and was interfacing it with Haskell,
I considered the possibility of actually using Haskell to compile my
computations into C.  Thus there would be a matrix data type in Haskell, but
the final output of the Haskell operations would be C code.  In retrospect
that would have had a number of advantages, perhaps both in performance and
interoperability with the 'normal' programming world.  However I also wanted
to take advantage of ghci so that I could interact with my code in real
time.  That too is probably possible with the current toolset, but it would
have taken somewhat longer to develop.
-- 
View this message in context: 
http://www.nabble.com/Sequencing-Operations-in-a-Monad-tf4446047.html#a12824919
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


Re: [Haskell-cafe] Sequencing Operations in a Monad

2007-09-17 Thread SevenThunders



Paul Johnson-2 wrote:
> 
> SevenThunders wrote:
>> Unfortunately if I wrap my  matrix references in the IO monad, then at
>> best
>> computations like 
>> S = A + B are themselves IO computations and thus whenever they are
>> 'invoked' the computation ends up getting performed repeatedly contrary
>> to
>> my intentions.  
> This sounds like a case for the infamous performUnsafeIO.  The reason 
> this is "unsafe" is that the compiler assumes that the IO computation it 
> wraps has no visible side effects, so it doesn't matter when it is 
> performed or how many times it gets performed.  If your IO computation 
> indeed has this nature then you are OK, but its up to you to make sure 
> of this.
> 
> Paul.
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 

In the end I went witth the performUnsafeIO 'solution'.  It seems
satisfactory but it is far from perfect. My matrices are stored in the C
world as pointers on a stack.  In Haskell land I only attempted to
'guarantee' that the contents of the referred matrices were referentially
transparent.  Thus, in theory, the stack order could change with function
application order but the 'contents' of the matrices remain the same.  For
those routines that do alter current variables I force the output into the
IO monad.

There are two main problems with this approach.  The first is that if a
computation generates a new matrix by pushing it on to the stack,  a problem
might arise if one of it's dependent input matrices has not been evaluated
yet and if it to requires a new matrix to be pushed on to the stack.  Thus
the output matrix could be 'pushed' prior to the dependent matrices.  This
sort of thing happens all the time with lazy evaluation.  So my fix here is
to write my low level routines with a lot of strictness annotations  using
$! and seq, wherever possible, as well as to force argument evaluation by
sequencing them first in the IO monad.  So far so good, but it is not
perfect,  one has to always keep this limitation in mind.

The second problem is that it is necessary to maintain complete control over
the C stack, allowing the library user to completely trash the stack if not
careful, and utterly destroy referential transparency.  Again one has to
keep this in mind whenever stack manipulations or clearing variables off the
stack.

Still with these limitations, it looks like Haskell is going to make things
reasonably nice.
-- 
View this message in context: 
http://www.nabble.com/Sequencing-Operations-in-a-Monad-tf4446047.html#a12748654
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


Re: [Haskell-cafe] Sequencing Operations in a Monad

2007-09-15 Thread SevenThunders


Ronald Guida wrote:
> 
> 
> 
> 
> I could translate your example to the following:
> 
>> let S = A += B in
>>   do
>>   s <- S
>>   (r,c) <-  size (return s)
>>   k  <- matindex (return s)
> 
> This should only perform action S one time.
> 
That's a good point actually.  If I am careful about how I 'execute' my io
actions then I can avoid
unintended consequences.  Outside of the monad, however there is still a
referential transparency problem.  If I do something like this (+.  and -.
are my matrix addition and matrix subtraction operators)
let
  iou = a1 +. a2
  iov = a1 -. a2

then later
do
   u <- iou
   v <- iov

I have the unfortunate consequence of executing a1 and a2 twice.



> A simple design rule would be: A function should not take an IO action
> as an input if that action is to executed exactly once and only once.
> 
Well my matrix addition with +. could satisfy this but still get me in  a
heap of trouble as shown above.
(+.) :: IO(Int) -> IO(Int) -> IO(Int)
Even worse with binary op.s you could do something like   let s = a +. a  . 
The bottom line is that
referential transparency goes out the door if your variables are IO actions. 
Perhaps this is a case where uniqueness types is better suited.




> This brings us back to sequencing.  Your "highly fluid" stack
> manipulations in C are exactly the thing that's bug-prone and anathema
> to functional programming.  Here's what I think you should do:
> 
As far as bug prone, in the C world it works out quite nicely actually. 
First memory management is handled with nary a thought by managing the stack
and doing a little reference counting.  (For efficiency reasons I allow some
of matrices on my stack to be references into submatrices of other matrices
on the stack.)  Second I have a debug mode turned on by a define in the
include file that does detailed sanity checks on all input arguments.  I
just don't get segfaults due to bad pointer references because of this. 

I have already FFI'd all of this interface into Haskell, used Haskell as
kind of a glorified scripting language and have  written several complex
applications in Haskell using this interface with reasonable success.   Of
course all the matrix op.s and stack manipulations are done in the IO monad. 
It's just that now I want more :).  I want the syntax sugar so that I can
reason about matrix op.s more naturally and perhaps automate my handling of
my matrix stack a little easier.




> 1. Write a bunch of safe wrappers, as Ryan has described.
> 
> 2. Test them thoroughly, and also *prove* that they are in fact safe.
> 
> 3. Write your application-specific code and test it.  Do your best to
>   get your application-specific matrix calculations correct.
> 
> 4. If the code is too slow then profile it.  Remember, 80% of the time
>   is usually spent in 20% of the code.  *IF* (and only if) the matrix
>   code happens to take up that 80% of the time, then proceed.
> 
> 5. You can move your application-specific matrix calculations from
>   Haskell to C and put them behind an FFI interface.  Then, working
>   in C, you can optimize out all the matrix copying that takes place
>   behind safe wrappers.  The calculations will run faster without the
>   overhead of Haskell.
> 

Well it certainly requires some thought here.  As I see it, I now have two
reasonable choices.  Either I pull all my matrix operations back inside the
IO monad and avoid the matrix action as a matrix variable paradigm  (due to
the loss of referential transparency)  or I devise some way to guarantee
'safety' and use unsafePerformIO.  I suppose I can use a somewhat
generalized version of safety where if I can guarantee that the order of
operations doesn't matter to the final output then I'm OK.  In this case if
I can make it so that reording the computations only reorders the locations
of my matrices on the stack, but otherwise doesn't affect the contents of
the matrices I think I am golden. 

I believe I got burned by following a nice tutorial interpretation of the IO
monad as a way of carrying around an undeclared state variable,  the world. 
But my little matrix IO variable is not just a world state with some matrix
data in it, rather it appears to be a world state with a chain of unapplied
function evaluations.  This is due to laziness I believe.  If I had a data
structure that looked more like a world state with a reference to a variable
in that world state, I could find a way to achieve my goals I think.
-- 
View this message in context: 
http://www.nabble.com/Sequencing-Operations-in-a-Monad-tf4446047.html#a12692656
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


Re: [Haskell-cafe] Sequencing Operations in a Monad

2007-09-15 Thread SevenThunders



apfelmus wrote:
> 
> SevenThunders wrote:
>> Ryan Ingram wrote:
>>> As long as the FFI calls don't make destructive updates to existing
>>> matrices, you can do what you want.
>>>
>>> For example, assuming you have:
>>>
>>> -- adds the second matrix to the first & overwrites the first
>>> matrixAddIO :: MatrixIO -> MatrixIO -> IO ()
>>>
>>> -- creates a new copy of a matrix
>>> matrixCopyIO :: MatrixIO -> IO MatrixIO
>>> ...
>>>
>>>
>> Well as you point out there is an efficiency issue if we need to copy
>> matrices all of the time in order to insure 'referential transparency'.  
>> Moreover I manage my matrices on a stack  in C, since it makes it easy to
>> handle memory allocation and deallocation.  The stack configuration tends
>> to
>> be highly fluid so there are always side effects going on.  Right now my
>> Matrix type wraps the index from the bottom of the Matrix stack into the
>> IO
>> monad.
> 
> If you need destructive updates, you indeed need a monad. Otherwise, I'd 
> use ForeignPtrs and import the matrix operations as pure functions (~ 
> unsafePerformIO).
> 
>>  I was just wondering if there was any obvious way to force an IO action
>> to
>> execute only once, since now each reference to the action IO causes it to
>> execute again.
> 
> Isn't that simply
> 
>do
>  x <- onlyOnce
>  mult x x
> 
> with
> 
>onlyOnce :: IO Int
>mult :: Int -> Int -> IO Int
> 
> ?
> 
> If you want
> 
>mult = liftM2 something :: IO Int -> IO Int -> IO Int
> 
> you can
> 
>do
>  x' <- onlyOnce
>  let x = return x'
>  mult x x
> 
> which is
> 
>do
>  x <- return `liftM` onlyOnce
>  mult x x
> 
> for short.
> 
> Regards,
> apfelmus
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 

I think  you are right. This is about my only choice.  All 'computations'
must first occur inside the monad.  
For a binary operation that kind of implies a type signature of the form,

-- matrix multiplication, integer indices into Matrix stack
(*.)  ::  Int -> Int -> IO (Int)
-- addition
(+.)  :: Int -> Int -> IO (Int)


But what if I want to do something likea *. ( c +. d)  ?  Well I'll have
to live with

do
   s <- c +. d
   p <- a *. s

Unless I additionally define an multio  multiplication operator
(multio)  ::  Int ->  IO(Int) -> IO(int)

so that I can do
do
   s <- a `multio` (c +. d)
-- 
View this message in context: 
http://www.nabble.com/Sequencing-Operations-in-a-Monad-tf4446047.html#a12692293
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


Re: [Haskell-cafe] Sequencing Operations in a Monad

2007-09-15 Thread Paul Johnson

SevenThunders wrote:

Unfortunately if I wrap my  matrix references in the IO monad, then at best
computations like 
S = A + B are themselves IO computations and thus whenever they are

'invoked' the computation ends up getting performed repeatedly contrary to
my intentions.  
This sounds like a case for the infamous performUnsafeIO.  The reason 
this is "unsafe" is that the compiler assumes that the IO computation it 
wraps has no visible side effects, so it doesn't matter when it is 
performed or how many times it gets performed.  If your IO computation 
indeed has this nature then you are OK, but its up to you to make sure 
of this.


Paul.

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


Re: [Haskell-cafe] Sequencing Operations in a Monad

2007-09-15 Thread Ronald Guida

SevenThunders wrote:
> OK so check out what really happens with liftM2.  Suppose I have an IO
> containing an involved matrix computation called s.  For simplicity 
we might

> assume that
>
> s :: IO (Int)  
>

> and the Int is an index into an array containing a bunch of matrices in C
> land.  Assume that s is determined by a succession of many IO operations
> that have lots of side effects and are fairly computationally intensive.
> Also assume that s is unevaluated.
>
> Now do an operation like
>
> q = liftM2 MultMatrix s s
>
> What happens is that s is 'evaluated' twice when q is evaluated
>
> e.g.
> do
> qint <- q
>
>
> That becomes evident when we look at liftM2's definition
> liftM2 f  =  \a b -> do { a' <- a; b' <- b; return (f a' b') }
>
> the statements
> a' <- a   and b' <- b will cause s to be evaluated twice.
>
> Therein lies my problem.

Here's your solution:

 do
-- Compare this to liftM2 and your definition of q
s' <- s   -- this evaluates s once and for all
qint <- return $ MultMatrix s' s'

-- Ron

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


Re: [Haskell-cafe] Sequencing Operations in a Monad

2007-09-15 Thread SevenThunders



Dominic Steinitz wrote:
> 
>>  If you arrange the types to try to do all the operations inside the IO
>> monad you can't chain together more than 1 binary operation.  eg.
>> 
>> do
>>S <- A + B
>>Z <- Q * S
>> 
>> vs
>> 
>> do 
>>S <-  Q * (A + B)
>> 
>> Are there any suggestions for this dilemma?  Am I using the wrong monad
>> for
>> this task?
> 
> I'm not sure if this is what you are asking but isn't liftM2 or some
> variant what you need?
> 
> Dominic.
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 

OK so check out what really happens with liftM2.  Suppose I have an IO
containing an involved matrix computation called s.  For simplicity we might
assume that

s :: IO (Int)   

and the Int is an index into an array containing a bunch of matrices in C
land.  Assume that s is determined by a succession of many IO operations
that have lots of side effects and are fairly computationally intensive. 
Also assume that s is unevaluated.

Now do an operation like

q = liftM2 MultMatrix s s

What happens is that s is 'evaluated' twice when q is evaluated

e.g.
do
qint <- q


That becomes evident when we look at liftM2's definition
liftM2 f  =  \a b -> do { a' <- a; b' <- b; return (f a' b') }

the statements 
a' <- a   and b' <- b will cause s to be evaluated twice.

Therein lies my problem.

-- 
View this message in context: 
http://www.nabble.com/Sequencing-Operations-in-a-Monad-tf4446788.html#a12687963
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


[Haskell-cafe] Sequencing Operations in a Monad

2007-09-14 Thread Dominic Steinitz
>  If you arrange the types to try to do all the operations inside the IO
> monad you can't chain together more than 1 binary operation.  eg.
> 
> do
>S <- A + B
>Z <- Q * S
> 
> vs
> 
> do 
>S <-  Q * (A + B)
> 
> Are there any suggestions for this dilemma?  Am I using the wrong monad for
> this task?

I'm not sure if this is what you are asking but isn't liftM2 or some
variant what you need?

Dominic.

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


Re: [Haskell-cafe] Sequencing Operations in a Monad

2007-09-14 Thread Ronald Guida

SevenThunders wrote:

I have a matrix library written in C and interfaced into Haskell
with a lot of additional Haskell support.


[snip]


Unfortunately if I wrap my matrix references in the IO monad, then
at best computations like S = A + B are themselves IO computations
and thus whenever they are 'invoked' the computation ends up getting
performed repeatedly contrary to my intentions.


Here's some thoughts:

First, the IO monad already does sequencing, and it already has the
ability to execute an action once only.

Let's look at an example:


test1 = do
  putStr "What is your name? "
  n <- getLine
  putStrLn $ "Hello, " ++ n ++ "!"
  return n



getName :: IO String -> IO String
getName nameAction = do
  n <- nameAction-- execute the action
  return n



getNameLength :: IO String -> IO Int
getNameLength nameAction = do
  n <- nameAction-- execute the action
  return $ length n



test2 = do
  let nameAction = test1 in do
n <- getName nameAction
putStrLn $ "Name = " ++ n
len <- getNameLength nameAction
putStrLn $ "Length = " ++ show len



test3 = do
  n <- test1
  putStrLn $ "Name = " ++ n
  putStrLn $ "Length = " ++ show (length n)



test4 = do
  let nameAction = test1 in do
n <- nameAction
n' <- getName (return n)
putStrLn $ "Name = " ++ n'
len <- getNameLength (return n)
putStrLn $ "Length = " ++ show len


GHCi> test1
What is your name? Ron
Hello, Ron!
"Ron"

GHCi> test2
What is your name? Alice
Hello, Alice!
Name = Alice
What is your name? Bob
Hello, Bob!
Length = 3

GHCi> test3
What is your name? Ron
Hello, Ron!
Name = Ron
Length = 3

GHCi> test4
What is your name? Ron
Hello, Ron!
Name = Ron
Length = 3

Notice that in test2, I am asked for my name twice.  This behavior is
expected because the functions "GetName" and "getNameLength" each
accept an action and execute it to get a name.

In test3, I am only asked for my name once.  I only want to execute
the action once, so I have to code it that way.

Before I explain test4, let's look at your example code:


let S = A += B in
  do
  (r,c) <-  size S
  k  <- matindex S


If S is being executed twice, then clearly S is an action.  Perhaps
the type of S is "IO MatrixIO" ?  If that's true, then presumably the
functions "size" and "matindex" have signatures:

size :: IO MatrixIO -> IO (Int, Int)
matindex :: IO MatrixIO -> IO Int

Each function takes an IO action as its first argument, executes that
action, and then computes a result.

My two functions "getName" and "getNameLength" are similar to "size"
and "matindex": each function takes an IO action, executes the action,
and computes a result.

Now, look at test4.  That's how I can work around the behaviour of
"getName" and "getNameLength" while ensuring that I am only asked for
my name one time.  This works because "return" creates an IO action
that does nothing and simply returns its argument.

I could translate your example to the following:


let S = A += B in
  do
  s <- S
  (r,c) <-  size (return s)
  k  <- matindex (return s)


This should only perform action S one time.

In fact, functions like "getNameLength" are poorly designed functions
because they fail on "Separation of concerns".  The "getNameLength"
function is doing two different things: (1) it executes an IO action
to get a name, and then (2) it computes and returns the name's length.
In test4, I am bypassing the execution of an IO action by passing the
non-action "return n" to the getNameLength function.

A simple design rule would be: A function should not take an IO action
as an input if that action is to executed exactly once and only once.

Let's move on to chained binary operations.


If you arrange the types to try to do all the operations inside the
IO monad you can't chain together more than 1 binary operation.


Using your example, suppose I want to compute S := Q * (A + B), but I
don't have a function that computes A + B.  Instead, what I have is a
function that computes A += B by modifying A in place.

If I want to compute S, and I don't care about preserving A, then I
would perform the following steps:
A += B;  S := Q * A

If I do want to preserve A, then I need to copy it first.
A' := copy A; A' += B; S := Q * A'

No matter what, I cannot escape the need to explicitly sequence the
operations.

In C++, I could play some very sophisticated games with templates and
operator overloading to coax the C++ compiler to accept an expression
with chained operations like "S = Q * (A + B)" and do the right
thing.  In Haskell, I'm pretty sure the corresponding techniques
involve using arrows.

If you don't want that level of sophistication, then you are best off
coding what you mean, as in:

do
-- compute S := Q * (A + B)
C <- A + B
S <- Q * C

Now, there's just one more thing [emphasis added].


Moreover I manage my matrices on a stack in C, since it makes it
easy to handle memory allocation and deallocation.  *The stack*
*configuration tends t

Re: [Haskell-cafe] Sequencing Operations in a Monad

2007-09-14 Thread SevenThunders



Ryan Ingram wrote:
> 
> As long as the FFI calls don't make destructive updates to existing
> matrices, you can do what you want.
> 
> For example, assuming you have:
> 
> -- adds the second matrix to the first & overwrites the first
> matrixAddIO :: MatrixIO -> MatrixIO -> IO ()
> 
> -- creates a new copy of a matrix
> matrixCopyIO :: MatrixIO -> IO MatrixIO
> ...
> 
> 
Well as you point out there is an efficiency issue if we need to copy
matrices all of the time in order to insure 'referential transparency'.  
Moreover I manage my matrices on a stack  in C, since it makes it easy to
handle memory allocation and deallocation.  The stack configuration tends to
be highly fluid so there are always side effects going on.  Right now my
Matrix type wraps the index from the bottom of the Matrix stack into the IO
monad.   

 I was just wondering if there was any obvious way to force an IO action to
execute only once, since now each reference to the action IO causes it to
execute again.
-- 
View this message in context: 
http://www.nabble.com/Sequencing-Operations-in-a-Monad-tf4446047.html#a12686766
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


Re: [Haskell-cafe] Sequencing Operations in a Monad

2007-09-14 Thread Ryan Ingram
As long as the FFI calls don't make destructive updates to existing
matrices, you can do what you want.

For example, assuming you have:

-- adds the second matrix to the first & overwrites the first
matrixAddIO :: MatrixIO -> MatrixIO -> IO ()

-- creates a new copy of a matrix
matrixCopyIO :: MatrixIO -> IO MatrixIO

Then you can define "safe" operators like this:

module Matrix (
   Matrix,
   matrixCreate,
   matrixAdd
) where
import System.IO.Unsafe (unsafePerformIO)

newtype Matrix = Matrix { liftMatrix :: MatrixIO }

matrixCreate :: MatrixIO -> IO Matrix
matrixCreate m = do
   mNew <- matrixCopyIO m
   return (Matrix mNew)

matrixAdd :: Matrix -> Matrix -> Matrix
matrixAdd (Matrix m1) (Matrix m2) = unsafePerformIO $ do
   mDest <- matrixCopyIO m1
   matrixAddIO mDest m2
   return (Matrix mDest)

What is important is that every use of unsafePerformIO comes with a
proof at some level that the computation really is "functional"; that
is, that the result depends only on the inputs and not on the order of
operations.  An informal sketch of this proof for this bit of code:

1) Matrices are only injected into the system via matrixCreate, which
is an ordered operation in the IO Monad; the "Matrix" constructor is
not exported.

2) matrixCreate copies its source data.  So changes to source MatrixIO
objects can't affect any Matrix.

3) matrixAddIO only modifies its first argument, not the second.  We
only call it with a brand-new matrix object, so it's safe to modify
there.

You should be able to expand this to the point that you can implement
Num operations.  But be warned that efficiency may suffer; lots of
intermediate matrices get created, used once, and then discarded.
It's possible that you can use GHC rules to rewrite & fuse operations
which would help; I'd expect a serious matrix library to do so.  See
http://www.haskell.org/ghc/docs/latest/html/users_guide/rewrite-rules.html

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


[Haskell-cafe] Sequencing Operations in a Monad

2007-09-14 Thread SevenThunders

I have a matrix library written in C and interfaced into Haskell with a lot
of additional Haskell
support.  The C library of course has a lot of side effects and actually
ties into the BLAS libraries, thus at the present time, most of the
interesting calls are done in the IO monad.  I have no intention of
rewriting what I've done so far or using someone elses Matrix library. 
(Mine is tuned somewhat for my application).

I attempted to extend my Haskell matrix interface using type classes (real
and complex matrices) and have run into a conceptual problem.  I would like
to be able to use operator notation for matrix arithmetic.
e.g.
R = Q * (A + B)

Unfortunately if I wrap my  matrix references in the IO monad, then at best
computations like 
S = A + B are themselves IO computations and thus whenever they are
'invoked' the computation ends up getting performed repeatedly contrary to
my intentions.  For example I might have some code like this,

let S = A += B in
   do
   (r,c) <-  size S
   k  <- matindex S
.

code of this nature results in S being applied twice and if  the operator += 
has side effects, those side effects will be applied twice.  Even if there
are no side effects the computation will unnecessarily be applied twice. 
What I need is a way to force a single execution of the IO action without
losing the syntax sugar. 

 If you arrange the types to try to do all the operations inside the IO
monad you can't chain together more than 1 binary operation.  eg.

do
   S <- A + B
   Z <- Q * S

vs

do 
   S <-  Q * (A + B)

Are there any suggestions for this dilemma?  Am I using the wrong monad for
this task?
-- 
View this message in context: 
http://www.nabble.com/Sequencing-Operations-in-a-Monad-tf4446047.html#a12685983
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