caml-list - the Caml user's mailing list
 help / color / mirror / Atom feed
* to merge list of lists
@ 2007-03-05  6:10 Pietro Abate
  2007-03-05  8:37 ` [Caml-list] " skaller
                   ` (2 more replies)
  0 siblings, 3 replies; 9+ messages in thread
From: Pietro Abate @ 2007-03-05  6:10 UTC (permalink / raw)
  To: ocaml ml

Hi all,
I want to write a small function to merge a list of lists

mergel [] [[1;2;3];[4;5;6];[7;8;9]];;
- : int list list = [[1; 4; 7]; [2; 5; 8]; [3; 6; 9]]

I've written it down, but to me, it looks overly complicated :

let rec mergel acc ll =
    let rec aux (al,all) = function
        [] -> (List.rev al,List.rev all)
      | [] :: tl -> aux (al,all) tl
      | (h :: l) :: tl -> aux ((h::al),(l::all)) tl
    in match aux ([],[]) ll with
      |([],[]) -> List.rev acc
      |(l,[]) -> l::acc
      |(l,tl) -> mergel (l::acc) tl
;;

Since my goal is to write it lazily, I'm wondering if there is a way of
re-write the same function just by using list primitives (map, flatten,
...). (?)

I always feel that when solving these kind of problems I miss some
greater truth ... for example, by using list comprehensions it's easy to
generalize a class of combinatorial problems. Is there a similar notion
I can use in this case ?

Any hints ?

:)
p

-- 
++ Blog: http://blog.rsise.anu.edu.au/?q=pietro
++ 
++ "All great truths begin as blasphemies." -George Bernard Shaw
++ Please avoid sending me Word or PowerPoint attachments.
   See http://www.fsf.org/philosophy/no-word-attachments.html


^ permalink raw reply	[flat|nested] 9+ messages in thread

* Re: [Caml-list] to merge list of lists
  2007-03-05  6:10 to merge list of lists Pietro Abate
@ 2007-03-05  8:37 ` skaller
  2007-03-05  8:53   ` Jon Harrop
  2007-03-05  9:47 ` Zheng Li
  2007-03-06  0:07 ` [Caml-list] " Pal-Kristian Engstad
  2 siblings, 1 reply; 9+ messages in thread
From: skaller @ 2007-03-05  8:37 UTC (permalink / raw)
  To: Pietro Abate; +Cc: ocaml ml

On Mon, 2007-03-05 at 17:10 +1100, Pietro Abate wrote:
> Hi all,
> I want to write a small function to merge a list of lists
> 
> mergel [] [[1;2;3];[4;5;6];[7;8;9]];;
> - : int list list = [[1; 4; 7]; [2; 5; 8]; [3; 6; 9]]
> 
> I've written it down, but to me, it looks overly complicated :

> I always feel that when solving these kind of problems I miss some
> greater truth ... 

In this case there is a library function:

	List.concat

that already does exactly what you want :)

-- 
John Skaller <skaller at users dot sf dot net>
Felix, successor to C++: http://felix.sf.net


^ permalink raw reply	[flat|nested] 9+ messages in thread

* Re: [Caml-list] to merge list of lists
  2007-03-05  8:37 ` [Caml-list] " skaller
@ 2007-03-05  8:53   ` Jon Harrop
  2007-03-05 19:02     ` skaller
  2007-03-07 14:33     ` Roland Zumkeller
  0 siblings, 2 replies; 9+ messages in thread
From: Jon Harrop @ 2007-03-05  8:53 UTC (permalink / raw)
  To: caml-list

On Monday 05 March 2007 08:37, skaller wrote:
> On Mon, 2007-03-05 at 17:10 +1100, Pietro Abate wrote:
> > mergel [] [[1;2;3];[4;5;6];[7;8;9]];;
> > - : int list list = [[1; 4; 7]; [2; 5; 8]; [3; 6; 9]]
>
> In this case there is a library function:
>
>       List.concat
>
> that already does exactly what you want :)

List.concat doesn't do that:

# List.concat [[1;2;3];[4;5;6];[7;8;9]];;
- : int list = [1; 2; 3; 4; 5; 6; 7; 8; 9]

Note that the OP is not asking for a concat or even a merge, but a transpose.

A naive (non tail recursive) transpose is a 1-liner:

# open List;;
# let rec transpose list =
    try map hd list :: transpose (map tl list) with _ -> [];;
val transpose : 'a list list -> 'a list list = <fun>

For example:

# transpose [[1;2;3];[4;5;6];[7;8;9]];;
- : int list list = [[1; 4; 7]; [2; 5; 8]; [3; 6; 9]]

