File Coverage

blib/lib/Rstats.pm
Criterion Covered Total %
statement 39 39 100.0
branch n/a
condition n/a
subroutine 10 10 100.0
pod n/a
total 49 49 100.0


line stmt bran cond sub pod time code
1             package Rstats;
2 21     21   443102 use strict;
  21         50  
  21         570  
3 21     21   103 use warnings;
  21         40  
  21         847  
4              
5             our $VERSION = '0.0148';
6              
7 21     21   11048 use Rstats::Class;
  21         69  
  21         198  
8              
9             sub import {
10 21     21   183 my $self = shift;
11            
12 21         65 my $class = caller;
13            
14 21         102 my $r = Rstats::Class->new;
15            
16             # Export primary methods
17 21     21   1245 no strict 'refs';
  21         40  
  21         971  
18 21         116 my @methods = qw/c_ C_ array matrix list data_frame factor ordered/;
19 21         59 for my $method (@methods) {
20 21     21   97 no strict 'refs';
  21         32  
  21         2961  
21 168         207 my $func = \&{"Rstats::Func::$method"};
  168         466  
22              
23 168     1502   786 *{"${class}::$method"} = sub { $func->($r, @_) }
  1502         368242  
24 168         686 }
25 21     1333   82 *{"${class}::r"} = sub { $r };
  21         101  
  1333         81439  
26            
27             # Export none argument methods
28 21         112 my @methods_no_args = qw/i_ T_ F_ TRUE FALSE NA NaN Inf NULL pi/;
29 21         49 for my $method (@methods_no_args) {
30 21     21   105 no strict 'refs';
  21         34  
  21         5233  
31 210         240 my $func = \&{"Rstats::Func::$method"};
  210         539  
32              
33 210     462   796 *{"${class}::$method"} = sub () { $func->($r, @_) };
  210         902  
  462         120253  
34             }
35            
36 21         65762 warnings->unimport('ambiguous');
37             }
38              
39             require XSLoader;
40             XSLoader::load('Rstats', $VERSION);
41              
42             1;
43              
44             =head1 NAME
45              
46             Rstats - R language build on Perl
47              
48             B
49              
50             =head1 SYNOPSYS
51            
52             use Rstats;
53            
54             # Vector
55             my $v1 = c_(1, 2, 3);
56             my $v2 = c_(3, 4, 5);
57            
58             my $v3 = $v1 + v2;
59             print $v3;
60            
61             # Sequence m:n
62             my $v1 = C_("1:3");
63              
64             # Matrix
65             my $m1 = matrix(C_("1:12"), 4, 3);
66            
67             # Array
68             my $a1 = array(C_("1:24"), c_(4, 3, 2));
69              
70             # Complex
71             my $z1 = 1 + 2 * i_;
72             my $z2 = 3 + 4 * i_;
73             my $z3 = $z1 * $z2;
74            
75             # Special value
76             my $true = TRUE;
77             my $false = FALSE;
78             my $na = NA;
79             my $nan = NaN;
80             my $inf = Inf;
81             my $null = NULL;
82            
83             # all methods are called from r
84             my $x1 = r->sum(c_(1, 2, 3));
85            
86             # Register helper
87             r->helper(my_sum => sub {
88             my ($r, $x1) = @_;
89            
90             my $total = 0;
91             for my $value (@{$x1->values}) {
92             $total += $value;
93             }
94            
95             return c_($total);
96             });
97             my $x2 = r->my_sum(c_(1, 2, 3));
98              
99             =head1 FUNCTIONS
100              
101             =head2 c_
102              
103             # c(1, 2, 3)
104             c_(1, 2, 3)
105              
106             Create vector. C function is equal to C of R.
107              
108             =head2 C_
109              
110             # 1:24
111             C_("1:24")
112              
113             C_ function is equal to C of R.
114              
115             =head2 array
116              
117             # array(1:24, c(4, 3, 2))
118             array(C_("1:24"), c_(4, 3, 2))
119              
120             =head2 TRUE
121              
122             # TRUE
123             TRUE
124              
125             =head2 T_
126              
127             # T
128             T_
129              
130             Alias of TRUE
131              
132             =head2 FALSE
133            
134             # FALSE
135             FALSE
136              
137             =head2 F_
138            
139             # F
140             F_
141              
142             Alias of FALSE
143              
144             =head2 NA
145              
146             # NA
147             NA
148              
149             =head2 NaN
150            
151             # NaN
152             NaN
153              
154             =head2 Inf
155              
156             # Inf
157             Inf
158              
159             =head2 NULL
160            
161             # NULL
162             NULL
163              
164             =head2 matrix
165              
166             # matrix(1:12, 4, 3)
167             matrix(C_("1:12"), 4, 3)
168            
169             # matrix(1:12, nrow=4, ncol=3)
170             matrix(C_("1:12"), {nrow => 4, ncol => 3});
171            
172             # matrix(1:12, 4, 3, byrow=TRUE)
173             matrix(C_("1:12"), 4, 3, {byrow => TRUE});
174              
175             =head1 VECTOR ACCESS
176              
177             =head2 Getter
178              
179             # x1[1]
180             $x1->get(1)
181              
182             # x1[1, 2]
183             $x1->get(1, 2)
184            
185             # x1[c(1,2), c(3,4)]
186             $x1->get(c_(1,2), c_(3,4))
187            
188             # x1[,2]
189             $x1->get(NULL, 2)
190            
191             # x1[-1]
192             $x1->get(-1)
193            
194             # x1[TRUE, FALSE]
195             $x1->get(TRUE, FALSE)
196            
197             # x1[c("id", "title")]
198             $x1->get(c_("id", "title"))
199              
200             =head2 Setter
201              
202             # x1[1] <- x2
203             $x1->at(1)->set($x2)
204              
205             # x1[1, 2] <- x2
206             $x1->at(1, 2)->set($x2)
207            
208             # x1[c(1,2), c(3,4)] <- x2
209             $x1->at(c_(1,2), c_(3,4))->set($x2)
210            
211             # x1[,2] <- x2
212             $x1->at(NULL, 2)->set($x2)
213            
214             # x1[-1] <- x2
215             $x1->at(-1)->set($x2)
216            
217             # x1[TRUE, FALSE] <- x2
218             $x1->at(TRUE, FALSE)->set($x2);
219            
220             # x1[c("id", "title")] <- x2
221             $x1->at(c_("id", "title"))->set($x2);
222              
223             =head1 OPERATORS
224              
225             # x1 + x2
226             $x1 + $x2
227            
228             # x1 - x2
229             $x1 - $x2
230            
231             # x1 * x2
232             $x1 * $x2
233            
234             # x1 / x2
235             $x1 / $x2
236            
237             # x1 ^ x2 (power)
238             $x1 ** $x2
239            
240             # x1 %% x2 (remainder)
241             $x1 % $x2
242              
243             # x1 %*% x2 (vector inner product or matrix product)
244             $x1 x $x2
245            
246             # x1 %/% x2 (integer quotient)
247             r->tranc($x1 / $x2)
248              
249             =head1 METHODS
250              
251             =head2 abs
252              
253             # abs(x1)
254             r->abs($x1)
255              
256             =head2 acos
257              
258             # acos(x1)
259             r->acos($x1)
260              
261             =head2 acosh
262              
263             # acosh(x1)
264             r->acosh($x1)
265              
266             =head2 append
267              
268             =head2 apply
269              
270             =head2 Arg
271              
272             =head2 array
273              
274             =head2 asin
275              
276             # asin(x1)
277             r->asin($x1)
278              
279             =head2 asinh
280              
281             # asinh(x1)
282             r->asinh($x1)
283              
284             =head2 atan2
285              
286             =head2 atan
287              
288             # atan(x1)
289             r->atan($x1)
290              
291             =head2 atanh
292              
293             # atanh(x1)
294             r->atanh($x1)
295              
296             =head2 c
297              
298             =head2 vec
299              
300             =head2 charmatch
301              
302             =head2 chartr
303              
304             =head2 cbind
305              
306             # cbind(c(1, 2), c(3, 4), c(5, 6))
307             r->cbind(c_(1, 2), c_(3, 4), c_(5, 6));
308              
309             =head2 ceiling
310              
311             # ceiling(x1)
312             r->ceiling($x1)
313              
314             =head2 col
315              
316             # col(x1)
317             r->col($x1)
318              
319             =head2 colMeans
320              
321             # colMeans(x1)
322             r->colMeans($x1)
323              
324             =head2 colSums
325              
326             =head2 Conj
327              
328             =head2 cos
329              
330             # cos(x1)
331             r->cos($x1)
332              
333             =head2 cosh
334              
335             # cosh(x1)
336             r->cosh($x1)
337              
338             =head2 cummax
339              
340             =head2 cummin
341              
342             =head2 cumsum
343              
344             =head2 cumprod
345              
346             =head2 complex
347              
348             =head2 data_frame
349              
350             =head2 diag
351              
352             =head2 diff
353              
354             =head2 exp
355              
356             # exp(x1)
357             r->exp($x1)
358              
359             =head2 expm1
360              
361             # expm1(x1)
362             r->expm1($x1)
363              
364             =head2 factor
365              
366             =head2 F
367              
368             =head2 FALSE
369              
370             =head2 floor
371              
372             # floor(x1)
373             r->floor($x1)
374              
375             =head2 gl
376              
377             =head2 grep
378              
379             =head2 gsub
380              
381             =head2 head
382              
383             =head2 i
384              
385             =head2 ifelse
386              
387             =head2 interaction
388              
389             =head2 is->element
390              
391             =head2 I
392              
393             =head2 Im
394              
395             =head2 Inf
396              
397             =head2 intersect
398              
399             =head2 kronecker
400              
401             =head2 length
402              
403             =head2 list
404              
405             =head2 log
406              
407             # log(x1)
408             r->log($x1)
409              
410             =head2 logb
411              
412             # logb(x1)
413             r->logb($x1)
414              
415             =head2 log2
416              
417             # log2(x1)
418             r->log2($x1)
419              
420             =head2 log10
421              
422             # log10(x1)
423             r->log10($x1)
424              
425             =head2 lower_tri
426              
427             =head2 match
428              
429             =head2 median
430              
431             =head2 merge
432              
433             =head2 Mod
434              
435             =head2 NA
436              
437             =head2 NaN
438              
439             =head2 na_omit
440              
441             =head2 ncol
442              
443             # ncol(x1)
444             r->ncol($x1)
445              
446             =head2 nrow
447              
448             # nrow(x1)
449             r->nrow($x1)
450              
451             =head2 NULL
452              
453             =head2 numeric
454              
455             =head2 matrix
456              
457             =head2 max
458              
459             =head2 mean
460              
461             =head2 min
462              
463             =head2 nchar
464              
465             =head2 order
466              
467             =head2 ordered
468              
469             =head2 outer
470              
471             =head2 paste
472              
473             =head2 pi
474              
475             =head2 pmax
476              
477             =head2 pmin
478              
479             =head2 prod
480              
481             =head2 range
482              
483             =head2 rank
484              
485             =head2 rbind
486              
487             # rbind(c(1, 2), c(3, 4), c(5, 6))
488             r->rbind(c_(1, 2), c_(3, 4), c_(5, 6))
489              
490             =head2 Re
491              
492             =head2 quantile
493              
494             =head2 read->table
495              
496             # read.table(...)
497             r->read->table(...)
498              
499             =head2 rep
500              
501             =head2 replace
502              
503             =head2 rev
504              
505             =head2 rnorm
506              
507             =head2 round
508              
509             # round(x1)
510             r->round($x1)
511              
512             # round(x1, digit)
513             r->round($x1, $digits)
514            
515             # round(x1, digits=1)
516             r->round($x1, {digits => TRUE});
517              
518             =head2 row
519              
520             # row(x1)
521             r->row($x1)
522              
523             =head2 rowMeans
524              
525             # rowMeans(x1)
526             r->rowMeans($x1)
527              
528             =head2 rowSums
529              
530             # rowSums(x1)
531             r->rowSums($x1)
532              
533             =head2 sample
534              
535             =head2 seq
536              
537             =head2 sequence
538              
539             =head2 set_diag
540              
541             =head2 setdiff
542              
543             =head2 setequal
544              
545             =head2 sin
546              
547             # sin(x1)
548             r->sin($x1)
549              
550             =head2 sinh
551              
552             # sinh(x1)
553             r->sinh($x1)
554              
555             =head2 sum
556              
557             =head2 sqrt
558              
559             # sqrt(x1)
560             r->sqrt($x1)
561              
562             =head2 sort
563              
564             =head2 sub
565              
566             =head2 subset
567              
568             =head2 sweep
569              
570             =head2 t
571              
572             # t
573             r->t($x1)
574              
575             =head2 tail
576              
577             =head2 tan
578              
579             # tan(x1)
580             r->tan($x1)
581              
582             =head2 tanh
583              
584             # tanh(x1)
585             r->tanh($x1)
586              
587             =head2 tapply
588              
589             =head2 tolower
590              
591             =head2 toupper
592              
593             =head2 T
594              
595             =head2 TRUE
596              
597             =head2 transform
598              
599             =head2 trunc
600              
601             # trunc(x1)
602             r->trunc($x1)
603              
604             =head2 unique
605              
606             =head2 union
607              
608             =head2 upper_tri
609              
610             =head2 var
611              
612             =head2 which
613              
614             =head2 as->array
615              
616             # as.array(x1)
617             r->as->array($x1)
618              
619             =head2 as->character
620              
621             # as.character(x1)
622             r->as->character($x1)
623              
624             =head2 as->complex
625              
626             # as.complex(x1)
627             r->as->complex($x1)
628              
629             =head2 as->integer
630              
631             # as.integer(x1)
632             r->as->integer($x1)
633              
634             =head2 as->list
635              
636             # as.list
637             r->as->list($x1)
638              
639             =head2 as->logical
640              
641             # as.logical
642             r->as->logical($x1)
643              
644             =head2 as->matrix
645              
646             # as.matrix(x1)
647             r->as->matrix($x1)
648              
649             =head2 as->numeric
650              
651             # as.numeric(x1)
652             r->as->numeric($x1)
653              
654             =head2 as->vector
655              
656             # as.vector(x1)
657             r->as->vector($x1)
658              
659             =head2 is->array
660              
661             # is.array(x1)
662             r->is->array($x1)
663              
664             =head2 is->character
665              
666             # is.character(x1)
667             r->is->character($x1)
668              
669             =head2 is->complex
670              
671             # is.complex(x1)
672             r->is->complex($x1)
673              
674             =head2 is->finite
675              
676             # is.finite(x1)
677             r->is->finite($x1)
678              
679             =head2 is->infinite
680              
681             # is.infinite(x1)
682             r->is->infinite($x1)
683              
684             =head2 is->list
685              
686             # is.list(x1)
687             r->is->list($x1)
688              
689             =head2 is->matrix
690              
691             # is.matrix(x1)
692             r->is->matrix($x1)
693              
694             =head2 is->na
695              
696             # is.na(x1)
697             r->is->na($x1)
698              
699             =head2 is->nan
700              
701             # is.nan(x1)
702             r->is->nan($x1)
703              
704             =head2 is->null
705              
706             # is.null(x1)
707             r->is->null($x1)
708              
709             =head2 is->numeric
710              
711             # is.numeric(x1)
712             r->is->numeric($x1)
713              
714             =head2 is->double
715              
716             # is.double(x1)
717             r->is->double($x1)
718              
719             =head2 is->integer
720              
721             # is.integer(x1)
722             r->is->integer($x1)
723              
724             =head2 is->logical
725              
726             # is.logical(x1)
727             r->is->logical($x1)
728              
729             =head2 is->vector
730              
731             # is.vector(x1)
732             r->is->vector($x1)
733              
734             =head2 labels
735              
736             # labels(x1)
737             r->labels($x1)
738              
739             =head2 levels
740              
741             # levels(x1)
742             r->levels($x1)
743            
744             # levels(x1) <- c("F", "M")
745             r->levels($x1 => c_("F", "M"))
746              
747             =head2 dim
748              
749             # dim(x1)
750             r->dim($x1)
751            
752             # dim(x1) <- c(1, 2)
753             r->dim($x1 => c_(1, 2))
754              
755             =head2 names
756              
757             # names(x1)
758             r->names($x1)
759              
760             # names(x1) <- c("n1", "n2")
761             r->names($x1 => c_("n1", "n2"))
762              
763             =head2 nlevels
764              
765             # nlevels(x1)
766             r->nlevels($x1)
767              
768             =head2 dimnames
769              
770             # dimnames(x1)
771             r->dimnames($x1)
772            
773             # dimnames(x1) <- list(c("r1", "r2"), c("c1", "c2"))
774             r->dimnames($x1 => list(c_("r1", "r2"), c_("c1", "c2")))
775              
776             =head2 colnames
777              
778             # colnames(x1)
779             r->colnames($x1)
780            
781             # colnames(x1) <- c("r1", "r2")
782             r->colnames($x1 => c_("r1", "r2"))
783              
784             =head2 rownames
785              
786             # rownames(x1)
787             r->rownames($x1)
788            
789             # rownames(x1) <- c("r1", "r2")
790             r->rownames($x1 => c_("r1", "r2"))
791              
792             =head2 mode
793              
794             # mode(x1)
795             r->mode($x1)
796            
797             # mode(x1) <- c("r1", "r2")
798             r->mode($x1 => c_("r1", "r2"))
799              
800             =head2 str
801              
802             # str(x1)
803             r->str($x1)
804              
805             =head2 typeof
806              
807             # typeof(x1)
808             r->typeof($x1);