Hello,

You forgot to cc the list, I'm replying all to have a complete thread so that others now and in the future can search similar problems they might encounter.
The following function bin2dec works as expected.


bin2dec <- function(x){
  s <- strsplit(x, "")
  s <- lapply(s, function(x){
    sum(as.integer(x)*2^((length(x) - 1):0))
  })
  unlist(s)
}


bin2dec("001100001111010101000011011110")
#[1] 205344990

b <- utf8ToBin("133m@ogP00PD;88MD5MTDww@2D7k", out = "bin")
bin2dec(b)
# [1]  1  3  3 53 16 55 47 32  0  0 32 20 11  8  8 29 20  5 29 36
#[21] 20 63 63 16  2 20  7 51


Hope this helps,

Rui Barradas

Às 20:52 de 27/12/19, Paul Bernal escreveu:
   Dear friend Rui,

Hope you are doing well, thanks for the previous feedback,

I have tried different things but have not been able to convert binary numbers back to decimal, to test if the output is  correct, I am taking the binary sequence = "001100001111010101000011011110" as a string, and this should give the following value (after converting back to decimal) = 205,344,990‬

I have labeled my different attempts as (Attempt 1, ..., Attempt 3) but none have worked (see the code below):

library(stringi)
library(dplyr)
library(R.utils)


#dataset1 <- data.frame(maml.mapInputPort(1)) # class: data.frame


ascii_datformat <- utf8ToInt("133m@ogP00PD;88MD5MTDww@2D7k")
ascii_datformat

Base <- ascii_datformat - 48

decy <- ifelse(Base > 40, Base-8, Base)


biny <- intToBin(decy)

binyframe <- data.frame(biny)

tbinyframe <- paste(t(binyframe[,1]), collapse="")

binyframe
tbinyframe

# Attempt 1

bin2dec <- function(x)
{
   x <- as.character(as.numeric(x))
   b <- as.numeric(unlist(strsplit(x, "")))
   pow <- 2 ^ ((length(b) - 1):0)
   sum(pow[b == 1])
}

# Attempt 2
#bin2dec.easy <- function(binaryvector) {
#  sum(2^(which(rev(binaryvector)==TRUE)-1))
#}

# Attempt 3

#utf8ToBin <- function(x, out = c("ascii", "dec", "bin")){
#   out <- match.arg(out)
#   ascii_datformat <- utf8ToInt(x)
#   Base <- ascii_datformat - 48
#   Base <- ifelse(Base > 40, Base - 8, Base)
#   Bin <- R.utils::intToBin(Base)
#   switch (out,
#     "ascii" = ascii_datformat,
#     "dec" = Base,
#     "bin" = Bin
#   )
#}


z <- substr(tbinyframe, 9, 38)

result <- bin2dec(z)
result

Any guidance will be greatly appreciated,

Best regards,

Paul

El vie., 27 dic. 2019 a las 12:31, Rui Barradas (<ruipbarra...@sapo.pt <mailto:ruipbarra...@sapo.pt>>) escribió:

    Hello,


    Your code and the answers provided, specially Marc's, led me to


    utf8ToBin <- function(x, out = c("ascii", "dec", "bin")){
        out <- match.arg(out)
        ascii_datformat <- utf8ToInt(x)
        Base <- ascii_datformat - 48
        Base <- ifelse(Base > 40, Base - 8, Base)
        Bin <- R.utils::intToBin(Base)
        switch (out,
          "ascii" = ascii_datformat,
          "dec" = Base,
          "bin" = Bin
        )
    }

    utf8ToBin("133m@", out = "ascii")
    utf8ToBin("133m@", out = "dec")
    utf8ToBin("133m@", out = "bin")


    Hope this helps,

    Rui Barradas

    Às 16:30 de 27/12/19, Paul Bernal escreveu:
     > Dear Jeff,
     >
     > Hope you are doing great. The link I provide below has the
    results I am
     > expecting. I am doing a test, trying to convert this string:
    "133m@ogP00PD
     > ;88MD5MTDww@2D7k" into ascii numbers, then to decimal, and
    ultimately, into
     > binary. I am trying to recreate the results obtained in the link
    below.
     >
     > http://www.it-digin.com/blog/?p=20
     >
     > Hope this answers your question.
     >
     > Thanks for any guidance you can provide,
     >
     > Cheers,
     >
     > Paul
     >
     > El vie., 27 dic. 2019 a las 11:18, Jeff Newmiller
    (<jdnew...@dcn.davis.ca.us <mailto:jdnew...@dcn.davis.ca.us>>)
     > escribió:
     >
     >> Your question is incomplete... what do you expect the result to be?
     >>
     >> Perhaps [1] is relevant?
     >>
     >> [1]
     >>
    
https://stackoverflow.com/questions/52298995/r-binary-decimal-conversion-confusion-ais-data
     >>
     >> On December 27, 2019 7:42:36 AM PST, Paul Bernal
    <paulberna...@gmail.com <mailto:paulberna...@gmail.com>>
     >> wrote:
     >>> Dear friends,
     >>>
     >>> Hope you are all doing well. I need to find a way to convert ascii
     >>> numbers
     >>> to six digit binary numbers:
     >>>
     >>> I am working with this example, I converted the string to
    ascii, and
     >>> finally to decimal, but I am having trouble converting the decimal
     >>> numbers
     >>> into their six digit binary representation. The code below is
    exactly
     >>> what
     >>> I have so far:
     >>>
     >>> ascii_datformat <- utf8ToInt("133m@ogP00PD;88MD5MTDww@2D7k")
     >>> ascii_datformat
     >>>
     >>> Base <- ascii_datformat - 48
     >>>
     >>> ifelse(Base > 40, Base-8, Base)
     >>>
     >>> x <- rev(intToBits(Base))
     >>> dec2bin <- function(x) paste(as.integer(rev(intToBits(x))),
    collapse =
     >>> "")
     >>> dec2bin
     >>>
     >>> any guidance will be greatly appreciated,
     >>>
     >>> Best regards,
     >>>
     >>> Paul
     >>>
     >>>        [[alternative HTML version deleted]]
     >>>
     >>> ______________________________________________
     >>> R-help@r-project.org <mailto:R-help@r-project.org> mailing list
    -- To UNSUBSCRIBE and more, see
     >>> https://stat.ethz.ch/mailman/listinfo/r-help
     >>> PLEASE do read the posting guide
     >>> http://www.R-project.org/posting-guide.html
     >>> and provide commented, minimal, self-contained, reproducible code.
     >>
     >> --
     >> Sent from my phone. Please excuse my brevity.
     >>
     >
     >       [[alternative HTML version deleted]]
     >
     > ______________________________________________
     > R-help@r-project.org <mailto:R-help@r-project.org> mailing list
    -- To UNSUBSCRIBE and more, see
     > https://stat.ethz.ch/mailman/listinfo/r-help
     > PLEASE do read the posting guide
    http://www.R-project.org/posting-guide.html
     > and provide commented, minimal, self-contained, reproducible code.
     >


______________________________________________
R-help@r-project.org mailing list -- To UNSUBSCRIBE and more, see
https://stat.ethz.ch/mailman/listinfo/r-help
PLEASE do read the posting guide http://www.R-project.org/posting-guide.html
and provide commented, minimal, self-contained, reproducible code.

Reply via email to