Send Beginners mailing list submissions to
[email protected]
To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
[email protected]
You can reach the person managing the list at
[email protected]
When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."
Today's Topics:
1. Relation between monads and computations (Dmitriy Matrosov)
2. Effective file I/O with bytestrings (Johannes Engels)
----------------------------------------------------------------------
Message: 1
Date: Thu, 9 Feb 2012 14:02:59 +0300
From: Dmitriy Matrosov <[email protected]>
Subject: [Haskell-beginners] Relation between monads and computations
To: [email protected]
Message-ID:
<CAFdVUFkLUTE9MfAEbKShnb=e9obipZLco6ixk2kwk6qdara=g...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8
Hi, everyone!
Not so long ago i started to learn haskell, and now i have a question
about relation between monads and computations. In fact, i think, that
i understand it and write some explanation for myself, but i'm not
sure whether my explanation is correct or not, and will be very
thankful if someone check it :) Here it is (i don't know category
theory and my math knowledge is poor, so if i accidently use some
terms from them incorrectly - it was just my understanding).
Monads and computations.
Generally computation consists of initial value, computation itself and the
result. So it can be illustrated as:
type a (M b) b
data I ------> C <--------- E
f ConstrM
I :: a
f :: a -> M b
data M a = ContrM a | ...
E :: b
Let's see what happens: i take initial value I of type a and map it to some
computation C (of type (M b)) using function f. Then, exist such value E of
type b, that C = (ConstrM E). This value E will be the result of computation.
Now consider two functions: unitM, which maps value into trivial computation
(trivial computation is a computation, which result is equal to initial
value):
type a (M a) a
data I ------> C <--------- I
unitM ConstrM
I :: a
unitM :: a -> M a
data M a = ContrM a | ...
and bindM, which yields result from one computation, then applies some
function f to the result, and makes another computation at the end (E is the
result of this last computation).
type (M a) a (M b) b
data C ---------> I -------> C' <---------- E
pattern f ConstrM
match
data C --------------------> C' <---------- E
C `bindM` f ConstrM
C :: M a
I :: a
f :: a -> M b
C' :: M b
data M a = ContrM a | ...
E :: b
bindM :: M a -> (a -> M b) -> M b
Now, using fucntions unitM and bindM there is possibly to convert arbitrary
function (k :: a -> b), which makes from initial value of type a value of type
b, into terms of general computation (represented by type M).
type a (M a) a b (M b) b
data I ------> C ---------> I ------> E -------> C' <-------- E
unitM pattern k unitM ConstrM
match
data I ------> C ---------> I -----------------> C' <-------- E
unitM pattern f = (unitM . k) ConstrM
match
data I ------> C ------------------------------> C' <-------- E
unitM `bindM` f ConstrM
data I --------------------------------------------> C' <-------- E
g = (`bindM` f) . unitM ConstrM
I :: a
unitM :: a -> M a
C :: M a
k :: a -> b
C' :: M b
data M a = ConstrM a | ...
E :: b
f :: a -> M b
bindM :: M a -> (a -> M b) -> M b
g :: a -> M b
On the first picture i take initial value I of type a, and map it to trivial
computation C of type (M a) using unitM. Then i yield result of this trivial
computation C (which is I, of course), apply function k to this result (value
I) and get value E of type b as result. Then i wrap this value E into trivial
computation C' using unitM. Result of computation C' is, of course, E. On the
intermediate pictures i show reduction steps of the first picture. And finally
i get: i take initial value I of type a, and map it using function g into
computation C'. The result of computation C' is value E of type b.
So, from arbitrary function (k :: a -> b) i can create function g, which maps
initial value I of type a into some computation of type (M b). Actual
computation (calculation) will still be performed by k, but the result will
have type of general computation (M b) instead of b.
Monad is a way to implement such general computation, a way to write a program
based on general computations, which later may be redefined, instead of
particular ones, which redefinition leads to rewrite of large of amount of
code. Monad is a triple of type constructor M and functions unitM and bindM
(and errorM, probably?). Type constructor represents computation itself,
functions unitM and bindM used to wrap your own specific computation (k :: a
-> b) on types a and b into monadic notation (general computation notation).
First two of monad laws demand, that unitM maps into trivial computation.
..may be continued..
--
Dmitriy Matrosov
------------------------------
Message: 2
Date: Fri, 10 Feb 2012 10:31:27 +0100
From: Johannes Engels <[email protected]>
Subject: [Haskell-beginners] Effective file I/O with bytestrings
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=ISO-8859-15; format=flowed
Dear Haskellers,
in several books (RWH, LYAH) I have found the statement that file I/O is
more effective with bytestrings than with common strings. As I am doing
mostly scientific programming and nearly every program of mine uses file
I/O, I would like to check this. So I tried to write a small
"benchmark": read a double matrix from file and write it to file again.
Regarding to reading, the benefit of bytestrings was actually huge, it
was about ten times faster than with strings. What refers to writing,
however, I failed completely. Most important, I did not find a function
which directly converts doubles to bytestrings. So the best I could
figure out was the following ugly workaround using Text.Show.ByteString:
import qualified Data.ByteString.Lazy as DL
import qualified Text.Show.ByteString as BS
import Data.Char
import Data.List
import Data.Array.Unboxed
lineendw8 = DL.pack [fromIntegral (ord '\n')]
blankw8 = DL.pack [fromIntegral (ord ' ')]
showAll :: UArray (Int, Int) Double -> -- matrix
Int -> -- number of rows
Int -> -- number of columns
DL.ByteString
showAll mymatrix numrows numcols = foldr f lineendw8 [0..numrows-1]
where f = showLine mymatrix numcols
showLine :: UArray (Int,Int) Double -> -- matrix
Int -> -- number of columns
Int -> -- current row
DL.ByteString -> -- accumulator
DL.ByteString
showLine mymatrix numcols row akku =
let f col s = DL.append blankw8 $
DL.append (BS.runPut $ BS.showp
(mymatrix!(row,col))) s
in DL.append lineendw8 $ foldr f akku [0..numcols-1]
main :: IO ()
main = do
-- read file into UArray Int, Int) Double ...
-- ....
-- ... and write it to file again
let bs = showAll mymatrix numrows numcols
DL.writeFile "writeOut.dat" bs
This was more in order to show goodwill than to present a solution, of
course. It actually works, but, ugly as it is, it is by no means faster
than the corresponding procedure with strings. So my question: what is
the canonical way to write doubles to file? I guess this question must
have been posed already hundred times before, so I would also appreciate
very much a link to former answers ...
Best regards
Johannes Engels
------------------------------
_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners
End of Beginners Digest, Vol 44, Issue 10
*****************************************