Re: [Haskell-cafe] Extension for "Pearls of Functional Algorithm Design" by Richard Bird, 2010, page 25 #Haskell

2011-05-20 Thread Daniel Peebles
Do you have some sort of link aggregator that auto-posts to haskell-cafe?

On Sat, May 21, 2011 at 12:09 AM, KC  wrote:

> Extension for "Pearls of Functional Algorithm Design" by Richard Bird,
> 2010, page 25 #Haskell
>
>
> ---
>
> ---
>
> module SelectionProblem where
>
> import Data.Array
> import Data.List
>
>
>
> ---
>
> ---
>
> -- Question: is there a way to get the type signature as the following:
> -- smallest :: (Ord a) => Int -> [Array Int a] -> a
>
>
> ---
>
> ---
>
>
> -- Works on 2 finite ordered disjoint sets represented as sorted arrays.
> smallest :: (Ord a) => Int -> (Array Int a, Array Int a) -> a
> smallest k (xa,ya) =
>search k (xa,ya) (0,m+1) (0,n+1)
>where
>(0,m) = bounds xa
>(0,n) = bounds ya
>
>
> -- Removed some of the "indexitis" at the cost of calling another function.
> search :: (Ord a) => Int -> (Array Int a, Array Int a) -> (Int,Int) ->
> (Int,Int) -> a
> search k (xa,ya) (lx,rx) (ly,ry)
>| lx == rx  = ya ! (k+ly)
>| ly == ry  = xa ! (k+lx)
>| otherwise = case (xa ! mx < ya ! my) of
>  (True)-> smallest2h k (xa,ya)
> ((lx,mx,rx),(ly,my,ry))
>  (False)   -> smallest2h k (ya,xa)
> ((ly,my,ry),(lx,mx,rx))
>  where
>  mx = (lx+rx) `div` 2
>  my = (ly+ry) `div` 2
>
>
> -- Here the sorted arrays are in order by their middle elements.
> -- Only cutting the leading or trailing array by half.
>
> -- Here xa is the first array and ya the second array by their middle
> elements.
>
> smallest2h :: (Ord a) => Int -> (Array Int a, Array Int a) ->
> ((Int,Int,Int),(Int,Int,Int)) -> a
> smallest2h k (xa,ya) ((lx,mx,rx),(ly,my,ry)) =
>case (k<=mx-lx+my-ly) of
>  (True)-> search k (xa,ya) (lx,rx) (ly,my)
>  (False)   -> search (k-(mx-lx)-1) (xa,ya) (mx+1,rx) (ly,ry)
>
>
>
> ---
>
> ---
>
> -- Works on 3 finite ordered disjoint sets represented as sorted arrays.
>
> smallest3 :: (Ord a) => Int -> (Array Int a, Array Int a, Array Int a) -> a
> smallest3 k (xa,ya,za) =
>-- On each recursive call the order of the arrays can switch.
>search3 k (xa,ya,za) (0,bx+1) (0,by+1) (0,bz+1)
>where
>(0,bx) = bounds xa
>(0,by) = bounds ya
>(0,bz) = bounds za
>
>
> -- Removed some of the "indexitis" at the cost of calling another function.
> search3 :: (Ord a) => Int -> (Array Int a, Array Int a, Array Int a) ->
>(Int,Int) -> (Int,Int) -> (Int,Int) -> a
> search3 k (xa,ya,za) (lx,rx) (ly,ry) (lz,rz)
>| lx == rx && ly == ry  = za ! (k+lz)
>| ly == ry && lz == rz  = xa ! (k+lx)
>| lx == rx && lz == rz  = ya ! (k+ly)
>
>| lx == rx  = search k (ya,za) (ly,ry) (lz,rz)
>| ly == ry  = search k (xa,za) (lx,rx) (lz,rz)
>| lz == rz  = search k (xa,ya) (lx,rx) (ly,ry)
>
>| otherwise = case (xa ! mx < ya ! my, xa ! mx < za ! mz, ya ! my
> < za ! mz) of
>  (True, True, True)-> smallest3h k (xa,ya,za)
> ((lx,mx,rx),(ly,my,ry),(lz,mz,rz)) -- a  (True, True, False)   -> smallest3h k (xa,za,ya)
> ((lx,mx,rx),(lz,mz,rz),(ly,my,ry)) -- a  (False, True, True)   -> smallest3h k (ya,xa,za)
> ((ly,my,ry),(lx,mx,rx),(lz,mz,rz)) -- b  (False, False, True)  -> smallest3h k (ya,za,xa)
> ((ly,my,ry),(lz,mz,rz),(lx,mx,rx)) -- b  (True, False, False)  -> smallest3h k (za,xa,ya)
> ((lz,mz,rz),(lx,mx,rx),(ly,my,ry)) -- c  (False, False, False) -> smallest3h k (za,ya,xa)
> ((lz,mz,rz),(ly,my,ry),(lx,mx,rx)) -- c
>  where
>  mx = (lx+rx) `div` 2
>  my = (ly+ry) `div` 2
>  mz = (lz+rz) `div` 2
>
>
> -- Here the sorted arrays are in order by their middle elements.
> -- Only cutting the leading or trailing array by half.
>
> -- Here xa is the first array, ya the second array, and za the third
> array by their middle elements.
> smallest3h :: (Ord a) => Int -> (Array Int a, Array Int a, Array Int a) ->
>((Int,Int,Int),(Int,Int,Int),(Int,Int,Int)) -> a
> smallest3h k (xa,ya,za) ((lx,mx,rx),(ly,my,ry),(lz,mz,rz)) =
>case (k<=mx-lx+my-ly+mz-lz) of
>  (True)-> search3 k (xa,ya,za) (lx,rx) (ly,ry) (lz,mz)
>  (False)   -> search3 (k-(mx-lx)-1) (xa,ya,za) (mx+1,rx) (ly,ry)
> (lz,rz)
>
>
>
>
> --
> --
> Regar

