[Haskell-cafe] How to use Control.Failure?

2009-12-19 Thread ntupel
I have looked at the recently released Control.Failure library but I
admit, I couldn't understand it completely. So given the example
below, how would Control.Failure help me here?

Thanks,
nt


-- Theirs (other library code stubs)
data TheirError = TheirErrorCase deriving Show
data TheirData  = TheirData deriving Show

theirFunc :: [String] - Either TheirError TheirData
theirFunc = undefined


-- Mine (my own code stubs)
data MyError = MyErrorCase deriving Show
data MyData  = MyData deriving Show

myFuncA :: TheirData - Either MyError MyData
myFuncA = undefined


-- Ugly. How to apply Control.Failure here?
myFuncB :: IO (Either MyError MyData)
myFuncB = do
let x = theirFunc []
case x of
Right x' - return $ myFuncA x'
Left  _  - return . Left $ MyErrorCase
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: How to use Control.Failure?

2009-12-19 Thread ntupel
On Dec 19, 5:14 pm, Michael Snoyman mich...@snoyman.com wrote:

 Well, here's one way of doing it. You have lots of choices here; these are
 the decisions I made in implementing the code:

 * myFuncB no longer lives in the IO monad. I wasn't sure if you specifically
 wanted that, but now it can work with *any* instance of Failure.
 * Since I assumed you ultimately wanted it to land in the IO monad, I
 defined Exception instances. However, if you were dealing with a different
 Failure instance (like [] or Maybe), these would be unncesary.
 * I also assume that what you meant by your code and their code is that
 you can modify your own code, but not theirs.

 If you show me what the real code is you're working on, I'd be happy to more
 fully develop a better solution with you. Anyway, here's the code.

Thank you very much. This helped a lot. I wasn't aware of many of the
details you showed me now, such as deriving from Typeable. The
assumptions you have made w.r.t to what I want to write all make sense
and I guess I can experiment with Control.Failure a little better now.

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


Re: [Haskell-cafe] How to implement this? A case for scoped record labels?

2009-05-27 Thread ntupel
On Tue, 2009-05-26 at 18:09 -0400, wren ng thornton wrote:
 GADTs can easily cover record selectors that apply to all constructors, 
 and selectors that apply to one constructor (or a set of constructors 
 producing the same type). If the family of selector sets forms a nice 
 tree hierarchy, you can use phantom type constructors and type variables 
 to express subtrees of that hierarchy as types, e.g.
[...]
 I don't know if the Bayeaux protocol is amenable to this or not. And I'm 
 sure there's a prettier way to do it anyhow.
 
 By using multiple phantom types you can encode any subset relation on 
 selector sets that can be described by a tree-ordered space. If the 
 subset relation is DAGy, then things get ugly again. You'll probably 
 have to use typeclasses in some form or another eventually, the question 
 is how much you rely on ad-hoc overloading vs how structured you can 
 make things by using other techniques.

Finally I got your point. Many thanks for your explanation. So, yes, in
principle GADTs seem helpful here, but it turned out that for Bayeux the
relations are difficult to encode and it seems I would indeed at least
partially have to use type classes again. It really is fascinating, I
learned a lot in the last days about GADTs, type families, and other
type trickery. Never mind that I still struggle to see an obvious
implementation strategy, all proposed solutions look like workarounds to
the lack of scoped record labels to me. Maybe I should just use prefixes
for the record selectors of individual data types. D'oh!

Thanks,
nt



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


Re: [Haskell-cafe] How to implement this? A case for scoped record labels?

2009-05-26 Thread ntupel
On Tue, May 26, 2009 at 4:32 AM, wren ng thornton w...@freegeek.org wrote:
 One alternative is to use Haskell's support for ad-hoc overloading. Define a
 typeclass for each selector (or group of selectors that must always occur
 together) which is polymorphic in the record type. [...]
 It's not pretty, but it gets the job done. Many people decry this as
 improper use of typeclasses though (and rightly so).

Yes. I was experimenting a little with type classes and the more
granular I defined them the more I got the feeling of producing a
hack. But as you said, it would get the job done and I will probably
give it a try.

 A better approach would
 probably be to use GADTs or the new data families which give a sort of dual
 of typeclasses (typeclasses give a small set of functions for a large set of
 types; GADTs give a large set of functions for a small set of types[0]).
 Someone more familiar with those approaches should give those versions.