-- 
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
OCaml for Scientists
http://www.ffconsultancy.com/products/ocaml_for_scientists


^ permalink raw reply	[flat|nested] 9+ messages in thread

* Re: to merge list of lists
  2007-03-05  6:10 to merge list of lists Pietro Abate
  2007-03-05  8:37 ` [Caml-list] " skaller
@ 2007-03-05  9:47 ` Zheng Li
  2007-03-05 14:42   ` Zheng Li
  2007-03-06  0:07 ` [Caml-list] " Pal-Kristian Engstad
  2 siblings, 1 reply; 9+ messages in thread
From: Zheng Li @ 2007-03-05  9:47 UTC (permalink / raw)
  To: caml-list

Pietro Abate <Pietro.Abate@anu.edu.au> writes:

> Hi all,
> I want to write a small function to merge a list of lists
>
> mergel [] [[1;2;3];[4;5;6];[7;8;9]];;
> - : int list list = [[1; 4; 7]; [2; 5; 8]; [3; 6; 9]]
>
> Since my goal is to write it lazily, I'm wondering if there is a way of
> re-write the same function just by using list primitives (map, flatten,
> ...). (?)
If you want to use high-order functions in the standard list library, here are
my versions:

open List
let rec merge = function
  | [] -> [] 
  | h :: [] -> map (fun x -> [x]) h
  | h::t -> map2 (fun x y -> x::y) h (merge t);;

Note that, it's not efficient at all but quite easy to understand. Another
version,

let rec merge l = match rev l with
  | [] -> []
  | h :: t -> fold_left (map2 (fun x y -> y::x)) (map (fun x -> [x]) h) t

maybe better.

> I always feel that when solving these kind of problems I miss some
> greater truth ... for example, by using list comprehensions it's easy to
> generalize a class of combinatorial problems. Is there a similar notion
> I can use in this case ?

A few weeks ago, someone else asked the permute question [1] in this
list. There are instructive followups you may want to read. I'll also post my
answer here sometime later.

[1]
http://caml.inria.fr/pub/ml-archives/caml-list/2007/02/cf0ae15f6f6e18ebf71c79c127d41a74.en.html

-- 
Zheng Li
http://www.pps.jussieu.fr/~li


^ permalink raw reply	[flat|nested] 9+ messages in thread

* Re: to merge list of lists
  2007-03-05  9:47 ` Zheng Li
@ 2007-03-05 14:42   ` Zheng Li
  0 siblings, 0 replies; 9+ messages in thread
From: Zheng Li @ 2007-03-05 14:42 UTC (permalink / raw)
  To: caml-list; +Cc: Erik de Castro Lopo


hi, 

> A few weeks ago, someone else asked the permute question [1] in this
> list. There are instructive followups you may want to read. I'll also post my
> answer here sometime later.

This is not a direct response to you question, but it could be related to the
problem you want to solve. The original version of this post was posted at a
FP forum several years ago. I recently read [1] which is almost identical, and
now your question which is closely related, so here I re-post it for your
reference.

[1] http://caml.inria.fr/pub/ml-archives/caml-list/2007/02/cf0ae15f6f6e18ebf71c79c127d41a74.en.html

The permute question raised in [1], and also in many other situation, is just
solving the 8-queen problem in another form (in OP, n = 8, whereas the n could
be any). 

There are typically two ways to solve such kind of problem: combination and
iteration. The former first combinatrially *generate* all the configurations
then filter (or other op) them according to some condition; the later does not
generate configurations, instead it iterates over them.

Almost any book I read would suggest to use iteration instead of combination
for such problems. But in case you're not solving the n-queen like problem and
really need to generate it by combination, here we investigate both of them.


By Combination
--------------
You probably won't be able to write such a function on the fly, especially when
taking functional, tail-recursion and row-major all into consideration. This
is due to the fact that there are usually 3 nested layers of recursion you need
to deal with here (if you really walk through them all by recursion): 

  - the arbitrary dimension $n$
  - the range in each dimension (min, max)
  - and any underlying operation over a list 
    (e.g. prefix all elements of a list with sth etc.)

Anyway, here is a possible version. We use (int * int) list, other than int
list * int list, to represent range pairs in each dimension to ensure we always
have the same number of lower/upper bounds.

