diff --git a/NAMESPACE b/NAMESPACE
index 072919dafaa86df497c4a62e8cbabcfedf1d4e83..07aa5b6bef5a8fe15688d9433e87fc4da982a87e 100644
--- a/NAMESPACE
+++ b/NAMESPACE
@@ -5,6 +5,7 @@ S3method(lines,mfft_deco)
 S3method(plot,SSAObject)
 S3method(plot,memObject)
 S3method(plot,mfft_deco)
+S3method(plot,mmfft)
 S3method(plot,periodogram)
 S3method(plot,wavelet)
 S3method(print,mfft_deco)
diff --git a/R/mmfft.R b/R/mmfft.R
index ae445c841d4af782c74cdb4597b38d4a4d1a58f8..f0497ef8d73c21107f2dc0496e58f6cce854341d 100644
--- a/R/mmfft.R
+++ b/R/mmfft.R
@@ -26,6 +26,7 @@ mmfft <- function(xdata, seglength = length(xdata) %/% 16, ...){
 }
   
 #' @rdname mmfft
+#' @export
 plot.mmfft <- function(x){
   freqrange <- 
     c(min(sapply(x, function(xs) min(xs$Freq))), 
@@ -35,7 +36,6 @@ plot.mmfft <- function(x){
     c(min(sapply(x, function(xs) min(xs$Amp))), 
       max(sapply(x, function(xs) max(xs$Amp))))
 
-  print(amprange)
   amp2lwd <- function(amp){ 3*amp/amprange[2] }
 
   length <- attr(x, "nsections") * 
@@ -48,17 +48,13 @@ plot.mmfft <- function(x){
   tstart <- attr(x,"start")
   tend   <- tstart  + nsec * tsec
 
-  print(freqrange)
-  print(c(tstart, tend))
   plot(c(tstart, tend), freqrange, type='n', xlab='Time', ylab='Rate')
  
   for (iseq in seq(nsec)){
     trange <- tstart + c(iseq-1,iseq)*tsec
     obj <- x[[iseq]]
     nfreq <- length(obj$Freq)
-    print(obj$Amp)
     lwds <- sapply(obj$Amp, amp2lwd)
-    print(lwds)
     for (j in seq(nfreq)){
       lines(trange, rep(obj$Freq[j],2), lwd=lwds[j])
     }
@@ -66,7 +62,3 @@ plot.mmfft <- function(x){
 
 }
 
-
-
-
-
diff --git a/R/toneCombinations.R b/R/toneCombinations.R
index 8bbbd9fda5fe3f150de204fb5f64cabe3f75389b..34ac0e7343f6a7cb8386839836c9bf1c4684bc40 100644
--- a/R/toneCombinations.R
+++ b/R/toneCombinations.R
@@ -6,6 +6,7 @@
 #' @importFrom RcppAlgos comboGeneral
 #' @param omegas: vector of references frequencies, optionally with rownames, 
 #' @param keepPositives : if TRUE, then only keeps positive combinations of frequencies
+#' @param fractions : defaults 1. Set 2 to include double-periods, and 3 triple-periods. 
 #' @return a vector with combination of tones and explicit rownames, using, if available, the
 #'         rownames provided in the input vector omega
 #' @author Michel Crucifix
@@ -14,7 +15,24 @@
 #' omegas <- c( 0.123, 0.14312, 0.33251, 0.554313)
 #' print(toneCombinations(omegas))
 
-toneCombinations <- function(omegas, keepPositives=TRUE){
+toneCombinations <- function(omegas, fractions=1, keepPositives=TRUE){
+ if (fractions == 2){
+   local({
+   tmp <- c(as.numeric(omegas), as.numeric(omegas)/2)
+   names(tmp) <- c(names(omegas), sprintf("%s/2", names(omegas)))
+   omegas <<- tmp
+   })
+ }
+
+ if (fractions == 3){
+   local({
+   tmp <- c(as.numeric(omegas), as.numeric(omegas)/2, as.numeric(omegas)/3)
+   names(tmp) <- c(names(omegas), sprintf("%s/2", names(omegas)), sprintf("%s/3", names(omegas)))
+   omegas <<- tmp
+   })
+ }
+
+
  twoomegas <- c(-omegas,omegas)
  indices  <- c(-seq(length(omegas)), seq(length(omegas)))
  result = rbind(
@@ -75,6 +93,7 @@ generate_name <- function(invec,char="s", labels = NULL){
 #' 
 #' @param infreq : input frequencies
 #' @param omegas : reference frequencies (a numeric vector which may contain explicit row names)
+#' @param fractions : 1, 2, or 3 depending on willing to include singe, double or triple periods
 #' @param tol1 : acceptable tolerance for being considered as a certain attribution
 #'               (if several frequencies match the criteria, the closest will be taken)
 #' @param tol2 : acceptable tolerance for being considered as a likely or plausible
@@ -93,9 +112,9 @@ generate_name <- function(invec,char="s", labels = NULL){
 #' plot(outfreqs, outamps, type='h')
 #' text(outfreqs, outamps+0.1, attributions)
 #'
-attributeTones <- function(infreq , omegas, tol1 = 1.e-6, tol2 = 1.e-4) { 
+attributeTones <- function(infreq , omegas, fractions=1, tol1 = 1.e-6, tol2 = 1.e-4) { 
   attributions <- rep("", length(infreq))
-  combis <- toneCombinations(omegas)
+  combis <- toneCombinations(omegas, fractions=fractions)
   for (i in seq(infreq)){
     deltas <- abs(infreq[i] - combis)
     bestSuspect <- which.min(abs(infreq[i] - combis))
diff --git a/man/attributeTones.Rd b/man/attributeTones.Rd
index 00f347d5ebc32a1bf3cd124ccf9729fde4a8e4c0..0d962e072a2b5591bd8d2f3148bb555228b3a241 100644
--- a/man/attributeTones.Rd
+++ b/man/attributeTones.Rd
@@ -4,13 +4,15 @@
 \alias{attributeTones}
 \title{Attribution of combination of tones}
 \usage{
-attributeTones(infreq, omegas, tol1 = 1e-06, tol2 = 1e-04)
+attributeTones(infreq, omegas, fractions = 1, tol1 = 1e-06, tol2 = 1e-04)
 }
 \arguments{
 \item{infreq}{: input frequencies}
 
 \item{omegas}{: reference frequencies (a numeric vector which may contain explicit row names)}
 
+\item{fractions}{: 1, 2, or 3 depending on willing to include singe, double or triple periods}
+
 \item{tol1}{: acceptable tolerance for being considered as a certain attribution
 (if several frequencies match the criteria, the closest will be taken)}
 
diff --git a/man/toneCombinations.Rd b/man/toneCombinations.Rd
index a716e1b81973d234492c0871128497f73c75ee45..7f6bc125d5414926726ddbb979f76b0f02600a3d 100644
--- a/man/toneCombinations.Rd
+++ b/man/toneCombinations.Rd
@@ -4,9 +4,11 @@
 \alias{toneCombinations}
 \title{Generation of combination of tones}
 \usage{
-toneCombinations(omegas, keepPositives = TRUE)
+toneCombinations(omegas, fractions = 1, keepPositives = TRUE)
 }
 \arguments{
+\item{fractions}{: defaults 1. Set 2 to include double-periods, and 3 triple-periods.}
+
 \item{keepPositives}{: if TRUE, then only keeps positive combinations of frequencies}
 
 \item{omegas:}{vector of references frequencies, optionally with rownames,}