[Haskell-cafe] Extension for "Pearls of Functional Algorithm Design" by Richard Bird, 2010, page 25 #Haskell

2011-05-20 Thread KC
Extension for "Pearls of Functional Algorithm Design" by Richard Bird,
2010, page 25 #Haskell

---
---

module SelectionProblem where

import Data.Array
import Data.List


---
---

-- Question: is there a way to get the type signature as the following:
-- smallest :: (Ord a) => Int -> [Array Int a] -> a

---
---


-- Works on 2 finite ordered disjoint sets represented as sorted arrays.
smallest :: (Ord a) => Int -> (Array Int a, Array Int a) -> a
smallest k (xa,ya) =
search k (xa,ya) (0,m+1) (0,n+1)
where
(0,m) = bounds xa
(0,n) = bounds ya


-- Removed some of the "indexitis" at the cost of calling another function.
search :: (Ord a) => Int -> (Array Int a, Array Int a) -> (Int,Int) ->
(Int,Int) -> a
search k (xa,ya) (lx,rx) (ly,ry)
| lx == rx  = ya ! (k+ly)
| ly == ry  = xa ! (k+lx)
| otherwise = case (xa ! mx < ya ! my) of
  (True)-> smallest2h k (xa,ya) ((lx,mx,rx),(ly,my,ry))
  (False)   -> smallest2h k (ya,xa) ((ly,my,ry),(lx,mx,rx))
  where
  mx = (lx+rx) `div` 2
  my = (ly+ry) `div` 2


-- Here the sorted arrays are in order by their middle elements.
-- Only cutting the leading or trailing array by half.

-- Here xa is the first array and ya the second array by their middle elements.

smallest2h :: (Ord a) => Int -> (Array Int a, Array Int a) ->
((Int,Int,Int),(Int,Int,Int)) -> a
smallest2h k (xa,ya) ((lx,mx,rx),(ly,my,ry)) =
case (k<=mx-lx+my-ly) of
  (True)-> search k (xa,ya) (lx,rx) (ly,my)
  (False)   -> search (k-(mx-lx)-1) (xa,ya) (mx+1,rx) (ly,ry)