-------------------------------------------------------------------------
open List
let permute : (int * int) list -> int list list =
  let rec aux res tmp = function
    | [] -> res
    | (a,b) :: t when a <= b ->
        let tmp' = fold_left (fun l x -> (a :: x) :: l) tmp res in
        aux res tmp' ((a + 1, b) :: t) 
    | _  :: t -> aux (rev tmp) [] t in
  function [] -> []  | l -> aux [[]] [] (rev l)
-------------------------------------------------------------------------

test it: (given min <= max )

-------------------------------------------------------------------------
# permute [];;
- : int list list = []
# permute [1,4];;
- : int list list = [[1]; [2]; [3]; [4]]
permute [(1,4); (12,15); (5,6); (21,22)];;
- : int list list =
[[1; 12; 5; 21]; [1; 12; 5; 22]; [1; 12; 6; 21]; [1; 12; 6; 22];
 [1; 13; 5; 21]; [1; 13; 5; 22]; [1; 13; 6; 21]; [1; 13; 6; 22];
 [1; 14; 5; 21]; [1; 14; 5; 22]; [1; 14; 6; 21]; [1; 14; 6; 22];
 [1; 15; 5; 21]; [1; 15; 5; 22]; [1; 15; 6; 21]; [1; 15; 6; 22];
 [2; 12; 5; 21]; [2; 12; 5; 22]; [2; 12; 6; 21]; [2; 12; 6; ...]; ...]
--------------------------------------------------------------------------

Though, doing such kind of job with combination is really bad:

 - It's difficult to write, esp. fully functional, tail-recursive, row-major
   etc.
 - It generates and hold *all* the configurations in *memory*, which is
   unnecessary in most cases when you just want to iter (esp. filter)
   them. It has serious problem with huge data.
 - It generates all the result at last -- at the final step, but nothing before
   that. Think about the situation if data is huge and take months to permute
   before you can see a single result, and after that you found something is
   initially wrong with your algorithm. You definitely want to see the frontal
   configurations coming out without waiting for the latter, but the
   combination way doesn't work like that.

One should aware the many points above don't apply to lazy language like
haskell, as the configurations are not really computed and hold in memory
unless required. 


By Iteration
------------

So as in any book, in most case you should use iteration, I won't repeat
them. It can be done functionally in OCaml without doubt. I give a version
written in stream, you won't have any problem in rewrite it with list if you
want.

--------------------------------------------------------------------------------
let rec next = function
  | h::t, min::min_t, max::max_t -> 
      if h < max then h + 1 :: t else min :: next (t, min_t, max_t)
  | _ -> raise (Invalid_argument "next")

