[Haskell-cafe] Arrows for invertible programming: Notation question

2005-12-23 Thread Joel Reymont

Folks,

I have been looking at the code for the Arrows for invertible  
programming paper (http://www.cs.ru.nl/A.vanWeelden/bi-arrows/) and  
I have a question about syntax. ghci surely does not like it.


What does this mean and how do I make it compile?

mapl{|a, b|arr|} :: (mapl{|a, b|arr|}, ArrowChoice arr, BiArrow arr)  
= arr a b


Thanks, Joel

--
http://wagerlabs.com/


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


Re: [Haskell-cafe] Vectors in Haskell

2005-12-23 Thread Cale Gibbard
Implicit conversion is a mess. Suppose that
test5 = v1 + v2
Now,
test5 :: (Add (Vector a) (Vector a1) (Vector c), Num a, Num a1) = Vector c
Note that a and a1 don't occur on the right hand side of the =, so
the only way that they could be determined is if there was a
functional dependency c - a a1, but there isn't, and furthermore,
your instances violate the addition of such a dependency.

The fundamental problem here is that there's no one way to compute
test5, even if we force it to be Vector Double. Do we perform
fromIntegrals or don't we? There's no way to tell what is desired.

On the other hand, elegant vector space libraries are possible. Here's
a short module I wrote for general inner product spaces in a small
raytracer:

{-# OPTIONS -fglasgow-exts #-}

module Space where

-- Class for an abstract inner product space
class (Floating f) = Space f v | v - f where
  vZero  :: v  -- representation for the zero vector
  vAdd   :: v - v - v-- addition
  vMul   :: f - v - v-- left scalar multiply
  vInner :: v - v - f-- inner product

vNeg v = (-1) `vMul` v
v `vSub` w = v `vAdd` (vNeg w)
a `vDiv` v = recip a `vMul` v
vNorm v   = sqrt (v `vInner` v)
vDistance v w = vNorm (w `vSub` v)
vNormalise v  = (vNorm v) `vDiv` v

-- shorthand infix operators
-- note that the angle brackets go next to vectors
a + b = vAdd a b
a - b = vSub a b
a * b = vInner a b
r * a = vMul r a
a * r = vMul r a
r / a = vDiv r a
a / r = vDiv r a

data V3 = V3 !Double !Double !Double deriving (Eq, Show)

instance Space Double V3 where
 vZero = V3 0 0 0
 vAdd (V3 x y z) (V3 x' y' z') = V3 (x + x') (y + y') (z + z')
 vMul a (V3 x y z) = V3 (a*x) (a*y) (a*z)
 vInner (V3 x y z) (V3 x' y' z') = x*x' + y*y' + z*z'

v3Cross (V3 x y z) (V3 x' y' z') = V3 (y*z' - z*y') (z*x' - x*z') (x*y' - y*x')

squareDistance v w = let d = v - w in d * d
--- cut here

hope this helps
 - Cale

On 22/12/05, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:

 Dear Haskell,

 Most of the time we get along well.  But, I'm growing weary of the
 arguments, fights, and nitpicking when I try to implement new mathematical
 types and overload your operators.  I don't know how to cooperate with your
 type systems.  At moments like this, I think about getting back together
 with C++.

 I love you.  But, I also love implementing complex numbers, vectors,
 matrices, and quaternions, and Galois fields.  C++ is not nearly as elegant
 and beautiful as you.  But, C++ doesn't complain when I try to do this.
 Isn't there some way we can work things out so I can implement these types
 with you?

 Seriously, I'm trying to implement a vector.  I'm starting with vector
 addition:

 {-
This code is works with Glasgow, ghci, with these options:
   -fglasgow-exts
   -fallow-undecidable-instances
   -fno-monomorphism-restriction
   -fallow-incoherent-instances
 -}

 data Vector a = Vector [a] deriving Show

 class Add a b c | a b - c where
(.+) :: a - b - c

 instance Add Int Int Int where
(.+) x y = x + y

 instance Add Int Double Double where
(.+) x y = (fromIntegral x) + y

 instance Add Double Int Double where
(.+) x y = x + (fromIntegral y)

 instance Add Double Double Double where
(.+) x y = x + y


 instance (Add a b c) = Add (Vector a) (Vector b) (Vector c) where
(.+) (Vector x) (Vector y) = Vector (zipWith (.+) x y)

 vi1 = Vector [(1::Int)..3]
 vi2 = Vector [(10::Int),15,2]
 vd1 = Vector [(1::Double)..3]
 vd2 = Vector [(10::Double),15,2]
 test1 = vi1 .+ vi2
 test2 = vi1 .+ vd2
 test3 = vd1 .+ vi2
 test4 = vd1 .+ vd2

 v1 = Vector [1,2,3]
 v2 = Vector [10,15,2]


 However, it is necessary to explicitly nail down the type of the Vector.  v1
 and v2 are more general.

 *Main :t v1
 v1 :: forall a. (Num a) = Vector a
 *Main :t v2
 v2 :: forall a. (Num a) = Vector a
 *Main test2

 I'd like for .+ to work with v1 and v2.  So, I can use things like Vector
 [1,2,3] in expressions, instead of Vector[(1::Int),2,3].  However, v1 and v2
 do not work with .+ in the code I produced above.

 Does anyone have any ideas how to make this work?  I hoped defining .+ more
 generally for instances of Num would make my vector addition code work with
 v1 and v2.  My failed attempt involved making the following changes . . .

 -- I added this
 instance (Num d) = Add d d d where
(.+) x y = x + y

 -- instance Add Int Int Int where
 --(.+) x y = x + y

 instance Add Int Double Double where
(.+) x y = (fromIntegral x) + y

 instance Add Double Int Double where
(.+) x y = x + (fromIntegral y)

 -- instance Add Double Double Double where
 --(.+) x y = x + y

 When I make these changes and compile, I get the following error messages on
 the declaration of test1 and test4. . .

 Vector2.hs:38:12:
 Overlapping instances for Add (Vector Int) (Vector Int) (Vector Int)
   arising from use of `.+' at Vector2.hs:38:12-13
 Matching instances:
   Vector2.hs:31:0: instance (Add a b c) = 

Re: [Haskell-cafe] Arrows for invertible programming: Notation question

2005-12-23 Thread Ralf Hinze
 What does this mean and how do I make it compile?
 
 mapl{|a, b|arr|} :: (mapl{|a, b|arr|}, ArrowChoice arr, BiArrow arr) = arr a 
 b

It's Generic Haskell source code, see

http://www.generic-haskell.org/

Generic Haskell is an extension of Haskell that supports generic programming.

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


Re: [Haskell-cafe] Arrows for invertible programming: Notation question

2005-12-23 Thread Joel Reymont
Is this something that can be compiled with GHC right now? I noticed - 
fgenerics but I think it does something else entirely.


On Dec 23, 2005, at 8:52 AM, Ralf Hinze wrote:


It's Generic Haskell source code, see

http://www.generic-haskell.org/

Generic Haskell is an extension of Haskell that supports generic  
programming.


--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Arrows for invertible programming: Notation question

2005-12-23 Thread Ralf Hinze
 Is this something that can be compiled with GHC right now? I noticed - 
 fgenerics but I think it does something else entirely.

GH is a pre-compiler that takes GH code to Haskell code,
so this is a two-step process. -fgenerics turns derivable
type classes on (see Derivable type classes, Ralf Hinze
and Simon Peyton Jones, Haskell Workshop 2000, pp94-105).
The two are different but related ...

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


Re[2]: [Haskell-cafe] Re: Tutorial uploaded

2005-12-23 Thread Bulat Ziganshin
Hello Daniel,

Wednesday, December 21, 2005, 6:34:10 PM, you wrote:

DC You can show them this on the first page:

DC main = do
DC x - getLine()
DC print my_program(x)

this named `interactive` :)  try:

main = interactive(map toUpper)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] exuberant-ctags, haskell, vim, tlist plugin

2005-12-23 Thread Bulat Ziganshin
Hello Marc,

Thursday, December 22, 2005, 7:22:38 PM, you wrote:
MW exuberant-ctags to parse the files which doesn't support haskell, yet.

search for hasktags. i have a slightly modified version of this
program, which also finds function definitions without prototypes


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re[2]: [Haskell-cafe] Substring replacements

2005-12-23 Thread Bulat Ziganshin
Hello Branimir,

Wednesday, December 21, 2005, 10:18:43 AM, you wrote:

try to add

{-# NOINLINE replace #-}

to both programs and repeat comparision

BM These are tests:
BM No optimisations (no -O):

NOINLINE just prevents RunTimeCompilation (see wiki page for details),
so this way you will test speed of replace on previously unknown
string. disabling optimization says nothing about real speed of
optimized program, which searches for the many different strings

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re[2]: [Haskell-cafe] Re: Tutorial uploaded

2005-12-23 Thread Bulat Ziganshin
Hello Bill,

Wednesday, December 21, 2005, 6:38:33 PM, you wrote:
BW PS:  While looking over my post it occurred to me that the issue is at
BW least as much methodological as it is linguistic.  So I ask:  Does
BW Haskell stand far enough apart from other programming languages to
BW warrant adapting standard methodological principles to it?  Is there an
BW identifiable Haskell Way?

as the man, who learned Haskell just year ago, and written large
enough imperative program in Haskell (you can see it at
http://freearc.narod.ru), i can answer both yes and no. yes, Haskell
really changes the way i program. no, it not diverges from the
standard methodology - it forces to use it! :)

any real program uses global variables, side-effects of functions,
manually controlled sharing of data and so on. imagine programming in
language which just don't support any provision for those tricks

well, Haskell implementations de-facto supports such tricks, but they
are considered as bad programming style and can lead to problems
with optimized compilation, so you will aspire to avoid them as much
as possible. you will need to decide beforehand for each function,
whether it will have side effects or will be pure (although you of
course may change your solution, whis will require to edit all
functions which directly or indirectly call it, because function with
side effects cannot be called inside pure function)

you will need to learn programming techniques, which can be used in
reliable way instead of forbidden unreliable ones - such as implicit
parameters and using large structure to pass through the many levels
of calls all data needed for these functions

you will become an expert in organizing cycles via recursion

ay least, you must try :)  even if Haskell is not useful as real
programming language, you at least will improve your programming style
;)



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re[2]: [Haskell-cafe] Functions with side-effects?

2005-12-23 Thread Bulat Ziganshin
Hello Daniel,

Wednesday, December 21, 2005, 6:24:29 PM, you wrote:

DC So I can have an IO bit (e.g. a do-block) that calls functions (which
DC are purely functional code) but I can't have a function that executes 
DC any IO.

it's true

DC For example, it is not possible to write a function my_read_file that 
DC could work like this:

DC my_data = my_read_file(my_file.txt)

DC Correct? Otherwise this would be a function that is not referentially 
DC transparent.

you are right. type IO a, after all, stands for RealWorld -
(a,RealWorld), i.e. it gets RealWorld as parameter and returns,
besides value of type a, a new RealWorld state. the function which
type don't ended with IO a, just can't receive or return value of
type RealWorld, so there is just no way to check something outside or
return new state of the outer world


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] Re: Tutorial uploaded

2005-12-23 Thread Bulat Ziganshin
Hello Daniel,

Thursday, December 22, 2005, 3:13:06 PM, you wrote:
DC Well, I'm a newbie, and I wrote it. I have enough understanding to
DC generate that code, even if I don't understand it all. This is what I know:

please, don't learn Haskell!!! we will test different tutorials on
you! :)))



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re[2]: [Haskell-cafe] Statements spanning multiple lines?

2005-12-23 Thread Bulat Ziganshin
Hello Greg,

Thursday, December 22, 2005, 8:15:08 PM, you wrote:

GB You might also like to try the slightly more efficient...

GB pyth n = [(a,b,c) | a - [1..n],  
GB b - [a..n],   
GB c - [a+1..n],

c - [b+1..n] is even better :)

GB a*a + b*b == c*c ]



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re[2]: [Haskell-cafe] Re: Battling time leaks

2005-12-23 Thread Bulat Ziganshin
Hello Joel,

Wednesday, December 21, 2005, 9:47:19 PM, you wrote:
 can you say what it exactly means? we are not mastered in your code.
 some common explanation like my program takes 6 seconds to
 deserialize 50kb of data on Pentium4/3ghz will be more understabdable

JR That's why I posted the code at http://wagerlabs.com/timeleak.tgz

JR The alerts are issued when the time of unstuffing exceeds 3 seconds.

this says nothing to me. you must say

1) your end goal - say, run 1000 threads each 3 seconds
2) why you can't share result of one unpickling among all threads?
3) your computer
4) unpickling time for one 50kb record


 if your current problem is deserialization speed, i can give you my
 own library. it now runs about 500kb/sec on 1ghz processor

JR My issue is that I 1) have about 250 records and 2) my wire format is  
JR different from the Haskell representation. Everything arrives to me  
JR little-endian, for example.

1) you can use TH (may be, Einar will help you. he already have TH
support in its own SerTH library). even without TH, writing Binary
instances, imho, is an order easier than writing pickler functions -
especially when you need only deserialiation :)
2) Binary library use network format (little-endian) on all platforms

but i'm absolutely not sure that your real problem is raw unpickling speed

JR It looks like pickling is the bottleneck so I'm converting all the  
JR structures to Storable :(. In the meantime, I'm looking for suggestions.

JR Einar offered BinSer which lets me use a single spec for the record  
JR format, conversions included. See http://cs.helsinki.fi/u/ekarttun/ 
JR haskell/test.hs. I still can't figure out how I would go from a :+: b  
JR to Foo a b, though.

interesting thing, i will look. i'm rewrote from scratch my serialization
library 2 times, and still want to fully rewrite it again :)

http://cs.helsinki.fi/u/ekarttun/haskell/test.hs

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re[2]: [Haskell-cafe] Re: Tutorial uploaded

2005-12-23 Thread Bulat Ziganshin
Hello John,

Thursday, December 22, 2005, 3:48:37 AM, you wrote:

JM You can't not start with IO for people who already know how to program,
JM if you are teaching someone programming for the very first time then
JM starting with the pure functional side is fine. But for people that
JM already know how to program, they are constantly thinking of everything
JM else they have written and how they might do it in the language they are
JM currently learning comparing and contrasting in their head. They need to
JM have the tools to replicate what they have done with other languages
JM right away, they don't want to know how to do the examples given in the
JM book except insofar as they let them understand how to write the
JM examples wiggling around in their head.

yes, it's just about me :)  first i time i tried to learn Haskell
(afair, it was advertized on bzip2 page), i decided that it need to
write everything as a pure function and found monad concept very
complex (afair, gentle introduction emphasizes that monads are very
complex things!). next time i tried to learn Haskell, my main question
was is it possible to use imperative style of controlling program
action?. i recognized functional power of language and it was the
last barrier to really use it

so, i think, it is needed to reassure imperative programmers at
first pages by demonstrating techiques of imperative programming,
including conditional execution and IORef/MArray and only after that
present more convenient alternatives. at least for my imperative feel,
conditional execution, cycles, modifiable variables and arrays
together form enough basis to implement any algorithm


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


[Haskell-cafe] Continuations

2005-12-23 Thread Joel Reymont

Folks,

My current setup involves threads that block on a MVar/TMVar until  
they read an event from it and then proceed. I would like to convert  
these threads into continuations whereby a continuation is saved when  
an event is requested and I can call that continuation when an even  
arrives.


I had done this in Lisp before like this:

(defun/cc receive (game)
  (let/cc k
;; save continuation
(setf (continuation game) k)
;; TODO: start a timer here
))

(defun/cc ask-for-blind (game amount context)
  (let ((posted nil)
(seat nil)
(active (car context))
(small-blind-p (= (small-blind$ game) amount)))
(while (and (not posted) (car active))
  (setf seat (pop active))
  ;; skip people who are waiting
  ;; for the big blind if small blind
  ;; is being posted.
  (unless (and (waiting-for-bb-p seat)
   small-blind-p)
(setf (state seat) 'sitting-out)
(setf (current game) seat)
(send (player seat) 'blind amount)
(let* ((cmd (receive game)) --- note the call to  
receive here

   (action (first cmd))
   (bet (second cmd))
   (inplay$ (inplay$ (player seat
...

How would this translate into Haskell and the Cont monad?

Alternatively, I would appreciate an example that requests, say, two  
Ints by saving a continuation each time and returns the sum.


Thanks, Joel

--
http://wagerlabs.com/





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


Re[2]: [Haskell-cafe] Arrows and pickler combinators

2005-12-23 Thread Bulat Ziganshin
Hello Jeremy,

Thursday, December 22, 2005, 11:25:40 PM, you wrote:

JS As I mentioned, the current implementation is a bit of hack-job, but I
JS think the design is somewhat compelling because of the flexibility
JS gained by seperating the pickling/unpickling from the mechanism used
JS to write/read the bytes.

JS I hope to clean to code up and submit a TMR article eventually.

seem that number of serialization libraries is larger that one can
imagine :)  i also wrote my own (thirs) library which in some places
are close to your, in some better and in some worser. for examle, i
want to use any monad instead of fixed IO in current design. on the
other side, i support bit-oriented  byte-oriented serialization, and
whole hierarchy of Stream types

i'm not sure what yor goal was a speed, but if you are interesting -
your design may be not too fast because of using tuples



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] Vectors in Haskell

2005-12-23 Thread Henning Thielemann


On Thu, 22 Dec 2005 [EMAIL PROTECTED] wrote:


Dear Haskell,

Most of the time we get along well.  But, I'm growing weary of the
arguments, fights, and nitpicking when I try to implement new mathematical
types and overload your operators.  I don't know how to cooperate with
your type systems.  At moments like this, I think about getting back
together with C++.

I love you.  But, I also love implementing complex numbers, vectors,
matrices, and quaternions, and Galois fields.


quaternions and matrices are still missing, but anything else is 
available in:

 http://cvs.haskell.org/darcs/numericprelude/

For linear algebra I setup a Wiki page:
 http://haskell.org/hawiki/LinearAlgebra
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Arrows for invertible programming: Notation, question

2005-12-23 Thread Arjen

On Fri, 23 Dec 2005, Joel Reymont wrote:

 Folks,

 I have been looking at the code for the Arrows for invertible
 programming paper (http://www.cs.ru.nl/A.vanWeelden/bi-arrows/) and
 I have a question about syntax. ghci surely does not like it.

I've updated the web page to say that is does not work with Hugs, GHCi 
or GHC -fgenerics, sorry for the confusion.
It really requires Generic Haskell (GH) 1.42. I never got GH working 
with GHC 6.4, so you also really need GHC 6.2.2. I think you can run the 
result of the GH preprocessor (using the right command line options) in 
GHCi or Hugs, but I'm not sure.


If anyone got GH working with GHC 6.4(+), please tell me how you did it.

 What does this mean and how do I make it compile?

 mapl{|a, b|arr|} :: (mapl{|a, b|arr|}, ArrowChoice arr, BiArrow arr)
 = arr a b

In GH this means: mapl is a polytypic (type-indexed in a and b) function 
that yields an arr(ow) from a to b. It is overloaded in ArrowChoice and 
BiArrow on the arr(ow). Because it is polytypic, it is also overloaded 
`in itself'. Most of the time GH does not require the last part 
explicitly, but sometimes it triggers a bug if you don't specify it.

The semantics of mapl can be found in the paper.

regards,
Arjen

   Thanks, Joel

 --
 http://wagerlabs.com/

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


Re: [Haskell-cafe] Functions with side-effects?

2005-12-23 Thread Glynn Clements

Daniel Carrera wrote:

 I'm a Haskell newbie and I don't really understand how Haskell deals 
 with functions that really must have side-effects. Like a rand() 
 function or getLine().

Those aren't functions.

A function is a single-valued relation, i.e. a (possibly infinite) set
of ordered pairs x,y such that the set doesn't contains two pairs
a,b and c,d where a == c and b =/= d. IOW, a static mapping from
argument to result.

Haskell uses the term function to mean a function in the strict
mathematical sense, and not (like most other languages) to mean a
procedure which returns a value as well as reading and writing some
implicit state.

 I know this has something to do with monads, but I don't really 
 understand monads yet. Is there someone who might explain this in newbie 
 terms? I don't need to understand the whole thing, I don't need a rand() 
 function right this minute. I just want to understand how Haskell 
 separates purely functional code from non-functional code (I understand 
 that a rand() function is inevitably not functional code, right?)

All Haskell code is functional (discounting certain low-level details
such as unsafePerformIO).

Side effects are implemented by making the prior state an argument and
the new state a component of the result, i.e. a C procedure of type:

res_t foo(arg_t);

becomes a Haskell function with type:

ArgType - State - (State, ResType)

To simplify coding (particularly, making sure that you use the correct
iteration of the state at any given point), all of this is usually
wrapped up in an instance of the Monad class. But there isn't anything
special about Monad instances. The class itself and many of its
instances are written in standard Haskell.

To provide a concrete example, here's a monadic random number
generator:

type Seed = Int

data Rand a = R { app :: Seed - (Seed, a) }

myRand :: Rand Int
myRand = R $ \seed - let
result = (seed' `div` 65536) `mod` 32768
seed' = seed * 1103515245 + 12345
in (seed', result)

instance Monad Rand where
f = g = R $ \seed - let (seed', x) = app f seed
 in app (g x) seed'
return x = R $ \seed - (seed, x)

runR :: Seed - Rand a - a
runR seed f = snd $ app f seed

Example usage:

randomPair :: Rand (Int, Int)
randomPair = do
myRand = \x -
myRand = \y -
return (x, y)

or, using do notation (which is simply syntactic sugar):

randomPair :: Rand (Int, Int)
randomPair = do
x - myRand
y - myRand
return (x, y)

main = print $ runR 99 randomPair

The main difference between the built-in IO monad and the Rand monad
above is that where the Rand monad has a Seed for its state, the IO
monad has the (conceptual) World type.

As the World type has to represent the entire observable state of the
universe, you can't actually obtain instances of it within a Haskell
program, and thus there is no equivalent to runR.

Instead, you provide an IO instance (main) to the runtime, which
(conceptually) applies it to the World value representing the state of
the universe at program start, and updates the universe to match the
World value returned from main at program end.

-- 
Glynn Clements [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Vectors in Haskell

2005-12-23 Thread Udo Stenzel
[EMAIL PROTECTED] wrote:
 {-
This code is works with Glasgow, ghci, with these options:
   -fglasgow-exts
   -fallow-undecidable-instances
   -fno-monomorphism-restriction
   -fallow-incoherent-instances
 -}

First off, try lighter weapons first.  Be switching on all possible
extensions you're also getting worse error reporting and more unexpected
interactions.  -fglasgow-exts and -fallow-overlapping-instances should
be enough.

 
 v1 = Vector [1,2,3]
 v2 = Vector [10,15,2]
 
 I'd like for .+ to work with v1 and v2.  So, I can use things like Vector
 [1,2,3] in expressions, instead of Vector[(1::Int),2,3].

And what do you think work would mean?  It is unknown whether v1 and
v2 contain Ints or Doubles, so it is not known how to add them.  What do
you expect the compiler to do?  Usually the result of the addition would
be known (you want a Vector Double), but with the mixed additions you
defined that doesn't imply a type for v1 or v2.


 Vector2.hs:38:12:
 Overlapping instances for Add (Vector Int) (Vector Int) (Vector Int)
   arising from use of `.+' at Vector2.hs:38:12-13
 Matching instances:
   Vector2.hs:31:0: instance (Add a b c) = Add (Vector a) (Vector b)
 (Vector c)
   Vector2.hs:15:0: instance (Num d) = Add d d d
 In the definition of `test1': test1 = vi1 .+ vi2
 
 I interpret this as saying that the compiler doesn't know if the .+ in test1 
 =
 vi1 .+ vi2 should match the Vector instance or the Num instance.  I could
 understand this if Vector was an instance of class Num.  However, this is not
 the case.  I figure either Glasgow has a bug or I don't really understand the
 error message.

You don't understand the mechanism.  GHC first looks at the instance
head, then decides which instance to use, then tries to satisfy the
context.  Now try to find an instance for (Add (Vector Int) (VectorInt)
(Vector Int)):

Does it match (Add (Vector a) (Vector b) (Vector c))?  It does.
Does it match (Add d d d)?  It too does.
Which one is more specialized?  Neither.  I can't decide.

You want to express a priority.  This is possible, but not obvious.
First, define overlapping instances in such a way than one is strictly
more general:

instance (Add a b c) = Add (Vector a) (Vector b) (Vector c)
instance (...) = Add a b c -- see below

To declare (Add d d d) you need a second class:

class Add' a b c
instance Num d = Add' d d d

instance Add' a b c = Add a b c


This should work (but I didn't test it).  For three times (Vector Int),
the first instance for Add is choosen, since it is strictly more
specific than the second.  For three times Int, only the second can
match.  Then the context (Add' ...) is satisfied.  For three times
String (which must not work), the second instance for Add matches, but
the context (Add' ...) cannot be satisfied.  It works a bit like Prolog
written backwards and without backtracking :)


 I'd be grateful for any suggestions or pointers to information on how to
 implement vectors (or other mathematical types) so they seamlessly and
 intuitively work with types, classes and operators already built into Haskell.

In general, do something more simple, as Cale suggested.  The implicit
conversions don't buy you much, but the type system extensions will
cause lots of headaches.


Udo.
-- 
Part of any serious QA is removing Perl code the same way you go over a
dilapidated building you inherit to remove chewing gum and duct tape and
fix whatever was kept together for real. -- Erik Naggum


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


[Haskell-cafe] StringMap

2005-12-23 Thread Christian Maeder

Hi,

could I ask you for efficient StringMap implementations, i.e. based on 
tries or hash keys? It's mainly for the sake of interest. In the (not 
too distant) future I'd like to see a library module Data.MapString 
along the lines of Data.Map and Data.IntMap.


So it would be nice (but no requirement) if your implementation could be 
easily compared to (or exchanged with) the Data.Map String instance. 
(I also still lack a comparison and correctness test infrastructure.)


Cheers and Merry Xmas
Christian
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] W3C discussion: Principle of Least Power

2005-12-23 Thread Graham Klyne
There's a possibly-interesting thread running on the W3C TAG mailing list [2]
about the Principle of Least Power [1], in which Haskell gets a mention.

The debate gets kind-of interesting around discussion of analyzability of
language expressions vs expressibility, with passing reference to Turing
completeness.  Intuitively, I've felt that expressions in a pure functional
language are easier to analyze than expressions in (say) C or Java, despite them
all being fully Turing complete (so no difference in expressive power there).

Can it truly be said that it's easier to analyze a functional expression than a
C program?  What could that actually mean?  I feel the discussion is (so far)
missing a trick, but I'm not sure what it is.

#g
--

[1] http://lists.w3.org/Archives/Public/www-tag/2005Dec/0101.html
http://lists.w3.org/Archives/Public/www-tag/2005Dec/0113.html
http://lists.w3.org/Archives/Public/www-tag/2005Dec/0115.html
(etc.)

[2] http://web3.w3.org/2001/tag/
http://lists.w3.org/Archives/Public/www-tag/

-- 
Graham Klyne
For email:
http://www.ninebynine.org/#Contact

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


Re: [Haskell-cafe] Vectors in Haskell

2005-12-23 Thread Bulat Ziganshin
Hello Jeff,

Friday, December 23, 2005, 1:52:02 AM, you wrote:

JHhc {-
JHhcThis code is works with Glasgow, ghci, with these options:
JHhc   -fglasgow-exts
JHhc   -fallow-undecidable-instances
JHhc   -fno-monomorphism-restriction
JHhc   -fallow-incoherent-instances
JHhc -}

:) replace it with:

{-# OPTIONS -fglasgow-exts -fallow-undecidable-instances 
-fno-monomorphism-restriction -fallow-incoherent-instances #-}

and the compiler will set this options automatically. btw, why you
need to disable the monomorphism restriction?

JHhc v1 = Vector [1,2,3]
JHhc v2 = Vector [10,15,2]

use instead:

vector :: [Double] - Vector Double
vector = Vector
v1 = vector [1,2,3]
v2 = vector [10,15,2]


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] Re: kinds question

2005-12-23 Thread David Roundy
On Thu, Dec 22, 2005 at 06:27:41PM -0800, Ashley Yakeley wrote:
 David Roundy wrote:
 Hello all,
 
 I have a question about how to create the right kind to declare lists to be
 a class.  I have a class Foo
 
 class Foo f where
   foo :: f a - Foo
 
 and I want to define that a list of Foos is also a Foo, but can't see how
 to do it.  I imagine something like
 
 instance Foo f = Foo [f] where
   foo xs = map foo xs
 
 but of course [f] isn't a valid type.
 
 [] and f both have * - *, and you want to compose them. You can do this 
 like this:
 
   newtype Compose p q a = MkCompose p (q a)
 
 and then
 
   instance Foo f = instance (Compose [] f) where
 foo (MkCompose fs) = ...

Given:

instance Foo f = Foo (Compose [] f) where
foo _ = undefined

ghc gives me the error:

test.hs:24:0:
Illegal instance declaration for `Foo (Compose [] f)'
(The instance type must be of form (T a b c)
 where T is not a synonym, and a,b,c are distinct type variables)
In the instance declaration for `Foo (Compose ([]) f)'

I can, however, define

instance (Functor p, Foo q) = Foo (Compose p q) where
foo (MkCompose fs) = MkCompose (fmap foo fs)

but in any case, this doesn't make a list itself a Foo, so you'd still need
wrappers, which would defeat the point of putting lists into the class.  :(
-- 
David Roundy
http://www.darcs.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Vectors in Haskell

2005-12-23 Thread David Roundy
On Fri, Dec 23, 2005 at 12:12:49PM +0100, Udo Stenzel wrote:
 [EMAIL PROTECTED] wrote:
  {-
 This code is works with Glasgow, ghci, with these options:
-fglasgow-exts
-fallow-undecidable-instances
-fno-monomorphism-restriction
-fallow-incoherent-instances
  -}
 
 First off, try lighter weapons first.  Be switching on all possible
 extensions you're also getting worse error reporting and more unexpected
 interactions.  -fglasgow-exts and -fallow-overlapping-instances should be
 enough.

Indeed, I think this is a very important point, and one of the reasons I'd
like to see Haskell 06 come out with a reasonable set of extensions that
are known to work together well.  I've gone down this path before, adding
extension after extension, and it just leads to more and more
confusion--since I don't understand what the extensions do, or how they
change the language!
-- 
David Roundy
http://www.darcs.net


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


RE: Re[2]: [Haskell-cafe] Substring replacements

2005-12-23 Thread Branimir Maksimovic





From: Bulat Ziganshin [EMAIL PROTECTED]
Reply-To: Bulat Ziganshin [EMAIL PROTECTED]
To: Branimir Maksimovic [EMAIL PROTECTED]
CC: haskell-cafe@haskell.org
Subject: Re[2]: [Haskell-cafe] Substring replacements
Date: Fri, 23 Dec 2005 11:32:01 +0300

Hello Branimir,

Wednesday, December 21, 2005, 10:18:43 AM, you wrote:

try to add

{-# NOINLINE replace #-}

to both programs and repeat comparision

BM These are tests:
BM No optimisations (no -O):

NOINLINE just prevents RunTimeCompilation (see wiki page for details),
so this way you will test speed of replace on previously unknown
string. disabling optimization says nothing about real speed of
optimized program, which searches for the many different strings



I got it. These tests were with NOINLINE in both cases but I didn;t
saw any speed difference in results as actually replace (straight)
and searchReplace (KMP) is just called for two differnet strings.
Perhaps if I call that for long list of short patterns patterns on short 
string,

test would display different results (INLINE wouldn't help).
I'll try that next.

Greetings, Bane.

_
Don't just search. Find. Check out the new MSN Search! 
http://search.msn.click-url.com/go/onm00200636ave/direct/01/


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


[Haskell-cafe] Strong Normalization was Re: W3C discussion: Principle of Least Power

2005-12-23 Thread Shae Matijs Erisson
Graham Klyne [EMAIL PROTECTED] writes:

 Can it truly be said that it's easier to analyze a functional expression than
 a C program?  What could that actually mean?  I feel the discussion is (so
 far) missing a trick, but I'm not sure what it is.

The LtU article What good is strong normalization in programming
languages?[1] may be helpful here. Barry Jay's comment about always
terminating data access plus loops or fixpoints interests me in particular.

I wonder, would it be useful to have a language designed entirely that way?
Could you have a terminating language with only a single top level loop?
Could any two programs be composed such that the result still only has a single
top level loop? Would a language structured that way be advantageous for
debugging, proof assistants, or other verifications?

[1] http://lambda-the-ultimate.org/node/view/1120
--
Shae Matijs Erisson - http://www.ScannedInAvian.com/ - Sockmonster once said:
You could switch out the unicycles for badgers, and the game would be the same.

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


Re: [Haskell-cafe] Continuations

2005-12-23 Thread Joel Reymont


On Dec 23, 2005, at 1:06 PM, Bulat Ziganshin wrote:


hm... you are waste much time unsystematically optimizing
random-selected parts of program.


It's an assumption that you are making.


what you want to buy with continuations and, more important, why you
need it?


To try to implement thread priorities. I would like to use  
continuations instead of threads and pick the next continuation to  
run based on how much time it has to responde to the poker server.


JR Alternatively, I would appreciate an example that requests,  
say, two

JR Ints by saving a continuation each time and returns the sum.

do a - readLn :: IO Int
   b - readLn :: IO Int
   return (a+b)

[...]

amazed? :)


Amused yes, amazed no. The code does not save a continuation after  
requesting each integer and does not allow me to call/cc it saved  
continuation with an integer of my choice.


This is pretty much what I'm looking for: http://lisp.tech.coop/Web% 
2FContinuation


Thanks, Joel

--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Substring replacements

2005-12-23 Thread Daniel Fischer
Hello Bulat,

I'm not sure what your point is, let's try to enlighten me.

Am Mittwoch, 21. Dezember 2005 16:30 schrieben Sie:
 Hello Daniel,

 Wednesday, December 21, 2005, 5:20:18 PM, you wrote:

 DF ordinarily, on my computer, your version of straightforward is 10-15%
 faster DF than KMP (search-patterns are now supplied on the command line
 -- which has DF no big impact;

 of course. the search pattern can be compiled into the search
 algorithm just at the time of program execution. just for example, if
 you have code

 main = do [x] - getArgs
   y - return $ map (\n - fac $ read x) [1..10^6]

 then `fac $ read x` will be computed just one time. in this time, if
 your perform many searches with the same pattern - compiler must
 initialize array just one time and use it for all searches

Errrh, what here? If I want to replace each occurence of a pattern within a 
String, of course I want the arrays built only once, destroying and 
rebuilding them would be deliberate stupidity, that can't be your point, 
certainly. And also if we interactively search and replace, as in an editor, 
we'd hold on to the arrays until we get the message 'no more of that, next 
pattern'.


 DF searched string is  able sea...; all compiled with -O2;
 DF NOINLINE makes no difference -- at least with optimisations on --

 why? i think that is the right way to check speed of optimized program
 without pre-compiling search pattern to search/replace algorithm at
 runtime
? What has NOINLINE to do with precompiling the search pattern?
BTW, I think, the KMP-algorithm is too large to be inlined anyway (maybe, if 
we explicitly asked for it), so I wouldn't expect any NOINLINE-effect in the 
first place.

And about RunTimeCompilation, I don't quite understand the Wiki-page, what I 
imagined might be the point there is that, if I know the search pattern 
before, I might import the general algorithm, write a function
searchReplacePattern = searchReplace pattern
and the arrays might then be built at compile-time and included in the object 
code -- but I've no idea whether compilers are clever enough to do that (I 
believe it should be possible to write compilers which would do that, but is 
it worth the trouble -- or is that sort of optimisation easy and routinely 
done?) -- but why that would be called RunTimeCompilation, I cannot imagine.
So then, the thing that might make a difference, would be not to give the 
search pattern at compile-time, which I did. Of course, since we search a 
long String, the time needed to build the arrays is minute in relation to the 
time needed to traverse the String, but in the more realistic situation of a 
shorter String (50 kB instead of 48 MB), it would be significant.

 DF ; without optimisations, KMP suffers far worse than straightforward).

 this test is meaningless

Well, it's not really a test for the algorithm, but for ghc's optimiser and 
I've forgotten the exact numbers, but KMP compiled without optimisation is 
much much, much slower than with -O2, so the optimiser does a really great 
job.

  KMP is O(m) while straightforward is O(m*n).

 DF Where m is the length of the input and n is the length of the
 searched-for DF pattern, I think?
 DF But these are worst-case complexities, I believe, ordinarily,
 straightforward DF will be O(m), too.

 and have longer init time (and take more space), so on typical
 searches it will be worser than trivial algorithm

I believe you've misread here. I'm saying that while the worst case complexity 
for the straighforward (or trivial) algorithm is O(n*m) -- as witnessed by my 
test, which was deliberately designed to be bad for that --, usually, in 
most real situations, that will have O(m) complexity, too.
And I -- like you -- believe that for typical searches the straightforward 
algorithm will be faster (at least with a clever implementation, like yours).

Cheers,
Daniel

P.S.: I'd really appreciate another attempt at explaining RunTimeCompilation 
to me (might well be an URL of a paper or something).

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


Re: [Haskell-cafe] Optimization help needed

2005-12-23 Thread Bulat Ziganshin
Hello Joel,

Thursday, December 22, 2005, 7:27:17 PM, you wrote:
JR #ifdef BIG_ENDIAN
JR swap16 v = (v `shiftR` 8) .|. (v  `shiftL` 8)
JR #else
JR swap16 v = v
JR #endif

afaik, your code anyway will not work on non-x86 architectures,
because your `storable` definition use unaligned reads which are not
supported outside x86 world


and about :+: - read Derivable type classes
[http://research.microsoft.com/~simonpj/Papers/derive.ps.gz]; and
7.11. Generic classes of ghc manual

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] exuberant-ctags, haskell, vim, tlist plugin

2005-12-23 Thread Claus Reinke

Claus: I've now patched the tlist plugin to use hasktags distributed
with ghc.. But exuberant-ctags also adds a character as tag description
(e.g f for function c for class) which hasktags doesn't.


I wasn't talking about hasktags (which I found somewhat limited
last time I tried), but about ghci's :ctags/:etags (I think those are the
command names now, it is :tags in my version). I guess tag descriptions
could be added, as long as they fit somewhere into the comment format
of tags files.. of course it would be even nicer to ask ghc interactively
about haskell-specific information, just as the visualstudio plugin does.

but as long as things work for you now..

cheers,
claus

ps: happy holidays everyone!-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell Speed

2005-12-23 Thread Daniel Carrera

Hi all,

I'm taking a look at the Computer Language Shootout Benchmarks.

http://shootout.alioth.debian.org/

It looks like Haskell doesn't do very well. It seems to be near the 
bottom of the pile in most tests. Is this due to the inherent design of 
Haskell or is it merely the fact that GHC is young and hasn't had as 
much time to optimize as other compilers?


For example, another very slow language is Ruby. In Ruby's case, there 
is a design factor that will always make it slow. I wonder if Haskell is 
in a smilar situation.


Yes yes, I know that a high level language trades CPU time by programmer 
time. I'm still interested in the CPU time question though :)


Cheers,
Daniel.
--
 /\/`) http://oooauthors.org
/\/_/  http://opendocumentfellowship.org
   /\/_/
   \/_/I am not over-weight, I am under-tall.
   /
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe