]> Creatis software - CreaPhase.git/blob - octave_packages/dataframe-0.9.1/@dataframe/subsref.m
Add a useful package (from Source forge) for octave
[CreaPhase.git] / octave_packages / dataframe-0.9.1 / @dataframe / subsref.m
1 function resu = subsref(df, S)
2   %# function resu = subsref(df, S)
3   %# This function returns a subpart of a dataframe. It is invoked when
4   %# calling df.field, df(value), or df{value}. In case of fields,
5   %# returns either the content of the container with the same name,
6   %# either the column with the same name, priority being given to the
7   %# container. In case of range, selection may occur on name or order
8   %# (not rowidx for rows). If the result is homogenous, it is
9   %# downclassed. In case an extra field is given, is it used to
10   %# determine the class of the return value. F.i., 
11   %# df(1, 2, 'dataframe') 
12   %# does not return a scalar but a dataframe, keeping all the meta-information
13
14   %% Copyright (C) 2009-2012 Pascal Dupuis <Pascal.Dupuis@uclouvain.be>
15   %%
16   %% This file is part of Octave.
17   %%
18   %% Octave is free software; you can redistribute it and/or
19   %% modify it under the terms of the GNU General Public
20   %% License as published by the Free Software Foundation;
21   %% either version 2, or (at your option) any later version.
22   %%
23   %% Octave is distributed in the hope that it will be useful,
24   %% but WITHOUT ANY WARRANTY; without even the implied
25   %% warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR
26   %% PURPOSE.  See the GNU General Public License for more
27   %% details.
28   %%
29   %% You should have received a copy of the GNU General Public
30   %% License along with Octave; see the file COPYING.  If not,
31   %% write to the Free Software Foundation, 51 Franklin Street -
32   %% Fifth Floor, Boston, MA 02110-1301, USA.
33   
34   %#
35   %# $Id: subsref.m 9585 2012-02-05 15:32:46Z cdemills $
36   %#
37   
38   %# what kind of object should we return ?
39   asked_output_type = ''; asked_output_format = [];
40
41   if (strcmp (S(1).type, '.')) %# struct access
42     indi = strmatch (S(1).subs, 'as');
43     if (~isempty (indi)) 
44       if (length (S) < 2 || ~strcmp (S(2).type, '.'))
45         error ("The output format qualifier 'as' must be followed by a type");
46       endif
47       asked_output_type = "array";
48       asked_output_format = S(2).subs; S = S(3:end);
49     else
50       indi = strmatch(S(1).subs, 'array');
51       if (~isempty (indi)) 
52         asked_output_type = "array";    
53         S = S(2:end);
54       else
55         indi = strmatch (S(1).subs, char ('df', class (df)));
56         if (~isempty (indi))
57           %# requiring a dataframe
58           if (1 == indi) %# 'df' = short for 'dataframe'
59             asked_output_type = 'dataframe';
60           else
61             asked_output_type =  S(1).subs;
62           endif
63           S = S(2:end);
64           if (isempty (S) && strcmp (asked_output_type, class (df)))
65             resu = df; return; 
66           endif
67         else
68           indi = strmatch(S(1).subs, 'cell');
69           if (~isempty (indi))
70             asked_output_type =  S(1).subs;
71             S = S(2:end);
72           else
73             %# access as a pseudo-struct
74             resu = struct(df); %# avoid recursive calls  
75             if (1 == strfind(S(1).subs, '_')) %# its an internal field name
76               %# FIXME: this should only be called from class members and friends
77               %# FIXME -- in case many columns are asked, horzcat them
78               resu = horzcat (feval (@subsref, resu, S));
79             else
80               %# direct access through the exact column name
81               indi = strmatch(S(1).subs, resu._name{2}, "exact");
82               if (~isempty (indi))
83                 resu = df._data{indi}; %# extract colum;
84                 if (strcmp (df._type{indi}, 'char') \
85                     && 1 == size (df._data{indi}, 2))
86                   resu = char (resu)
87                 endif 
88                 if (length (S) > 1)
89                   dummy = S(2:end); S = S(1);
90                   switch dummy(1).type
91                     case '()'
92                       if (isa(dummy(1).subs{1}, "char"))
93                         [indr, nrow, dummy(1).subs{1}] = \
94                             df_name2idx(df._name{1}, dummy(1).subs{1}, df._cnt(1), 'row');
95                       endif
96                       resu = feval(@subsref, resu, dummy);
97                     otherwise
98                       error ("Invalid column access");
99                   endswitch
100                 endif
101               else %# access of an attribute
102                 dummy = S(2:end); S = S(1);
103                 postop = ''; further_deref = false;
104                 %# translate the external to internal name
105                 switch S(1).subs
106                   case "rownames"
107                     S(1).subs = "_name";
108                     S(2).type = "{}"; S(2).subs{1}= 1;
109                     postop = @(x) char (x); 
110                   case "colnames"
111                     S(1).subs = "_name";
112                     S(2).type = "{}"; S(2).subs{1}= 2;
113                     postop = @(x) char (x); further_deref = true;
114                   case "rowcnt"
115                     S(1).subs = "_cnt";
116                     S(2).type = "()"; S(2).subs{1}= 1;
117                   case "colcnt"
118                     S(1).subs = "_cnt";
119                     S(2).type = "()"; S(2).subs{1}= 2;
120                   case "rowidx"
121                     S(1).subs = "_ridx"; further_deref = true;
122                   case "types"  %# this one should be accessed as a matrix
123                     S(1).subs = "_type"; further_deref = true;
124                   case "source"
125                     S(1).subs = "_src";
126                     further_deref = true;
127                   case "comment"
128                     S(1).subs = "_cmt";
129                     further_deref = true;
130                   case "new"
131                     if (isempty (dummy))
132                       resu = dataframe([]);
133                     else
134                       if (!strcmp (dummy(1).type, "()"))
135                         error ("Bogus constructor call");
136                       endif
137                       resu = dataframe(dummy(1).subs{:});
138                     endif
139                     if (length (dummy) > 1)
140                       resu = subsref(resu, dummy(2:end));
141                     endif
142                     return;
143                   otherwise
144                     error ("Unknown column name: %s", S(1).subs);
145                 endswitch
146                 if (!isempty (dummy))
147                   if ~further_deref,
148                     error ("Invalid sub-dereferencing");
149                   endif
150                   if (isa(dummy(1).subs{1}, "char"))
151                     [indc, ncol, dummy(1).subs{1}] = \
152                         df_name2idx(df._name{2}, dummy(1).subs{1}, \
153                                     df._cnt(2), 'column');
154                     if (isempty (indc)) 
155                       %# should be already catched  inside df_name2idx
156                       error ("Unknown column name: %s",  dummy(1).subs{1});
157                     endif
158                   endif
159                   if (!strcmp (dummy(1).type, '()'))
160                     error ("Invalid internal field name sub-access, use () instead");
161                   endif
162                 endif
163                 %# workaround around bug 30921, fixed in hg changeset 10937
164                 %# if !isempty (dummy)
165                 S = [S dummy];
166                 %# endif
167                 resu = feval(@subsref, resu, S);
168                 if (!isempty (postop))
169                   resu = postop(resu);
170                 endif
171               endif
172             endif
173             return
174           endif
175         endif
176       endif
177     endif
178   endif
179   
180   %# disp('line 103 '); keyboard
181
182   IsFirst = true;
183   while 1, %# avoid recursive calls on dataframe sub-accesses
184   
185     %# a priori, performs whole accesses
186     nrow = df._cnt(1); indr = 1:nrow; 
187     ncol = df._cnt(2); indc = 1:ncol; 
188     %# linear indexes
189     [fullindr, fullindc, fullinds, onedimidx] = deal([]);
190
191     %# iterate over S, sort out strange constructs as x()()(1:10, 1:4)
192     while length (S) > 0,
193       if (strcmp (S(1).type, '{}'))
194         if (!IsFirst || !isempty (asked_output_format))
195           error ("Illegal dataframe dereferencing");
196         endif
197         [asked_output_type, asked_output_format] = deal('cell');
198       elseif (!strcmp (S(1).type, '()'))
199         %# disp(S); keyboard
200         error ("Illegal dataframe dereferencing");
201       endif
202       if (isempty (S(1).subs)) %# process calls like x()
203         if (isempty (asked_output_type))
204           asked_output_type = class (df);
205         endif
206         if (length (S) <= 1) 
207           if (strcmp (asked_output_type, class (df)))
208             %# whole access without conversion
209             resu = df; return; 
210           endif
211           break; %# no dimension specified -- select all, the
212           %# asked_output_type was set in a previous iteration
213         else
214           %# avoid recursive calls
215           S = S(2:end); 
216           IsFirst = false; continue;
217         endif      
218       endif
219       %# generic access
220       if (isempty (S(1).subs{1}))
221         error ('subsref: first dimension empty ???');
222       endif
223       if (length (S(1).subs) > 1)
224         if (isempty (S(1).subs{2}))
225           error ('subsref: second dimension empty ???');
226         endif
227         [indr, nrow, S(1).subs{1}] = \
228             df_name2idx(df._name{1}, S(1).subs{1}, df._cnt(1), 'row');      
229         if (!isa(indr, 'char') && max (indr) > df._cnt(1))
230           error ("Accessing dataframe past end of lines");
231         endif
232         [indc, ncol, S(1).subs{2}] = \
233             df_name2idx(df._name{2}, S(1).subs{2}, df._cnt(2), 'column');
234         if (max (indc) > df._cnt(2))
235           %# is it a two index access of a 3D structure ?
236           if (length (df._cnt) > 2)
237             [fullindc, fullinds] = ind2sub (df._cnt(2:3), indc);
238             if (fullindc <= df._cnt(2))
239               indc = fullindc; inds = fullinds; 
240             endif
241           endif
242           %# retest
243           if (max (indc) > df._cnt(2))
244             error ("Accessing dataframe past end of columns");
245           endif
246         endif
247       else
248         %# one single dim -- probably something like df(:), df(A), ...
249         fullindr = 1; onedimidx = S(1).subs{1};
250         switch class (S(1).subs{1})
251           case {'char'} %# one dimensional access, disallow it if not ':' 
252             if (strcmp (S(1).subs{1}, ':'))
253               fullindr = []; fullindc = []; asked_output_type = "array"; 
254             else
255               error (["Accessing through single dimension and name " \
256                       S(1).subs{1} " not allowed\n-- use variable(:, 'name') instead"]);
257             endif
258           case {'logical'}
259             S(1).subs{1} = find(S(1).subs{1});
260           case {'dataframe'}
261             S(1).subs{1} = subsindex(S(1).subs{1}, 1);
262         endswitch
263
264         if (isempty (S(1).subs{1})) 
265           resu = df_colmeta(df);
266           return; 
267         endif
268
269         if (!isempty (fullindr))
270           %# convert linear index to subscripts
271           if (length (df._cnt) <= 2)
272             [fullindr, fullindc] = ind2sub (df._cnt, S(1).subs{1});
273             fullinds = ones (size (fullindr));
274           else
275             dummy = max (cellfun(@length, df._rep));
276             [fullindr, fullindc, fullinds] = ind2sub\
277                 ([df._cnt dummy], S(1).subs{1});
278           endif 
279           
280           indr = unique (fullindr); nrow = length (indr);
281           %# determine on which columns we'll iterate
282           indc = unique (fullindc)(:).'; ncol = length (indc);
283           if (!isempty (asked_output_type) && ncol > 1)
284             %# verify that the extracted values form a square matrix
285             dummy = zeros(indr(end), indc(end));
286             for indi = (1:ncol)
287               indj = find (fullindc == indc(indi));
288               dummy(fullindr(indj), indc(indi)) = 1;
289             endfor
290             dummy = dummy(indr(1):indr(end), indc(1):indc(end));
291             if (any (any (dummy!= 1)))
292               error ("Vector-like selection is not rectangular for the asked output type");
293             else
294               fullindr = []; fullindc = [];
295             endif
296           endif 
297         endif
298       endif
299       %# at this point, S is either empty, either contains further dereferencing
300       break;
301     endwhile
302     
303     %# we're ready to extract data
304     %# disp('line 211 '); keyboard
305     
306     if (isempty (asked_output_type))
307       output_type = class (df); %# force df output
308     else
309       if (!strcmp (asked_output_type, "array") \
310           || !isempty (asked_output_format))
311         %# override the class of the return value
312         output_type = asked_output_type;
313       else
314         %# can the data be merged ?
315         output_type = df._data{indc(1)}(1);
316         dummy = isnumeric(df._data{indc(1)}); 
317         for indi = (2:ncol)
318           dummy = dummy & isnumeric (df._data{indc(indi)});
319           if (~strcmp (class (output_type), df._type{indc(indi)}))
320             if (dummy) 
321               %# let downclassing occur
322               output_type = horzcat (output_type, df._data{indc(indi)}(1));
323               continue; 
324             endif
325             %# unmixable args -- falls back to type of parent container 
326             error ("Selected columns %s not compatible with cat() -- use 'cell' as output format", mat2str (indc));
327             %# dead code -- suppress previous line for switching automagically the output format to df
328             output_type = class (df); 
329             break;
330           endif
331         endfor
332         asked_output_format = class (output_type);
333         output_type = "array";
334       endif
335     endif
336     
337     if (any(strcmp ({output_type, asked_output_type}, class (df))))
338       if (!isempty (S) && (1 == length (S(1).subs)))
339         %# is the selection index vector-like ?
340         if ((isnumeric(S(1).subs{1}) && isvector(S(1).subs{1}) &&
341              df._cnt(1) > 1) && isempty (asked_output_type))
342           %# in the case of vector input, favor array output
343           [asked_output_type, output_type] = deal("array");
344         endif
345       endif
346     endif
347       
348     indt = {}; %# in case we have to mix matrix of different width
349     if (!isempty (fullinds))
350       inds = unique (fullinds); nseq = length (inds);
351       indt(1, 1:df._cnt(2)) = inds;
352     else      
353       inds = 1; indt(1, 1:df._cnt(2)) = inds; nseq = 1;
354       if (isempty (S) || all(cellfun('isclass', S(1).subs, 'char')))
355         inds = ':'; indt(1, 1:df._cnt(2)) = inds;
356         nseq = max (cellfun(@length, df._rep(indc)));
357       else
358         if (length (S(1).subs) > 1) %# access-as-matrix
359           if (length (S(1).subs) > 2)
360             inds = S(1).subs{3};
361             if (isa(inds, 'char'))
362               nseq = max (cellfun(@length, df._rep(indc)));
363               indt(1, 1:df._cnt(2)) = inds;
364             else
365               %# generate a specific index for each column
366               nseq = length (inds);
367               dummy = cellfun(@length, df._rep(indc));
368               indt(1, 1:df._cnt(2)) = inds;
369               indt(1==dummy) = 1; 
370             endif
371           endif
372         endif
373       endif
374     endif
375
376     if (strcmp (output_type, class (df)))
377       %# disp('line 295 '); keyboard
378       %# export the result as a dataframe
379       resu = dataframe ([]);
380       resu._cnt(1) = nrow; resu._cnt(2) = ncol;
381       if (isempty (fullindr))
382         for indi = (1:ncol)
383           resu._data{indi} =  df._data{indc(indi)}\
384               (indr, df._rep{indc(indi)}(indt{indc(indi)})); 
385           resu._rep{indi} =  1:size (resu._data{indi}, 2);
386           resu._name{2}(indi, 1) = df._name{2}(indc(indi));
387           resu._over{2}(1, indi) = df._over{2}(indc(indi));
388           resu._type{indi} = df._type{indc(indi)};
389         endfor
390         if (!isempty (df._ridx) && size (df._ridx, 2) >= inds)
391           resu._ridx = df._ridx(indr, inds);
392         endif 
393         if (length (df._name{1}) >= max (indr))
394           resu._name{1}(1:nrow, 1) = df._name{1}(indr);
395           resu._over{1}(1, 1:nrow) = df._over{1}(indr);
396         endif
397       else
398         dummy = df_whole(df);
399         dummy = dummy(onedimidx);
400         for indi = (1:resu._cnt(2))
401           indc = unique (fullindc(:, indi));
402           if (1 == length (indc))
403             resu._name{2}(indi)= df._name{2}(indc);
404             resu._over{2}(indi)= df._over{2}(indc);
405             unfolded = df._data{indc}(:, df._rep{indc});
406             indj =  sub2ind (size (unfolded), fullindr(:, indi), \
407                             fullinds(:, indi));
408             resu._data{indi} = unfolded(indj);
409             resu._type{indi} = df._type{indc};
410             resu._rep{indi} = 1:size (resu._data{indi}, 2);  
411           else
412             resu._name{2}(indi)= ["X" num2str(indi)];
413             resu._over{2}(indi)= true;
414             resu._data{indi} = squeeze(dummy(:, indi, :));
415             resu._type{indi} = class (dummy(1, indi, 1));
416             resu._rep{indi} = 1:size (resu._data{indi}, 2);  
417           endif
418         endfor
419         if (1 ==  size (df._ridx, 2))
420           resu._ridx = repmat (df._ridx, [1 ncol 1]);
421         else
422           resu._ridx = df._ridx;
423         endif
424         if (!isempty (resu._ridx))
425           if (size (resu._ridx, 2) > 1)
426             resu._ridx = resu._ridx(indr, indc);
427           else
428             resu._ridx = resu._ridx(indr);
429           endif
430         endif
431       endif
432       %# to be verified :       keyboard
433       resu._src = df._src;
434       resu._cmt = df._cmt;
435       resu = df_thirddim(resu);
436       if (length (S) > 1) %# perform further access, if required
437         df = resu;
438         S = S(2:end);   %# avoid recursive calls
439         continue;       %# restart the loop around line 150
440       endif
441       return;
442       
443     elseif (strcmp (output_type, 'cell'))
444       %# export the result as a cell array
445       if (isempty (asked_output_format))
446         resu = cell (2+nrow, 2+ncol); resu(1:end, 1:2) = {''};
447         resu(2, 3:end) = df._type(indc);                        %column type
448         row_offs = 2; col_offs = 2;
449         for indi = (1:ncol)
450           resu{1, 2+indi} = df._name{2}{indc(indi)};            % column name
451         endfor
452         resu(3:end, 1) =  mat2cell (df._ridx(indr), ones (nrow, 1), 1);
453         if (length (df._name{1}) >= max (indr))
454           resu(3:end, 2) = df._name{1}{indr};
455         endif           
456       else
457         resu = cell (nrow, ncol);
458         row_offs = 0; col_offs = 0;
459       endif
460       for indi = (1:ncol)
461         switch df._type{indc(indi)}                             % cell content
462           case {'char' }
463             %# dummy = cellstr(df._data{indc(indi)}(indr, :));
464             dummy = df._data{indc(indi)}(indr, :);
465             resu(1+row_offs:end, indi+col_offs) = dummy;
466           otherwise
467             dummy = df._data{indc(indi)}(indr, :);
468             resu(1+row_offs:end, indi+col_offs) = \
469                 mat2cell (dummy, ones (nrow, 1), size (dummy, 2));
470         endswitch
471       endfor
472
473       %# did we arrive here by x.cell ?
474       if (0 == length (S)) return; endif
475       
476       %# perform the selection on the content, keeping the header
477       if (length (S) > 1) %# perform further access, if required
478         if (~strcmp (S(2).type, '()'))
479           error ("Illegal dataframe-as-cell sub-dereferencing");
480         endif
481         if (!isempty (asked_output_format))
482           resu = feval(@subsref, resu, S(2:end));
483         else    
484           if (length (S(2).subs) != 1)
485             %# normal, two-dimensionnal access apply the selection on the
486             %# zone containing the data
487             dummy = S;
488             if (!isempty (dummy(2).subs))
489               dummy(2).subs{2} = ':';
490             endif
491             resuf = cat (2, \
492                          %# reselect indexes
493                          feval (@subsref, resu(3:end, 1),
494                                 dummy(2:end)), \
495                          %# reselect rownames
496                          feval (@subsref, resu(3:end, 2),
497                                 dummy(2:end)), \
498                          %# extract - reorder - whatever
499                          feval (@subsref, resu(3:end, 3:end), S(2:end))
500                          \
501                          );
502             dummy = S;
503             if (!isempty (dummy(2).subs))
504               dummy(2).subs{1} =  [1 2];
505             endif
506             resuf =  cat(1, \
507                          %# reselect column names and types
508                          [cell(2, 2) feval(@subsref, resu(1:2,
509                                                           3:end), \
510                                            dummy(2:end))], \
511                          resuf \
512                          );
513             resuf(1:2, 1:2) = {''}; resu = resuf;
514           else
515             %# one dimensionnal access of the whole 2D cell array -- you
516             %# asked it, you got it
517             resu = feval(@subsref, resu(:), S(2:end));
518             if (!isa(S(2).subs{1}, 'char') \
519                   && size (S(2).subs{1}, 2) > 1)
520               resu = resu.';
521             endif
522           endif
523         endif
524       elseif (1 == length (S(1).subs))
525         resu = resu(:);
526         if (!isa(S(1).subs{1}, 'char') \
527               && size (S(1).subs{1}, 2) > 1)
528           resu = resu.';
529         endif
530       endif
531       return; %# no more iteration required
532   
533     else
534       %# export the result as a vector/matrix. Rules:
535       %# * x(:, :, :) returns a 3D matrix 
536       %# * x(:, n:m, :) returns a 3D matrix 
537       %# * x(:, :) returns a horzcat of the third dimension 
538       %# * x(:, n:m) select only the first sequence 
539       %# * x(:) returns a vertcat of the columns of x(:, :)
540       %# disp('line 403 '); keyboard
541       if (isempty (S) || isempty (S(1).subs) || \
542           length (S(1).subs) > 1 || \
543           (isnumeric(S(1).subs{1}) && !isvector(S(1).subs{1}))) 
544         %# access-as-matrix
545         df = struct(df);        %# remove the magic, avoid recursive calls 
546         if (isempty (fullindr)) %# two index access
547           if (~isempty (asked_output_format)) %# force a conversion
548             if (strmatch(asked_output_format, 'cell'))
549               extractfunc = @(x) mat2cell\
550                   (df._data{indc(x)}(indr, df._rep{indc(x)}(inds)), \
551                    ones (nrow, 1));
552             else
553               extractfunc = @(x) cast ( df._data{indc(x)}\
554                                        (indr, df._rep{indc(x)}(inds)),\
555                                        asked_output_format);
556             endif
557           else %# let the usual downclassing occur
558             extractfunc = @(x) df._data{indc(x)}(indr, df._rep{indc(x)}(inds));
559           endif 
560           try
561             if (nseq > 1)
562               dummy = reshape (extractfunc (1), nrow, 1, []); 
563               if (size (dummy, 3) < nseq)
564                 dummy = repmat (dummy, [1 1 nseq]);
565               endif
566             else
567               dummy = extractfunc (1);
568             endif
569           catch
570             error ("Column %d format (%s) can't be converted to %s", \
571                    indc(1), df._type{indc(1)}, asked_output_format);
572           end_try_catch
573           if (ncol > 1)
574             %# dynamic allocation with the final type
575             resu = repmat (dummy, [1 ncol]);
576             for indi = (2:ncol)
577               try
578                 if (nseq > 1)
579                   dummy = reshape (extractfunc (indi), nrow, 1, []);
580                   if (size (dummy, 3) < nseq)
581                     dummy = repmat (dummy, [1 1 nseq]);
582                   endif
583                 else
584                   dummy = extractfunc (indi);
585                 endif
586               catch
587                 error ("Column %d format (%s) can't be converted to %s", \
588                        indc(indi), df._type{indc(indi)}, asked_output_format);
589               end_try_catch
590               resu(:, indi, :) = dummy;
591             endfor
592           else
593             if (strcmp (df._type{indc(1)}, 'char'))
594               resu = char (dummy);
595             else
596               resu = dummy;
597             endif
598           endif
599           if (!isempty (S) && 2 == length (S(1).subs) \
600               && all(cellfun('isclass', S(1).subs, 'char')))
601             resu = reshape (resu, nrow, ncol*nseq);
602           endif
603         else %# one index access
604           %# disp('line 557'); keyboard
605           if (~isempty (asked_output_format)) %# force a conversion
606             if (strmatch (asked_output_format, 'cell'))
607               extractfunc = @(x, y) mat2cell (df._data{x}(:, df._rep{x}(y)), \
608                                               ones (length (y), 1));
609             else
610               extractfunc = @(x, y) cast (df._data{x}(:, df._rep{x})(y), \
611                                           asked_output_format);      
612             endif
613           else %# let the usual downclassing occur
614             extractfunc = @(x, y) df._data{x}(:, df._rep{x})(y);
615           endif
616           try
617             resu = zeros(0, class (sum (cellfun (@(x) zeros (1, class (x(1))),\
618                                                  df._data(indc)))));
619             for indi = (indc)
620               dummy = find (indi == fullindc);   %# linear global index
621               %# linear index for this matrix
622               idx = sub2ind (size (df._data{indi}), fullindr(dummy), \
623                              fullinds(dummy));
624               resu(dummy) = extractfunc (indi, idx);
625             endfor
626           catch
627             disp (lasterr); 
628             error ("Column %d format (%s) can't be converted to %s", \
629                    indi, df._type{indi}, asked_output_format);
630           end_try_catch
631           resu = reshape (resu, size (onedimidx));
632         endif
633       else %# access-as-vector
634         %# disp('line 548 '); keyboard
635         if (!isempty (fullindr))
636           switch df._type{indc(1)}
637             case {'char'}
638               resu = df._data{indc(1)}(fullindr(1), \
639                                        df._rep{indc(1)}(fullinds(1)));
640               for indi = (2:length (fullindr))
641                 resu = char (resu, df._data{indc(indi)}\
642                              (fullindr(indi), df._rep{indc(indi)}(fullinds(indi))));
643               endfor
644             otherwise
645               if (isempty (asked_output_format))
646                 resu = df._data{fullindc(1)}\
647                     (fullindr(1), df._rep{fullindc(1)}(fullinds(1)));
648               else      %# this type will propagate with subsequent cat
649                 resu = cast (df._data{fullindc(1)}\
650                              (fullindr(1), df._rep{fullindc(1)}(fullinds(1))),\
651                              asked_output_format);
652               endif
653               for indi = (2:length (fullindr))
654                 resu = cat(1, resu, df._data{fullindc(indi)}\
655                            (fullindr(indi), \
656                             df._rep{fullindc(indi)}(fullinds(indi))));
657               endfor
658           endswitch
659         else %# using the (:) operator
660           resu = df_whole(df)(:);
661         endif
662         if (!isa(S(1).subs{1}, 'char') \
663               && size (S(1).subs{1}, 2) > 1)
664           resu = resu.';
665         endif
666       endif
667       if (length (S) > 1) %# perform further access, if required
668          %# disp('line 442 '); keyboard
669         resu = feval(@subsref, resu, S(2:end));
670       endif
671     endif
672     return; %# no more iteration required
673   endwhile
674
675   %# disp("line 343 !?!"); %# keyboard
676   return  
677   
678 endfunction