let permute l =
  let min, max = List.split (rev l) in
  let rec gen x = [< 'rev x; if x = max then [<>] else gen (next (x,min,max)) >]
  in gen min;;
---------------------------------------------------------------------------------

Then you just use Stream.iter, Stream.next or parser to do whatever you want
with it, including store it globally to get the same reult as the combination
method if you really need. e.g

let s = permute [(1,4); (12,17); (5,6)] in
Stream.iter (fun l -> List.iter (Printf.printf "%d ") l; print_newline ()) s

There is another stream version which doesn't use the "next" function above,
instead recursion over the dimensions and ranges, similar to the combination
way but can produce result lazily. 

-------------------------------------------------------------------------------
let rec map f = parser [<'x ; rest>] -> [<'f x; map f rest>] | [< >] -> [< >]

let rec permute = function
  | (a, b) :: t when a <= b ->
      [< (match t with [] -> [<'[a]>] | _ -> map (fun x -> a :: x) (permute t));
         permute ((a + 1, b) :: t) >]
  | _ -> [< >];;
------------------------------------------------------------------------------

HTH.

-- 
Zheng Li
http://www.pps.jussieu.fr/~li/software
(OcamlP3l, STM for OCaml, Enhanced toplevel etc.)


^ permalink raw reply	[flat|nested] 9+ messages in thread

* Re: [Caml-list] to merge list of lists
  2007-03-05  8:53   ` Jon Harrop
@ 2007-03-05 19:02     ` skaller
  2007-03-05 19:40       ` skaller
  2007-03-07 14:33     ` Roland Zumkeller
  1 sibling, 1 reply; 9+ messages in thread
From: skaller @ 2007-03-05 19:02 UTC (permalink / raw)
  To: Jon Harrop; +Cc: caml-list

On Mon, 2007-03-05 at 08:53 +0000, Jon Harrop wrote:
> On Monday 05 March 2007 08:37, skaller wrote:
> > On Mon, 2007-03-05 at 17:10 +1100, Pietro Abate wrote:
> > > mergel [] [[1;2;3];[4;5;6];[7;8;9]];;
> > > - : int list list = [[1; 4; 7]; [2; 5; 8]; [3; 6; 9]]
> >
> > In this case there is a library function:
> >
> >       List.concat
> >
> > that already does exactly what you want :)
> 
> List.concat doesn't do that:
> 
> # List.concat [[1;2;3];[4;5;6];[7;8;9]];;
> - : int list = [1; 2; 3; 4; 5; 6; 7; 8; 9]
> 
> Note that the OP is not asking for a concat or even a merge, but a transpose.

Yes, sorry! I didn't look closely enough.
I have a related function in Felix, which transposes
a tuple of tuples, which is done with a term like

	_tuple_trans ((1,2,3),(4,5,6),(7,8,9))

here's the code, which is quite imperative, and which has
extra mess from the error diagnostics. In this case there
is a special representation for the type of a tuple
with all the elements the same type, instead of

	int * int * int

the type can be given as

	int * 3

where 3 = 1 + 1 + 1, 1 is the usual unit type, and + is
an anonymous variant combinator. A type like 3 is
called a unitsum (it is a sum of units). This in turn
allows arrays to be considered as tuples of the same
element type, and the special representation is required
to allow arrays of large extent (there's no way a representation
of a 20,000 integer tuple is going to fly in a production
compiler). Also note the result of this calculation is
a bound term, the function 'be' binds expressions,
and this code is part of that function.

So the code is somewhat more complex, but it does the
same thing. It's very hard to tell if the code is correct:
I'd be interested in a more functional way to do this
that was actually simpler (but had the same semantics).
The 'guts' of the calculation is done by the 'tr'
function introduced on line 2.


  | `AST_apply (sr,(`AST_name (_,"_tuple_trans",[]),e)) ->
    let tr nrows ncolumns =
      let e' = ref [] in
      for i = nrows - 1 downto 0 do
        let x = ref [] in
        for j = ncolumns - 1 downto 0 do
          let v = `AST_get_n (sr,(i,`AST_get_n (sr,(j,e)))) in
          x := v :: !x;
        done;
        e' := `AST_tuple (sr,!x) :: (!e');
      done
      ;
      be (`AST_tuple (sr,!e'))
    in
    let calnrows t = 
      let nrows =
        match t with 
        | `BTYP_tuple ls -> length ls
        | `BTYP_array (_,`BTYP_unitsum n) -> n
        | _ -> clierrn [sr] "Tuple transpose requires entry to be tuple"
      in 
      if nrows < 2 then
        clierr sr "Tuple transpose requires tuple argument with 2 or