---
---

-- Works on 3 finite ordered disjoint sets represented as sorted arrays.

smallest3 :: (Ord a) => Int -> (Array Int a, Array Int a, Array Int a) -> a
smallest3 k (xa,ya,za) =
-- On each recursive call the order of the arrays can switch.
search3 k (xa,ya,za) (0,bx+1) (0,by+1) (0,bz+1)
where
(0,bx) = bounds xa
(0,by) = bounds ya
(0,bz) = bounds za


-- Removed some of the "indexitis" at the cost of calling another function.
search3 :: (Ord a) => Int -> (Array Int a, Array Int a, Array Int a) ->
(Int,Int) -> (Int,Int) -> (Int,Int) -> a
search3 k (xa,ya,za) (lx,rx) (ly,ry) (lz,rz)
| lx == rx && ly == ry  = za ! (k+lz)
| ly == ry && lz == rz  = xa ! (k+lx)
| lx == rx && lz == rz  = ya ! (k+ly)

| lx == rx  = search k (ya,za) (ly,ry) (lz,rz)
| ly == ry  = search k (xa,za) (lx,rx) (lz,rz)
| lz == rz  = search k (xa,ya) (lx,rx) (ly,ry)

| otherwise = case (xa ! mx < ya ! my, xa ! mx < za ! mz, ya ! my
< za ! mz) of
  (True, True, True)-> smallest3h k (xa,ya,za)
((lx,mx,rx),(ly,my,ry),(lz,mz,rz)) -- a smallest3h k (xa,za,ya)
((lx,mx,rx),(lz,mz,rz),(ly,my,ry)) -- a smallest3h k (ya,xa,za)
((ly,my,ry),(lx,mx,rx),(lz,mz,rz)) -- b smallest3h k (ya,za,xa)
((ly,my,ry),(lz,mz,rz),(lx,mx,rx)) -- b smallest3h k (za,xa,ya)
((lz,mz,rz),(lx,mx,rx),(ly,my,ry)) -- c smallest3h k (za,ya,xa)
((lz,mz,rz),(ly,my,ry),(lx,mx,rx)) -- c Int -> (Array Int a, Array Int a, Array Int a) ->
((Int,Int,Int),(Int,Int,Int),(Int,Int,Int)) -> a
smallest3h k (xa,ya,za) ((lx,mx,rx),(ly,my,ry),(lz,mz,rz)) =
case (k<=mx-lx+my-ly+mz-lz) of
  (True)-> search3 k (xa,ya,za) (lx,rx) (ly,ry) (lz,mz)
  (False)   -> search3 (k-(mx-lx)-1) (xa,ya,za) (mx+1,rx) (ly,ry) (lz,rz)




-- 
--
Regards,
KC

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


[Haskell-cafe] -- Extension for "Pearls of Functional Algorithm Design" by Richard Bird, 2010, page 25 #Haskell -- Extension for "Pearls of Functional Algorithm Design" by Richard Bird, -- 2010, page

2011-04-28 Thread caseyh
-- Extension for "Pearls of Functional Algorithm Design" by Richard  
Bird, 2010, page 25 #Haskell


-- O(log|X|+log|Y|+log|Z|) performance

-- Question: is there a way to get the type signature as the following:
-- smallest :: (Ord a) => Int -> [Array Int a] -> a


module SelectionProblem where

import Data.Array
import Data.List


-- Works on 2 finite ordered disjoint sets represented as sorted arrays.
smallest :: (Ord a) => Int -> (Array Int a, Array Int a) -> a
smallest k (xa,ya) =
search k (xa,ya) (0,m+1) (0,n+1)
where
(0,m) = bounds xa
(0,n) = bounds ya


-- Removed some of the "indexitis" at the cost of calling another function.
search :: (Ord a) => Int -> (Array Int a, Array Int a) -> (Int,Int) ->  
(Int,Int) -> a

search k (xa,ya) (lx,rx) (ly,ry)
| lx == rx  = ya ! (k+ly)
| ly == ry  = xa ! (k+lx)
| otherwise = case (xa ! mx < ya ! my) of
~~(True)-> smallest2h k (xa,ya)  
((lx,mx,rx),(ly,my,ry))
~~(False)   -> smallest2h k (ya,xa)  
((ly,my,ry),(lx,mx,rx))

~~where
~~mx = (lx+rx) `div` 2
~~my = (ly+ry) `div` 2


-- Here the sorted arrays are in order by their middle elements.
-- Only cutting the leading or trailing array by half.

-- Here xa is the first array and ya the second array by their middle  
elements.


smallest2h :: (Ord a) => Int -> (Array Int a, Array Int a) ->  
((Int,Int,Int),(Int,Int,Int)) -> a

smallest2h k (xa,ya) ((lx,mx,rx),(ly,my,ry)) =
case (k<=mx-lx+my-ly) of
~~(True)-> search k (xa,ya) (lx,rx) (ly,my)
~~(False)   -> search (k-(mx-lx)-1) (xa,ya) (mx+1,rx) (ly,ry)


---
---

-- Works on 3 finite ordered disjoint sets represented as sorted arrays.

smallest3 :: (Ord a) => Int -> (Array Int a, Array Int a, Array Int a) -> a
smallest3 k (xa,ya,za) =
-- On each recursive call the order of the arrays can switch.
search3 k (xa,ya,za) (0,bx+1) (0,by+1) (0,bz+1)
where
(0,bx) = bounds xa
(0,by) = bounds ya
(0,bz) = bounds za


-- Removed some of the "indexitis" at the cost of calling another function.
search3 :: (Ord a) => Int -> (Array Int a, Array Int a, Array Int a) ->
(Int,Int) -> (Int,Int) -> (Int,Int) -> a
search3 k (xa,ya,za) (lx,rx) (ly,ry) (lz,rz)
| lx == rx && ly == ry  = za ! (k+lz)
| ly == ry && lz == rz  = xa ! (k+lx)
| lx == rx && lz == rz  = ya ! (k+ly)

| lx == rx  = search k (ya,za) (ly,ry) (lz,rz)
| ly == ry  = search k (xa,za) (lx,rx) (lz,rz)
| lz == rz  = search k (xa,ya) (lx,rx) (ly,ry)

| otherwise = case (xa ! mx < ya ! my, xa ! mx < za ! mz, ya ! my  
< za ! mz) of
~~(True, True, True)-> smallest3h k (xa,ya,za)  
((lx,mx,rx),(ly,my,ry),(lz,mz,rz)) -- a~~(True, True, False)   -> smallest3h k (xa,za,ya)  
((lx,mx,rx),(lz,mz,rz),(ly,my,ry)) -- a~~(False, True, True)   -> smallest3h k (ya,xa,za)  
((ly,my,ry),(lx,mx,rx),(lz,mz,rz)) -- b~~(False, False, True)  -> smallest3h k (ya,za,xa)  
((ly,my,ry),(lz,mz,rz),(lx,mx,rx)) -- b~~(True, False, False)  -> smallest3h k (za,xa,ya)  
((lz,mz,rz),(lx,mx,rx),(ly,my,ry)) -- c~~(False, False, False) -> smallest3h k (za,ya,xa)  
((lz,mz,rz),(ly,my,ry),(lx,mx,rx)) -- c

~~where
~~mx = (lx+rx) `div` 2
~~my = (ly+ry) `div` 2
~~mz = (lz+rz) `div` 2


-- Here the sorted arrays are in order by their middle elements.
-- Only cutting the leading or trailing array by half.

-- Here xa is the first array, ya the second array, and za the third  
array by their middle elements.

smallest3h :: (Ord a) => Int -> (Array Int a, Array Int a, Array Int a) ->
((Int,Int,Int),(Int,Int,Int),(Int,Int,Int)) -> a
smallest3h k (xa,ya,za) ((lx,mx,rx),(ly,my,ry),(lz,mz,rz)) =
case (k<=mx-lx+my-ly+mz-lz) of
~~(True)-> search3 k (xa,ya,za) (lx,rx) (ly,ry) (lz,mz)
~~(False)   -> search3 (k-(mx-lx)-1) (xa,ya,za) (mx+1,rx) (ly,ry) (lz,rz)


---
---

-- To convert a list into an array indexed from 0.
xa = listArray (0, length xs - 1) xs
ya = listArray (0, length ys - 1) ys
za = listArray (0, length zs - 1) zs

xs = [0,17..90]
ys = [1,13..69]
zs = [7,24..91]


ua = listArray (0, length us - 1) us
va = listArray (0, length vs - 1) vs
wa = listArray (0, length ws - 1) ws

us = [0,17..100]
vs = [101,121..200]
ws = [201,221..300]


-- *SelectionProblem> sort (xs++ys++zs)
-- [0,1,7,13,17,24,25,34,37,41,49,51,58,61,68,75,85]



___
Haskell-Cafe mailing list
Haskell-Cafe@has

Re: [Haskell-cafe] -- Extension for "Pearls of Functional Algorithm Design" by Richard Bird, 2010, page 25 #Haskell

2011-04-26 Thread Jason Dagit
Do you have a question for the group or something you want to discuss?

On Mon, Apr 25, 2011 at 8:50 PM,  wrote:

