Skip to content

Commit

Permalink
Merge branch 'develop'
Browse files Browse the repository at this point in the history
Conflicts:
	R/charge.R
  • Loading branch information
dosorio committed Dec 15, 2014
2 parents a68f1e2 + 0376487 commit 9ab880f
Show file tree
Hide file tree
Showing 22 changed files with 112 additions and 132 deletions.
7 changes: 3 additions & 4 deletions DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,11 +1,10 @@
Package: Peptides
Version: 1.0
Date: 2014-08-30
Version: 1.0.2
Date: 2014-11-15
Title: Calculate indices and theoretical physicochemical properties of peptides and protein sequences
Author: Daniel Osorio, Paola Rondon-Villarreal and Rodrigo Torres.
Maintainer: Daniel Osorio <[email protected]>
URL: https://github.com/dosorio/Peptides/
Depends: seqinr , R (>= 2.10.0)
Suggests: RUnit
Description: Calculate physicochemical properties and indices from aminoacid sequences of peptides and proteins. Include also utilities for read and plot GROMACS output files .XVG.
Description: Calculate physicochemical properties and indices from aminoacid sequences of peptides and proteins. Include also utilities for read and plot GROMACS output files.
License: GPL-2
1 change: 0 additions & 1 deletion NAMESPACE
Original file line number Diff line number Diff line change
@@ -1,2 +1 @@
exportPattern("^[[:alpha:]]+")
importFrom( seqinr, s2c )
6 changes: 3 additions & 3 deletions R/AAcomp.R
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ aacomp<-function(seq){
rownames(AA)<-c("Tiny","Small","Aliphatic","Aromatic","NonPolar","Polar","Charged","Basic","Acidic")
colnames(AA)<-c("Number","Mole%")
# Divide the amino acid sequence and makes a frequencies table
seq1<-table(s2c(toupper(seq)))
seq1<-table(strsplit(toupper(seq),"")[[1]])
# Classify amino acids in a particular class and sum the absolute frequencies
AA[1,1]<-sum(seq1[c("A","C","G","S","T")],na.rm = TRUE)
AA[2,1]<-sum(seq1[c("A","B","C","D","G","N","P","S","T","V")],na.rm = TRUE)
Expand All @@ -23,6 +23,6 @@ aacomp<-function(seq){
AA[9,1]<-sum(seq1[c("B","D","E","Z")],na.rm = TRUE)
# Compute the relative frequencies for each class in percentage
AA[,2]<-(AA[,1]/nchar(seq)*100)
# Return output matrix rounded to 2 decimals
return(round(AA,2))
# Return output matrix rounded to 3 decimals
return(round(AA,3))
}
2 changes: 1 addition & 1 deletion R/Boman.R
Original file line number Diff line number Diff line change
Expand Up @@ -10,5 +10,5 @@ boman<-function(seq){
H=-4.66, Q=-5.54, K=-5.55, N=-6.64, E=-6.81, D=-8.72, R=-14.92)
# Asign a value to each amino acids in the sequence, sum the values and divide on amino acid sequence length
# Report the index rounded to 2 decimals
round(-1*sum(boman[s2c(toupper(seq))],na.rm=T)/nchar(seq),2)
return(-1*sum(boman[strsplit(toupper(seq),"")[[1]]],na.rm=T)/nchar(seq))
}
4 changes: 2 additions & 2 deletions R/MW.R
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ mw<-function(seq){
G=57.0519, H=137.1411, I=113.1594, L=113.1594, K=128.1741, M=131.1926, F=147.1766,
P=97.1167, S=87.0782, T=101.1051, W=186.2132, Y=163.1760, V=99.1326, U=150.0388,
O=237.3018)
# Sum the weight of each amino acid and add 18,2
# Sum the weight of each amino acid and add 18,02
# Return the MW rounded to 2 decimals
round(sum(weight[s2c(toupper(seq))],na.rm=TRUE)+18.0153,2)
sum(weight[strsplit(toupper(seq),split = "")[[1]]],na.rm=TRUE)+18.0153
}
2 changes: 1 addition & 1 deletion R/aindex.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@

aindex<-function(seq){
# Divide the amino acid sequence and extracts the relative frequency of Alanine, Valine, Leucine and Isoleucine
p<-(table(factor(s2c(toupper(seq)),levels = c("A","V","L","I")))/nchar(seq))
p<-table(strsplit(toupper(seq),"")[[1]])/nchar(seq)

# Aliphatic index = X(Ala) + a * X(Val) + b * ( X(Ile) + X(Leu) )
# where X(Ala), X(Val), X(Ile), and X(Leu) are mole percent (100 X mole fraction)
Expand Down
8 changes: 6 additions & 2 deletions R/charge.R
Original file line number Diff line number Diff line change
Expand Up @@ -4,13 +4,17 @@
# The net charge can be calculated using one of the 9 pKa scales availables Bjellqvist, EMBOSS, Murray, Sillero, Solomon,
# Stryer, Lehninger, Dawson or Rodwell

<<<<<<< HEAD
charge <- function(seq,pH=7,pKscale= "Lehninger"){
=======
charge <- function(seq,pH=7,pKscale="EMBOSS"){
>>>>>>> develop
# # Divide the amino acid sequence and makes an absolute frequencies table
aa<-table(factor(prot<-s2c(toupper(seq)),levels = LETTERS))
aa<-table(factor(prot<-strsplit(toupper(seq),"")[[1]],levels = LETTERS))
# Set pKscale
data(pKscales, envir = environment())
pKscales<-pKscales
pKs<-pKscales[,pmatch(pKscale,names(pKscales))]
pKs<-pKscales[,match.arg(pKscale,names(pKscales))]
names(pKs) <- rownames(pKscales)
# Charge
cterm <- (-1 /(1+10^(-1*(pH-pKs["cTer"]))))
Expand Down
43 changes: 18 additions & 25 deletions R/hmoment.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,30 +3,23 @@
# The hydrophobic moment detects periodicity in protein hydrophobicity.
# Proceedings of the National Academy of Sciences of the United States of America, 81(1), 140–4.

hmoment<-function(seq,angle){
# Loading Hydrophobicity scales
data(H, envir = environment())
# Setting global variables
H<-H
AA<-s2c(toupper(seq))
# Setting input length
if(nchar(seq)>10){
Pep<-NULL
for (i in 1: (nchar(seq)-9)){
Pep[i]<-paste(AA[i:(i+9)],collapse ="")}
}else{
Pep<-seq
}
# Defining the moment function
moment<-function(seq,angle){
vcos<-vsin<-uH<-NULL
aa<-s2c(toupper(seq))
for (i in 1: nchar(seq)){
vcos[i]<-(as.array(H[[12]])[aa[i]]*(cos((angle*(pi/180))*i)))
vsin[i]<-(as.array(H[[12]])[aa[i]]*(sin((angle*(pi/180))*i)))}
round(sqrt(sum(vcos,na.rm=TRUE)^2+sum(vsin,na.rm=TRUE)^2)/nchar(seq),2)
}
hmoment<-function(seq,angle=100,window=11){
# Load hydrophobicity scale
data(H,envir = environment())
h<-H[["Eisenberg"]]
# Spliting the sequence
aa<-strsplit(toupper(seq),"")[[1]]
window<-min(length(aa),window)
# Setting the sequences
pep<-embed(aa,window)
# Evaluating angles and functions
angle<- angle*(pi/180)*1:window
vcos<-h[t(pep)]*cos(angle)
vsin<-h[t(pep)]*sin(angle)
dim(vcos)<-dim(vsin)<-dim(t(pep))
vcos<-colSums(vcos)
vsin<-colSums(vsin)
# Applying the moment function to each 10 amino acids window
# Return the max value rounded to 3 decimals
max(sapply(Pep,function(x)moment(x,angle)))
# Return the max value
max(sqrt(vsin*vsin + vcos*vcos)/window)
}
8 changes: 4 additions & 4 deletions R/hydrophobicity.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,17 +5,17 @@
# A simple method for displaying the hydropathic character of a protein.
# Journal of Molecular Biology, 157(1), 105–32.

hydrophobicity<-function(seq,scale){
hydrophobicity<-function(seq,scale="KyteDoolittle"){
# Setting the hydrophobicity scale
M<-c("KyteDoolittle","AbrahamLeo", "BullBreese", "Guy", "Miyazawa", "Roseman", "Wolfenden",
"Wilson", "Cowan3.4", "Aboderin", "Sweet", "Eisenberg", "HoppWoods", "Manavalan",
"BlackMould", "Fauchere", "Janin", "Rao", "Tanford", "Cowan7.5", "Chothia",
"Rose")
scale<-pmatch(scale,M)
scale<-match.arg(scale,M)
# Loading hydrophobicity scales
data(H, envir = environment())
H<-H
# Sum the hydrophobicity of each amino acid and divide them between the sequence length
# Return the GRAVY value rounded to 2 decimals
round(sum(H[[scale]][s2c(toupper(seq))],na.rm = TRUE)/nchar(seq),2)
# Return the GRAVY value
sum(H[[scale]][strsplit(seq,"")[[1]]])/nchar(seq)
}
6 changes: 3 additions & 3 deletions R/instaindex.R
Original file line number Diff line number Diff line change
Expand Up @@ -32,13 +32,13 @@ instaindex<-function(seq){
AG=1,AA=1,AL=1,LW=24.68,LC=1,LM=1,LH=1,LY=1,LF=1,LQ=33.6,LN=1,LI=1,LR=20.26,LD=1,LP=20.26,LT=1,LK=-7.49,
LE=1,LV=1,LS=1,LG=1,LA=1,LL=1,"NA"=1)
# Divide the amino acid sequence in dipeptides
dp<-NULL
AA<-s2c(toupper(seq))
dp<-character(nchar(seq)-1)
AA<-strsplit(toupper(seq),"")[[1]]
for (i in 1: (nchar(seq)-1)){
dp[i]<-paste(AA[i:(i+1)],collapse = "")
}
# Apply the formula:
# (10/L)*sum(DIWV(XiYi+1) for each dipeptide)
# Return the index value rounded to 2 decimals
round((10/nchar(seq))*sum(guruprasad[dp],na.rm = TRUE),2)
(10/nchar(seq))*sum(guruprasad[dp],na.rm = TRUE)
}
45 changes: 16 additions & 29 deletions R/membpos.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,37 +3,24 @@
# Eisenberg, D. (1984). Three-dimensional structure of membrane and surface proteins.
# Annual Review of Biochemistry, 53, 595–623. doi:10.1146/annurev.bi.53.070184.003115

membpos<-function(seq,angle){
membpos<-function(seq,angle=100){
# Setting input length
AA<-s2c(toupper(seq))
if(nchar(seq)>11){
Pep<-NULL
for (i in 1: (nchar(seq)-10)){
Pep[i]<-paste(AA[i:(i+10)],collapse ="")}
}else{
Pep<-toupper(seq)
aa<-strsplit(toupper(seq),"")[[1]]
window<-min(length(aa),11)
pep<-character(nchar(seq)-window)
for (i in 1: (nchar(seq)-window)){
pep[i]<-paste(aa[i:(i+window)],collapse = "")
}
# Compute the hmoment and hydrophobicity for each amino acid window
data<-NULL
data$Pep<-as.vector(Pep)
data$H<-as.vector(sapply(Pep,function(x)hydrophobicity(x,"Eisenberg")))
data$uH<-round(as.vector(sapply(Pep,function(x)hmoment(x,angle))),2)
data$m<-((-0.421*data$H)+0.579)

data<-as.data.frame(matrix(nrow = length(pep),ncol = 5))
data[,1]<-pep
data[,2]<-round(as.vector(sapply(pep,function(x)hydrophobicity(x,"Eisenberg"))),3)
data[,3]<-round(as.vector(sapply(pep,function(x)hmoment(x,angle,window))),3)
data[,4]<-(data[,2]*-0.421)+0.579
colnames(data)<-c("Pep","H","uH","m","MembPos")
# Assigns a class depending on the hydrophobicity and hmoment
for (i in 1: length(Pep)){
if(data$uH[i]<=data$m[i] & data$H[i]>=0.5){
data$MembPos[i]<-"Transmembrane"
}else{
if (data$uH[i]<=data$m[i] & data$H[i]<=0.5){
data$MembPos[i]<-"Globular"
}
else{
if(data$uH[i]>=data$m[i]){
data$MembPos[i]<-"Surface"
}
}
}
}
return(as.data.frame(data[-4]))
data[which(data$uH<=data$m & data$H>=0.5),5]<-"Transmembrane"
data[which(data$uH<=data$m & data$H<=0.5),5]<-"Globular"
data[which(data$uH>=data$m),5]<-"Surface"
return(data[-4])
}
5 changes: 2 additions & 3 deletions R/pI.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,14 +2,13 @@
# This function computes the theoretical pI of a protein sequence using one of the 9 pKa scales availables
# Bjellqvist, EMBOSS, Murray, Sillero, Solomon, Stryer, Lehninger, Dawson or Rodwell

pI<-function (seq,pKscale)
pI<-function (seq,pKscale="EMBOSS")
{
# Define pH values
pHs <- seq(0 , 14 , 0.001)
# Evaluate the net charge for defined pHs
charges <- charge(seq,pHs,pKscale)
# Computes the pI and returns the value rounded to 3 decimals
I <- round(mean(pHs[which(abs(charges)==min(abs(charges)))]),3)
return(I)
return(pHs[which.min(abs(charges))])
}

Binary file modified data/Pepdata.RData
Binary file not shown.
2 changes: 1 addition & 1 deletion inst/tests/runit.boman.R
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ test.boman <- function(){
# BOMAN INDEX -1.24

# CHECK VALUES
checkEquals(boman("FLPVLAGLTPSIVPKLVCLLTKKC"),-1.24)
checkEquals(boman("FLPVLAGLTPSIVPKLVCLLTKKC"),-1.24,tolerance = 0.01)

# CHECK OUTPUT CLASS
checkTrue(is.numeric(boman("FLPVLAGLTPSIVPKLVCLLTKKC")))
Expand Down
6 changes: 3 additions & 3 deletions inst/tests/runit.charge.R
Original file line number Diff line number Diff line change
Expand Up @@ -8,9 +8,9 @@ test.charge <- function(){
# COMPARED TO YADAMP
# http://yadamp.unisa.it/showItem.aspx?yadampid=845&x=0,7055475
# SEQUENCE: FLPVLAGLTPSIVPKLVCLLTKKC
checkEquals(round(charge("FLPVLAGLTPSIVPKLVCLLTKKC",5,pKscale = "Lehn"),1),3)
checkEquals(round(charge("FLPVLAGLTPSIVPKLVCLLTKKC",7,pKscale = "Lehn"),1),2.9)
checkEquals(round(charge("FLPVLAGLTPSIVPKLVCLLTKKC",9,pKscale = "Lehn"),1),1.0)
checkEquals(charge("FLPVLAGLTPSIVPKLVCLLTKKC",5,pKscale = "Lehn"),3,tolerance = 0.01)
checkEquals(charge("FLPVLAGLTPSIVPKLVCLLTKKC",7,pKscale = "Lehn"),2.9,tolerance = 0.01)
checkEquals(charge("FLPVLAGLTPSIVPKLVCLLTKKC",9,pKscale = "Lehn"),1.0,tolerance = 0.01)

# CHECK OUTPUT CLASS
checkTrue(is.numeric(charge("FLPVLAGLTPSIVPKLVCLLTKKC",7,pKscale = "Bjellqvist")))
Expand Down
4 changes: 2 additions & 2 deletions inst/tests/runit.hmoment.R
Original file line number Diff line number Diff line change
Expand Up @@ -6,10 +6,10 @@ test.hmoment <- function(){
# BETA-SHEET 160º : 0.25

# ALPHA HELIX VALUE
checkEquals(hmoment("FLPVLAGLTPSIVPKLVCLLTKKC",100), 0.56)
checkEquals(hmoment(seq = "FLPVLAGLTPSIVPKLVCLLTKKC",angle = 100,window = 11), 0.520,tolerance = 0.01)

# BETA SHEET VALUE
checkEquals(hmoment("FLPVLAGLTPSIVPKLVCLLTKKC",160), 0.25)
checkEquals(hmoment(seq = "FLPVLAGLTPSIVPKLVCLLTKKC",angle = 160,window = 11), 0.271,tolerance = 0.01)

# CHECK OUTPUT CLASS
checkTrue(is.numeric(hmoment("FLPVLAGLTPSIVPKLVCLLTKKC",100)))
Expand Down
2 changes: 1 addition & 1 deletion inst/tests/runit.mw.R
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ mw.membpos <- function(){
# SEQUENCE: QWGRRCCGWGPGRRYCVRWC

# CHECK MW VALUE
checkEquals(mw("QWGRRCCGWGPGRRYCVRWC"), 2485.91)
checkEquals(mw("QWGRRCCGWGPGRRYCVRWC"), 2485.91,tolerance = 0.01)

# CHECK OUTPUT CLASS
checkTrue(is.numeric(mw("QWGRRCCGWGPGRRYCVRWC")))
Expand Down
2 changes: 1 addition & 1 deletion inst/tests/runit.pI.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ test.pI<- function(){
# Theoretical pI: 9.88

# CHECK pI VALUE
checkEquals(round(pI("QWGRRCCGWGPGRRYCVRWC","Bje"),2),9.88)
checkEquals(pI("QWGRRCCGWGPGRRYCVRWC","Bje"),9.88)

# CHECK OUTPUT CLASS
checkTrue(is.numeric(pI("QWGRRCCGWGPGRRYCVRWC","Bje")))
Expand Down
32 changes: 16 additions & 16 deletions man/Pepdata.Rd
Original file line number Diff line number Diff line change
Expand Up @@ -11,29 +11,29 @@ Physicochemical properties and indices from 100 amino acid sequences (50 antimic
\format{
A data frame with 100 observations on the following 23 variables.
\describe{
\item{\code{Sequence}}{a character vector with the sequences of 100 peptides (50 antimicrobial and 50 non-antimicrobial)}
\item{\code{Group}}{Integrer vector with the group code \code{"0"} for non antimicrobial and \code{"1"} for antimicrobial}
\item{\code{Length}}{a numeric vector with the length of the amino acid sequence}
\item{\code{sequence}}{a character vector with the sequences of 100 peptides (50 antimicrobial and 50 non-antimicrobial)}
\item{\code{group}}{Integrer vector with the group code \code{"0"} for non antimicrobial and \code{"1"} for antimicrobial}
\item{\code{length}}{a numeric vector with the length of the amino acid sequence}
\item{\code{mw}}{a numeric vector with the molecular weight of the amino acid sequence}
\item{\code{TinyAA}}{A numeric vector with the fraction (as percent) of tiny amino acids that make up the sequence}
\item{\code{SmallAA}}{A numeric vector with the fraction (as percent) of small amino acids that make up the sequence}
\item{\code{AliphaticAA}}{A numeric vector with the fraction (as percent) of aliphatic amino acids that make up the sequence}
\item{\code{AromaticAA}}{A numeric vector with the fraction (as percent) of aromatic amino acids that make up the sequence}
\item{\code{NonPolarAA}}{A numeric vector with the fraction (as percent) of non-polar amino acids that make up the sequence}
\item{\code{PolarAA}}{A numeric vector with the fraction (as percent) of polar amino acids that make up the sequence}
\item{\code{ChargedAA}}{A numeric vector with the fraction (as percent) of charged amino acids that make up the sequence}
\item{\code{BasicAA}}{A numeric vector with the fraction (as percent) of basic amino acids that make up the sequence}
\item{\code{AcidAA}}{A numeric vector with the fraction (as percent) of acid amino acids that make up the sequence}
\item{\code{tinyAA}}{A numeric vector with the fraction (as percent) of tiny amino acids that make up the sequence}
\item{\code{smallAA}}{A numeric vector with the fraction (as percent) of small amino acids that make up the sequence}
\item{\code{aliphaticAA}}{A numeric vector with the fraction (as percent) of aliphatic amino acids that make up the sequence}
\item{\code{aromaticAA}}{A numeric vector with the fraction (as percent) of aromatic amino acids that make up the sequence}
\item{\code{nonpolarAA}}{A numeric vector with the fraction (as percent) of non-polar amino acids that make up the sequence}
\item{\code{polarAA}}{A numeric vector with the fraction (as percent) of polar amino acids that make up the sequence}
\item{\code{chargedAA}}{A numeric vector with the fraction (as percent) of charged amino acids that make up the sequence}
\item{\code{basicAA}}{A numeric vector with the fraction (as percent) of basic amino acids that make up the sequence}
\item{\code{acidicAA}}{A numeric vector with the fraction (as percent) of acid amino acids that make up the sequence}
\item{\code{charge}}{a numeric vector with the charge of the amino acid sequence}
\item{\code{pI}}{a numeric vector with the isoelectric point of the amino acid sequence}
\item{\code{aindex}}{a numeric vector with the aliphatic index of the amino acid sequence}
\item{\code{instaindex}}{a numeric vector with the instability index of the amino acid sequence}
\item{\code{boman}}{{a numeric vector with the potential peptide-interaction index of the amino acid sequence}}
\item{\code{h}}{{a numeric vector with the hydrophobicity index of the amino acid sequence}}
\item{\code{hydrophobicity}}{{a numeric vector with the hydrophobicity index of the amino acid sequence}}
\item{\code{hmoment}}{a numeric vector with the hydrophobic moment of the amino acid sequence}
\item{\code{Transmembrane}}{A numeric vector with the fraction of Transmembrane windows of 11 amino acids that make up the sequence}
\item{\code{Surface}}{A numeric vector with the fraction of Surface windows of 11 amino acids that make up the sequence}
\item{\code{Globular}}{A numeric vector with the fraction of Globular windows of 11 amino acids that make up the sequence}
\item{\code{transmembrane}}{A numeric vector with the fraction of Transmembrane windows of 11 amino acids that make up the sequence}
\item{\code{surface}}{A numeric vector with the fraction of Surface windows of 11 amino acids that make up the sequence}
\item{\code{globular}}{A numeric vector with the fraction of Globular windows of 11 amino acids that make up the sequence}
}
}

Expand Down
4 changes: 2 additions & 2 deletions man/Peptides-package.Rd
Original file line number Diff line number Diff line change
Expand Up @@ -12,8 +12,8 @@ and proteins. Include also utilities for read and plot GROMACS output files .XVG
\tabular{ll}{
Package: \tab Peptides\cr
Type: \tab Package\cr
Version: \tab 1.0\cr
Date: \tab 2014-08-30\cr
Version: \tab 1.0.2\cr
Date: \tab 2014-11-11\cr
License: \tab GPL-2\cr
}
}
Expand Down
17 changes: 9 additions & 8 deletions man/hmoment.Rd
Original file line number Diff line number Diff line change
Expand Up @@ -8,12 +8,13 @@
This function compute the hmoment based on Eisenberg, D., Weiss, R. M., & Terwilliger, T. C. (1984). Hydriphobic moment is a quantitative measure of the amphiphilicity perpendicular to the axis of any periodic peptide structure, such as the a-helix or b-sheet. It can be calculated for an amino acid sequence of N residues and their associated hydrophobicities Hn. If the secuence length is < 11 AA, the window length is equal to the AA sequence length, if it is > 11, windows of 11 residues are evaluated}

\usage{
hmoment(seq,angle)
hmoment(seq,angle,window)
}
%- maybe also 'usage' for other objects documented here.
\arguments{
\item{seq}{amino acid sequence as string}
\item{seq}{Amino acid sequence as string}
\item{angle}{Protein rotational angle}
\item{window}{Sequence fraction length}
}
\value{
The max hydrophobic moment (uH) as a numerical vector of length one}
Expand All @@ -24,14 +25,14 @@ Eisenberg, D., Weiss, R. M., & Terwilliger, T. C. (1984). The hydrophobic moment
# COMPARED TO EMBOSS:HMOMENT
# http://emboss.bioinformatics.nl/cgi-bin/emboss/hmoment
# SEQUENCE: FLPVLAGLTPSIVPKLVCLLTKKC
# ALPHA-HELIX ANGLE=100 : 0.56
# BETA-SHEET ANGLE=160 : 0.25
# ALPHA-HELIX ANGLE=100 : 0.52
# BETA-SHEET ANGLE=160 : 0.271

# ALPHA HELIX VALUE
hmoment("FLPVLAGLTPSIVPKLVCLLTKKC",100)
# [1] 0.56
hmoment(seq = "FLPVLAGLTPSIVPKLVCLLTKKC",angle = 100, window = 11)
# [1] 0.5199226

# BETA SHEET VALUE
hmoment("FLPVLAGLTPSIVPKLVCLLTKKC",160)
# [1] 0.25
hmoment(seq = "FLPVLAGLTPSIVPKLVCLLTKKC",angle = 160, window = 11)
# [1] 0.2705906
}
Loading

0 comments on commit 9ab880f

Please sign in to comment.