Interesting, but I fail to see how this might be applied to the
problem at hand. I played with associated types and they are quite
neat. But I would still be working with type classes, so how would
this be different from the first approach. W.r.t. GADTs I understood
these as to provide a way to be more specific about the return type of
constructor functions. But my problem is mostly a scope issue, isn't
it?

 If you want to be able to set the fields as well as read them then the
 classes should be more like lenses than projectors.

I am fine with selectors for now. But thanks for the references.

 Also take a look at hptotoc[4],
 the Haskell implementation of Google's Protocol Buffers which has many
 similar problems to your Bayeaux protocol. In general, protocols designed
 for OO are difficult to translate into non-OO languages.

From what I saw by briefly scanning the contents it seems to me the
problem is again solved with the type class approach you mentioned in
the beginning.

I wonder if I am completely off here, but I am surprised that there is
no progress on the scoped labels front. The Haskell wiki mentioned
that the status quo is due to a missing optimum in the design space,
but the same can be said about generic programming in Haskell and yet,
GHC ships with Scrap your boilerplate. So we have to resort to type
classes hacks instead of a proper solution. OTOH I might not have
understood the relevance of GADTs for this problem and it is a
non-issue but prima facie it doesn't seem to be.

Anyway, many thanks for your thoughtful reply.

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


[Haskell-cafe] How to implement this? A case for scoped record labels?

2009-05-25 Thread ntupel
Hi,

I would like to get some advice on how to best implement a protocol.
The protocol in question is Bayeux:
http://svn.cometd.org/trunk/bayeux/bayeux.html. The details don't
matter here - it defines a couple of requests and responses in JSON
format, basically JSON objects with different properties, some of
which are shared by all (e.g. channel) and some which are specific
for certain kinds of requests/responses (e.g. subscription). To give
an example, a connect request would look like this:

[
  {
 channel: /meta/connect,
 clientId: Un1q31d3nt1f13r,
 connectionType: long-polling
   }
]


Now I leave the actual JSON parsing to the excellent Text.JSON
library. My problem is how to get the types right.

At first I started with a big discriminated union, e.g.

data BayeuxMessage = HandshakeRequest { channel :: String , ... }
 | HandshakeResponse { channel :: String, successful :: Bool, ... }
 | ...

This way I could create BayeuxMessage values by copying the Text.JSON
parsed values over. However what I don't like is that many selector
functions, e.g. successful, are only partial and using them with a
BayeuxMessage value constructed with HandshakeRequest for example will
result in a runtime error. So I think it would be better to have
individual types for the protocol requests/responses, e.g.

data HandshakeRequest = HandshakeRequest { channel :: String , ... }
data HandshakeResponse = HandshakeResponse { channel :: String,
successful :: Bool, ... }
...

data BayeuxMessage = HSReq HandshakeRequest
| HSRes HandshakeResponse
...