more elements"
      ;
      nrows
    in
    let colchk nrows t =
      match t with 
      | `BTYP_tuple ls -> 
        if length ls != nrows then
          clierr sr ("Tuple transpose requires entry to be tuple of
length " ^ si nrows)

      | `BTYP_array (_,`BTYP_unitsum n) ->
        if n != nrows then
          clierr sr ("Tuple transpose requires entry to be tuple of
length " ^ si nrows)
        
      | _ -> clierr sr "Tuple transpose requires entry to be tuple"
    in
    let _,t = be e in
    let ncolumns, nrows = 
      match t with
      | `BTYP_tuple ls ->
        let ncolumns  = length ls in
        let nrows = calnrows (hd ls) in
        iter (colchk nrows) ls;
        ncolumns, nrows

      | `BTYP_array (t,`BTYP_unitsum ncolumns) ->
        let nrows = calnrows t in
        ncolumns, nrows

      | _ -> clierr sr "Tuple transpose requires tuple argument"
    in
      if nrows > 20 then
        clierr sr ("tuple fold: row bound " ^ si nrows ^ ">20, to
large")
      ;
      if ncolumns> 20 then
        clierr sr ("tuple fold: column bound " ^ si ncolumns^ ">20, to
large")
      ;
      tr nrows ncolumns


-- 
John Skaller <skaller at users dot sf dot net>
Felix, successor to C++: http://felix.sf.net


^ permalink raw reply	[flat|nested] 9+ messages in thread

* Re: [Caml-list] to merge list of lists
  2007-03-05 19:02     ` skaller
@ 2007-03-05 19:40       ` skaller
  0 siblings, 0 replies; 9+ messages in thread
From: skaller @ 2007-03-05 19:40 UTC (permalink / raw)
  To: Jon Harrop; +Cc: caml-list

On Tue, 2007-03-06 at 06:02 +1100, skaller wrote:

> 	int * int * int
> 
> the type can be given as
> 
> 	int * 3

Ooops .. I meant int ^ 3 of course, using an exponential.

-- 
John Skaller <skaller at users dot sf dot net>
Felix, successor to C++: http://felix.sf.net


^ permalink raw reply	[flat|nested] 9+ messages in thread

* Re: [Caml-list] to merge list of lists
  2007-03-05  6:10 to merge list of lists Pietro Abate
  2007-03-05  8:37 ` [Caml-list] " skaller
  2007-03-05  9:47 ` Zheng Li
@ 2007-03-06  0:07 ` Pal-Kristian Engstad
  2 siblings, 0 replies; 9+ messages in thread
From: Pal-Kristian Engstad @ 2007-03-06  0:07 UTC (permalink / raw)
  To: Pietro Abate; +Cc: caml-list

Sometimes, imperative style is easier to understand (and probably faster):

let transpose ll =
  let array = Array.map Array.of_list (Array.of_list ll) in (* create 2d 
array *)
  let maxlen = Array.fold_left (fun acc lst -> max acc (Array.length 
lst)) 0 array in (* find maximum length *)
  let res = Array.create maxlen [] in (* create return value *)
    for j = 0 to maxlen - 1 do
      for i = 0 to Array.length array - 1 do
        if j < Array.length array.(i) then
          res.(j) <- array.(i).(j) :: res.(j)
      done
    done;
    Array.to_list (Array.map List.rev res)

PKE.


Pietro Abate wrote:
> Hi all,
> I want to write a small function to merge a list of lists
>
> mergel [] [[1;2;3];[4;5;6];[7;8;9]];;
> - : int list list = [[1; 4; 7]; [2; 5; 8]; [3; 6; 9]]
>
> I've written it down, but to me, it looks overly complicated :
>
> let rec mergel acc ll =
>     let rec aux (al,all) = function
>         [] -> (List.rev al,List.rev all)
>       | [] :: tl -> aux (al,all) tl
>       | (h :: l) :: tl -> aux ((h::al),(l::all)) tl
>     in match aux ([],[]) ll with
>       |([],[]) -> List.rev acc
>       |(l,[]) -> l::acc
>       |(l,tl) -> mergel (l::acc) tl
> ;;
>
> Since my goal is to write it lazily, I'm wondering if there is a way of
> re-write the same function just by using list primitives (map, flatten,
> ...). (?)
>
> I always feel that when solving these kind of problems I miss some
> greater truth ... for example, by using list comprehensions it's easy to
> generalize a class of combinatorial problems. Is there a similar notion
> I can use in this case ?
>
> Any hints ?
>
> :)
> p
>
>   

-- 
Pål-Kristian Engstad (engstad@naughtydog.com), Lead Programmer, ICE
team, Naughty Dog, Inc., 1601 Cloverfield Blvd, 6000 North,
Santa Monica, CA 90404, USA. Ph.: (310) 633-9112.

"Most of us would do well to remember that there is a reason Carmack
is Carmack, and we are not Carmack.",
                       Jonathan Blow, 2/1/2006, GD Algo Mailing List




^ permalink raw reply	[flat|nested] 9+ messages in thread

* Re: [Caml-list] to merge list of lists
  2007-03-05  8:53   ` Jon Harrop
  2007-03-05 19:02     ` skaller
@ 2007-03-07 14:33     ` Roland Zumkeller
  1 sibling, 0 replies; 9+ messages in thread
From: Roland Zumkeller @ 2007-03-07 14:33 UTC (permalink / raw)
  To: caml-list

On 05/03/07, Jon Harrop <jon@ffconsultancy.com> wrote:
> # let rec transpose list =
>     try map hd list :: transpose (map tl list) with _ -> [];;

Here is a slightly different version that raises an exception if the
given list is not quadratic:

let rec transpose xs =
  if for_all ((=) []) xs then [] else
    map hd xs :: transpose (map tl xs);;

-- 
http://www.lix.polytechnique.fr/~zumkeller/


^ permalink raw reply	[flat|nested] 9+ messages in thread

end of thread, other threads:[~2007-03-07 14:33 UTC | newest]

Thread overview: 9+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2007-03-05  6:10 to merge list of lists Pietro Abate
2007-03-05  8:37 ` [Caml-list] " skaller
2007-03-05  8:53   ` Jon Harrop
2007-03-05 19:02     ` skaller
2007-03-05 19:40       ` skaller
2007-03-07 14:33     ` Roland Zumkeller
2007-03-05  9:47 ` Zheng Li
2007-03-05 14:42   ` Zheng Li
2007-03-06  0:07 ` [Caml-list] " Pal-Kristian Engstad

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for NNTP newsgroup(s).