> -- Extension for "Pearls of Functional Algorithm Design" by Richard Bird,
> -- 2010, page 25 #Haskell
>
> -- This version assumes 3 disjoint ordered sets represented as lists.
> -- So either: xy
> -- Since it uses lists it is no faster than the divide and conquer
> approach.
>
> -- I might try to convert this version to sorted arrays for
> -- O(log|X|+log|Y|+log|Z|) performance
> -- If I can figure out how to do it without suffering from "indexitis".
>
>
>
> smallest3'' :: Ord a => Int -> ([a], [a], [a]) -> a
>
> smallest3'' k ([],[],ts) = ts !! k
> smallest3'' k (zs,[],[]) = zs !! k
> smallest3'' k ([],ws,[]) = ws !! k
>
> smallest3'' k ([],ws,ts) = smallest'' k (ws,ts)
> smallest3'' k (zs,[],ts) = smallest'' k (zs,ts)
> smallest3'' k (zs,ws,[]) = smallest'' k (zs,ws)
>
> smallest3'' k (zs,ws,ts) =
> case (a ~~(True, True, True)-> smallest3h'' k ((zs,p,ys),(ws,q),(ts,o,rs))
> -- a ~~(True, False, True)   -> smallest3h'' k ((zs,p,ys),(ts,o),(ws,q,us))
> -- a ~~(False, True, True)   -> smallest3h'' k ((ws,q,vs),(zs,p),(ts,o,rs))
> -- b ~~(False, True, False)  -> smallest3h'' k ((ws,q,vs),(ts,o),(zs,p,xs))
> -- b ~~(True, False, False)  -> smallest3h'' k ((ts,o,ss),(zs,p),(ws,q,us))
> -- c ~~(False, False, False) -> smallest3h'' k ((ts,o,ss),(ws,q),(zs,p,xs))
> -- c
> where
> ~~p = (length zs) `div` 2
> ~~q = (length ws) `div` 2
> ~~o = (length ts) `div` 2
>
> ~~(xs, a : ys)  = splitAt p zs
> ~~(us, b : vs)  = splitAt q ws
> ~~(rs, c : ss)  = splitAt o ts
>
> ~~smallest3h'' k ((zs,p,ys),(ws,q),(ts,o,rs)) =
> case (k<=p+q+o) of
> ~~(True)-> smallest3'' k (zs,ws,rs)
> ~~(False)   -> smallest3'' (k-p-1) (ys,ws,ts)
>
>
>
>
> smallest'' :: Ord a => Int -> ([a], [a]) -> a
> smallest'' k ([],ws) = ws !! k
> smallest'' k (zs,[]) = zs !! k
> smallest'' k (zs,ws) =
> case (a ~~(True, True)  -> smallest'' k (zs,us)
> ~~(True, False) -> smallest''(k-p-1) (ys,ws)
> ~~(False, True) -> smallest'' k (xs,ws)
> ~~(False, False)-> smallest''(k-q-1) (zs,vs)
> where
> ~~p = (length zs) `div` 2
> ~~q = (length ws) `div` 2
> ~~(xs, a : ys)  = splitAt p zs
> ~~(us, b : vs)  = splitAt q ws
>
>
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] -- Extension for "Pearls of Functional Algorithm Design" by Richard Bird, 2010, page 25 #Haskell

2011-04-25 Thread caseyh

-- Extension for "Pearls of Functional Algorithm Design" by Richard Bird,
-- 2010, page 25 #Haskell

-- This version assumes 3 disjoint ordered sets represented as lists.
-- So either: xy
-- Since it uses lists it is no faster than the divide and conquer approach.

-- I might try to convert this version to sorted arrays for
-- O(log|X|+log|Y|+log|Z|) performance
-- If I can figure out how to do it without suffering from "indexitis".



smallest3'' :: Ord a => Int -> ([a], [a], [a]) -> a

smallest3'' k ([],[],ts) = ts !! k
smallest3'' k (zs,[],[]) = zs !! k
smallest3'' k ([],ws,[]) = ws !! k

smallest3'' k ([],ws,ts) = smallest'' k (ws,ts)
smallest3'' k (zs,[],ts) = smallest'' k (zs,ts)
smallest3'' k (zs,ws,[]) = smallest'' k (zs,ws)

smallest3'' k (zs,ws,ts) =
case (a~~(True, True, True)-> smallest3h'' k  
((zs,p,ys),(ws,q),(ts,o,rs)) -- a~~(True, False, True)   -> smallest3h'' k  
((zs,p,ys),(ts,o),(ws,q,us)) -- a~~(False, True, True)   -> smallest3h'' k  
((ws,q,vs),(zs,p),(ts,o,rs)) -- b~~(False, True, False)  -> smallest3h'' k  
((ws,q,vs),(ts,o),(zs,p,xs)) -- b~~(True, False, False)  -> smallest3h'' k  
((ts,o,ss),(zs,p),(ws,q,us)) -- c~~(False, False, False) -> smallest3h'' k  
((ts,o,ss),(ws,q),(zs,p,xs)) -- c

where
~~p = (length zs) `div` 2
~~q = (length ws) `div` 2
~~o = (length ts) `div` 2

~~(xs, a : ys)  = splitAt p zs
~~(us, b : vs)  = splitAt q ws
~~(rs, c : ss)  = splitAt o ts

~~smallest3h'' k ((zs,p,ys),(ws,q),(ts,o,rs)) =
case (k<=p+q+o) of
~~(True)-> smallest3'' k (zs,ws,rs)
~~(False)   -> smallest3'' (k-p-1) (ys,ws,ts)




smallest'' :: Ord a => Int -> ([a], [a]) -> a
smallest'' k ([],ws) = ws !! k
smallest'' k (zs,[]) = zs !! k
smallest'' k (zs,ws) =
case (a smallest'' k (zs,us)
~~(True, False) -> smallest''(k-p-1) (ys,ws)
~~(False, True) -> smallest'' k (xs,ws)
~~(False, False)-> smallest''(k-q-1) (zs,vs)
where
~~p = (length zs) `div` 2
~~q = (length ws) `div` 2
~~(xs, a : ys)  = splitAt p zs
~~(us, b : vs)  = splitAt q ws




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