This however does not work because record selectors have module scope,
so the compiler will complain that channel et. al. are defined
multiple times. As a workaround I could put each type into its own
module, but at least GHC requires a file per module (which is *very*
inconvenient IMO). If we would have scoped labels (e.g. like proposed
here: http://legacy.cs.uu.nl/daan/pubs.html#scopedlabels) it seems
like it would have been straightforward.

So certainly I am missing something and there is a better way to
design this. Hence this e-mail. I welcome any advice how this would
best be done in Haskell with GHC.

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


[Haskell-cafe] JSON serialization/deserialization

2008-09-12 Thread ntupel
Dear list members,

I try to use Text.JSON
(http://hackage.haskell.org/cgi-bin/hackage-scripts/package/json) to
serialize and deserialize record types. As I understand it, the data
types need to be instances of class JSON. However I have difficulties
to come up with a nice implementation of showJSON and readJSON. For
example:


module Test where

import Text.JSON

data Record =
One {
field1 :: String,
field2 :: String }
  | Two {
field :: String } deriving (Eq, Ord, Show, Read)

showJSON (One x y) = toJSObject [(field1, x), (field2, y)]
showJSON (Two x)   = toJSObject [(field, x)]

readJSON x = -- ???

This lacks the instance declaration itself but my problem is more
fundamental. How can I write the readJSON method? In general how would
one approach the problem of serialization/deserialization? I am
puzzled that the type classes Show and Read can be derived
automatically. I can not think of any way to do this.

Thanks for your help!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Text.JSON idiomatic use

2008-09-12 Thread ntupel
As a follow up to my previous JSON serialization post I came up with a
first draft of some simple record type serialization/deserialization. 

What I would like to know is, whether this is the right approach or what
better ways there are to make a custom data type an instance of class
JSON. Any chance to reduce the amount of boilerplate required to do
this? I would be grateful for any feedback (also general style comments
are much appreciated).

Many thanks!




module Test where

import Text.JSON

data Message =
Error {
event   :: String,
channel :: String,
id  :: String,
cause   :: String,
message :: String}
  | Join {
event   :: String,
channel :: String,
id  :: String,
name:: String}
  | Leave {
event   :: String,
channel :: String,
id  :: String,
really  :: Bool}
  deriving (Eq, Show, Read)

asJSString :: String - JSValue
asJSString = JSString . toJSString

asString :: JSValue - String
asString (JSString s) = fromJSString s

asBool :: JSValue - Bool
asBool (JSBool b) = b


showErrorJSON, showJoinJSON, showLeaveJSON :: Message - JSValue

showErrorJSON (Test.Error evt cha id cau msg) =
showJSON $ toJSObject [(event, evt), (channel, cha), (id, id), 
(cause, cau), (message, msg)]

showJoinJSON (Join evt cha id nme) =
showJSON $ toJSObject [(event, evt), (channel, cha), (id, id), 
(name, nme)]

showLeaveJSON (Leave evt cha id rly) =
showJSON $ toJSObject [(event, asJSString evt), (channel, asJSString 
cha), (id, asJSString id), (really, JSBool rly)]


createMessage, readErrorJSON, readJoinJSON, readLeaveJSON :: [(String, 
JSValue)] - Maybe Message

readErrorJSON xs = do
evt - lookup event xs
cha - lookup channel xs
id  - lookup id xs
cau - lookup cause xs
msg - lookup message xs
Just (Test.Error (asString evt) (asString cha) (asString id) (asString cau) 
(asString msg))

readJoinJSON xs = do
evt - lookup event xs
cha - lookup channel xs
id  - lookup id xs
nme - lookup name xs
Just (Join (asString evt) (asString cha) (asString id) (asString nme))

readLeaveJSON xs = do
evt - lookup event xs
cha - lookup channel xs
id  - lookup id xs
rly - lookup really xs
Just (Leave (asString evt) (asString cha) (asString id) (asBool rly))

createMessage obj = do
evt - lookup event obj
case asString evt of
/error  - readErrorJSON obj
/me/add - readJoinJSON obj
/me/remove - readLeaveJSON obj
_ - Nothing

instance JSON Message where
showJSON x@(Test.Join_ _ _ _) = showJoinJSON x
showJSON x@(Test.Leave   _ _ _ _) = showLeaveJSON x
showJSON x@(Test.Error _ _ _ _ _) = showErrorJSON x

readJSON (JSObject o) = 
case createMessage . fromJSObject $ o of
Just m  - Ok m
Nothing - Text.JSON.Error Parsing failed.

readJSON _ = Text.JSON.Error Records must be JSObjects


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


Re: [Haskell-cafe] Performance problem with random numbers

2007-10-17 Thread ntupel
On Sat, 2007-10-13 at 18:33 -0300, Isaac Dupree wrote:
 GHC StdGen's random and randomR are somewhat slow.  I found that 
 changing to a custom ((x*a + b) `mod` c) random-generator (instance of 
 RandomGen) much sped things up (since nothing depended on the random 
 numbers being good quality).

Yes, I also switched now to a simple custom linear congruential
generator (which is random enough for this task) and restructured the
code a bit and am happy now since it is even a bit faster than the Java
implementation :)

Thanks,
Thoralf


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


Re: Laziness (was: [Haskell-cafe] Performance problem with random numbers)

2007-10-15 Thread ntupel
On Mon, 2007-10-15 at 10:48 -0400, David Roundy wrote:
 I have no idea if this example will help your actual code, but it
 illustrates that at least in this example, it's pretty easy to gain an
 order of magnitude in speed.  (That func is a weird function, by the
 way.)
 

Thanks for your reply David,

Unfortunately my original problem was that System.Random.{random,
randomR} is used instead of all these weird test functions that I came
up with during experimentation. And I can't force anything inside StdGen
so I see no way of speeding up the original program sans replacing the
random number generator itself. When I did that I became about 4 times
faster than with System.Random but still an order of magnitude slower
than for instance by using the Java implementation (and I can confirm
that (^) is *very* expensive in this context).

Many thanks again,
Thoralf





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


Laziness (was: [Haskell-cafe] Performance problem with random numbers)

2007-10-14 Thread ntupel
On Sat, 2007-10-13 at 09:56 -0400, Brandon S. Allbery KF8NH wrote:
 Now you need to start forcing things; given laziness, things tend to  
 only get forced when in IO, which leads to time being accounted to  
 the routine where the forcing happened.  If random / randomR are  
 invoked with large unevaluated thunks, their forcing will generally  
 be attributed to them, not to functions within the thunks.
 
 (Yes, this means profiling lazy programs is a bit of a black art.)

After more testing I finally realized how right you are. It appears that
my problem is not related to random/randomR but only to laziness. I came
up with a test that doesn't use random numbers at all and still needs
about 2.5 seconds to complete (it is really just meaningless
computations):


module Main where

import Data.List

main :: IO ()
main = do let n = 100 :: Int
  print $ foldl' (\x y - seq y x) 0 (take n $ test 1 [1,2..])

test :: Int - [Int] - [Int]
test t g =
let (n, g') = next t g
in 
n:test t g'

next :: Int - [Int] - (Int, [Int])
next x (y:ys) =
let n = func y
in
if n = 0.5 then (x, ys) else (0, ys)
where
func x = fromIntegral x / (10 ^ len x)
where
len 0 = 0
len n = 1 + len (n `div` 10)


Now my problem still is, that I don't know how to speed things up. I
tried putting seq and $! at various places with no apparent improvement.
Maybe I need to find a different data structure for my random module and
lazy lists are simply not working well enough here?

Thanks,
Thoralf


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


Re: [Haskell-cafe] Performance problem with random numbers

2007-10-13 Thread ntupel
On Fri, 2007-10-12 at 20:25 -0700, Stefan O'Rear wrote:
 On Sat, Oct 13, 2007 at 12:09:57AM +0200, ntupel wrote:
  setup :: (Ord a, IArray a2 a, IArray a1 e, Num a) = [e] - [a] - (a1 Int 
  e, a1 Int e, a2 Int a)
  calcAlias :: (Ord e, Num e, IArray a e, Ix i, IArray a2 e1, IArray a1 e1) 
  = a2 i e1 - a1 i e1 - a i e - [i] - [i] - (a1 i e1, a i e)
  next :: (IArray a2 e1, IArray a e1, Ord e, IArray a1 e, RandomGen t, Random 
  e) = (a Int e1, a2 Int e1, a1 Int e) - t - (e1, t)
  randomList :: (Random e, RandomGen t1, IArray a2 e, Ord e, IArray a t, 
  IArray a1 t) = (a Int t, a1 Int t, a2 Int e) - t1 - [t]
 
...
 I would try specializing to StdGen, UArray, and Int, for RandomGen,
 IArray, and Random respectively.


Thanks for your reply Stefan. Unfortunately I could measure only a
relatively small improvement by changing to concrete types, e.g. using

setup :: [a] - [Double] - (Array Int a, Array Int a, UArray Int
Double)

calcAlias :: Array Int a - Array Int a - UArray Int Double - [Int] -
[Int] - (Array Int a, UArray Int Double)

next :: (Array Int a, Array Int a, UArray Int Double) - StdGen - (a,
StdGen)

randomList :: (Array Int a, Array Int a, UArray Int Double) - StdGen -
[a]

the sample code was about one second faster when compiled with -O2.
Profiling again indicated that most time was spend in random and randomR
(I manually added cost centers into next):

   main +RTS -p -RTS

total time  =8.00 secs   (160 ticks @ 50 ms)
total alloc = 2,430,585,728 bytes  (excludes profiling overheads)

COST CENTREMODULE   %time %alloc

random Random60.0   54.5
randomRRandom20.0   23.3
next   Random17.5   17.0
main   Main   1.92.5
randomList Random 0.62.8


previously (i.e. with long class contexts) it looked like this:


   main +RTS -p -RTS

total time  =7.85 secs   (157 ticks @ 50 ms)
total alloc = 2,442,579,716 bytes  (excludes profiling overheads)

COST CENTREMODULE   %time %alloc

random Random58.6   54.5
randomRRandom22.9   23.3
next   Random14.6   16.5
main   Main   2.52.5
randomList Random 1.33.1


Many thanks again,
Thoralf


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


Re: [Haskell-cafe] Performance problem with random numbers

2007-10-13 Thread ntupel
On Sat, 2007-10-13 at 09:56 -0400, Brandon S. Allbery KF8NH wrote:
 Now you need to start forcing things; given laziness, things tend to  
 only get forced when in IO, which leads to time being accounted to  
 the routine where the forcing happened.  If random / randomR are  
 invoked with large unevaluated thunks, their forcing will generally  
 be attributed to them, not to functions within the thunks.

But AFAIK random and randomR only take a StdGen (plus a range argument
in case of randomR) as argument so I don't understand where the
unevaluated thunks might be actually? (Maybe I should have said that
random and randomR are the ones from GHC's System.Random module.)

Thanks,
Thoralf


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


Re: [Haskell-cafe] Performance problem with random numbers

2007-10-13 Thread ntupel
On Sat, 2007-10-13 at 12:42 -0400, Brandon S. Allbery KF8NH wrote:
 Your apparently simple StdGen argument is actually a sort of program  
 state (represented by unevaluated thunks, not by a state monad; see  
 below) which gets altered with every invocation of random.  If  
 nothing is forced until the very end, it in effect becomes an  
 expression which produces the desired StdGen, with the uses of the  
 previous StdGen values as side effects of its computation that  
 occur when the thunk is evaluated at the end.  I'm not sure I'm up to  
 working through an example of what this looks like.

Thanks Brandon. I understand your argument but I don't know how to put
it into practice, i.e. how to force the evaluation of StdGen.

- Thoralf


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


Re: [Haskell-cafe] Performance problem with random numbers

2007-10-13 Thread ntupel
On Sat, 2007-10-13 at 13:35 -0400, Brandon S. Allbery KF8NH wrote:
 For starters, look into seq. Try applying it to any expression  
 using a generated random number.  This should force evaluation to  
 occur somewhere other than when random is trying to figure out what  
 StdGen value it's been told to use as its initial state.
 

Ok, but I still wonder where that might be. random and randomR are used
in a function named next as show here:

next :: (Array Int a, Array Int a, UArray Int Double) - StdGen - (a,
StdGen)
next (xs, as, rs) g =
let n = length $ indices xs
(x1, g1) = randomR (0, n - 1) g
(x2, g2) = random g1
r = rs!x1
in
if x2 = r 
then (xs!x1, g2) 
else (as!x1, g2)


x1 and x2 are used in the same function so I assume this already
requires their evaluation. The only function that calls next is
randomList:

randomList :: (Array Int a, Array Int a, UArray Int Double) - StdGen -
[a]
randomList t g = 
let (n, g') = next t g
in 
n:randomList t g'

Cf. my original e-mail for the complete program. 

 Alternately you can put all the uses in IO and use  
 Control.Exception.evaluate (or even print).  This is probably not  
 what you want to do in your actual production code, however.
 

Right. This is not what I want.

Many thanks again,
Thoralf


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


Re: [Haskell-cafe] Performance problem with random numbers

2007-10-13 Thread ntupel
On Sat, 2007-10-13 at 14:37 -0700, Don Stewart wrote:
 I've seen similar results switching to the SIMD mersenne twister C
 implementation for randoms:
 
 http://www.math.sci.hiroshima-u.ac.jp/~m-mat/MT/SFMT/index.html
 
 If there's interest, I can package up the bindings for hackage.
 

I would definitely be interested.

Many thanks,
Thoralf


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


[Haskell-cafe] Performance problem with random numbers

2007-10-12 Thread ntupel
Dear all,

I have implemented a small module to generate random items with a given
probability distribution using the alias approach [1] and unfortunately
compared to similar implementations in C++ or Java it is about 10 times
slower. I have to confess that I am still in the early stages of writing
Haskell programs so there is hopefully something I can do about it and I
hope some helpful soul on this list can give me a hint. 

I have attached my implementation and a small testing routine which runs
in about 5 seconds on my machine (when compiled with -O2) whereas my
Java-Implementation finishes in about 0.48 seconds. Profiling indicates
that the time is mostly spend in System.Random.random and
System.Random.randomR so I wonder if these are slow or what else might
cause the relative slowness of my implementation.

Many thanks for your responses,
Thoralf

PS: I would also appreciate any feedback about the module from a design
perspective. I bet I miss lots of good Haskell idioms.


[1] The alias methods moves probability mass of a non-uniform
probability distribution around to create a uniform distribution. Lets
say you have three items a, b, and c with distribution [0.2, 0.1,
0.7] then a uniform distribution would assign 1/3 to each so a and b
need to be filled up with exactly the same probability mass that c
has too much. Then 2 uniform random numbers are generated. The first one
to pick an item and the second one to pick either the item itself if the
value is in the original part or the alias otherwise. A much better
explanation can be found on the web somewhere. Anyway it should not
matter with regards to the performance problem I have.
module Main where

import Random
import System.Random
import Data.Array
import Data.List


main = do g - getStdGen
  let k = [a, b, c]
  n = 100 :: Int
  t = setup k [0.2, 0.1, 0.7] :: (Array Int String, Array Int String, Array Int Double)
  print $ foldl' (\a b - if b == b then a + 1 else a) 0 (take n $ randomList t g) / fromIntegral n

module Random (setup, next, randomList) where

import System.Random hiding (next)
import Data.Array.IArray


-- Given a list of items and a list of their propabilities generate a tripel
-- consisting of the values vector, the alias vector and the relative propabilities
-- vector which is used in applications of next, etc.
setup :: (Ord a, IArray a2 a, IArray a1 e, Num a) = [e] - [a] - (a1 Int e, a1 Int e, a2 Int a)
setup xs ps = 
let n  = length ps
xv = listArray (0, n - 1) xs
rv = listArray (0, n - 1) [fromIntegral n * p | p - ps]
(low, high) = splitAt 1 rv (indices rv) [] []
(a, r) = calcAlias xv xv rv high low
in
(xv, a, r)
where
-- Return a pair of lists, the first consisting of elements lower than
-- given threshold and the second with elements greater than threshold,
-- equal elements are ignored.
splitAt t v [] l h = (l, h)
splitAt t v (i:is) l h = case v!i of
x | x  t - splitAt t v is (i:l) h
  | x  t - splitAt t v is l (i:h)
  | otherwise - splitAt t v is l h


-- Given an list of highs and a list of lows, calculate the alias vector and the relative
-- propabilities vector.
calcAlias :: (Ord e, Num e, IArray a e, Ix i, IArray a2 e1, IArray a1 e1) = a2 i e1 - a1 i e1 - a i e - [i] - [i] - (a1 i e1, a i e)
calcAlias xv av rv []_  = (av, rv)
calcAlias xv av rv _ [] = (av, rv)
calcAlias xv av rv hi@(h:hs) (l:ls) =
let av' = av//[(l, xv!h)]
rv' = rv//[(h, rv!h + rv!l - 1)]
in
if rv'!h = 1
then calcAlias xv av' rv' hi ls
else calcAlias xv av' rv' hs (h:ls)


-- Generate a random item according to the given propability distribution as specified
-- by the given tripel which is the result of applying setup to a list of items and
-- a list of propabilities.
next :: (IArray a2 e1, IArray a e1, Ord e, IArray a1 e, RandomGen t, Random e) = (a Int e1, a2 Int e1, a1 Int e) - t - (e1, t)
next (xs, as, rs) g =
let n = length $ indices xs
(x1, g1) = randomR (0, n - 1) g
(x2, g2) = random g1
r = rs!x1
in
if x2 = r 
then (xs!x1, g2) 
else (as!x1, g2)


-- Generate a infinite list of random items according to the specified propability
-- distribution as given by the triple that results from applying setup to a pair
-- of a list of items and a list of propabilities (see setup for details).
randomList :: (Random e, RandomGen t1, IArray a2 e, Ord e, IArray a t, IArray a1 t) = (a Int t, a1 Int t, a2 Int e) - t1 - [t]
randomList t g = 
let (n, g') = next t g 
in 
n:randomList t g'

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