| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Bio.RNAlienLibrary
Description
This module contains functions for RNAlien
- module Bio.RNAlienData
 - createSessionID :: Maybe String -> IO String
 - logMessage :: String -> String -> IO ()
 - logEither :: Show a => Either a b -> String -> IO ()
 - modelConstructer :: StaticOptions -> ModelConstruction -> IO ModelConstruction
 - constructTaxonomyRecordsCSVTable :: ModelConstruction -> String
 - resultSummary :: ModelConstruction -> StaticOptions -> IO ()
 - setVerbose :: Verbosity -> Bool
 - logToolVersions :: String -> IO ()
 - checkTools :: [String] -> String -> IO (Either String String)
 - systemCMsearch :: Int -> String -> String -> String -> String -> IO ExitCode
 - readCMSearch :: String -> IO (Either ParseError CMsearch)
 - compareCM :: String -> String -> String -> IO Double
 - parseCMSearch :: String -> Either ParseError CMsearch
 - cmSearchsubString :: Int -> Int -> String -> String
 - setInitialTaxId :: Maybe String -> String -> Maybe Int -> Sequence -> IO (Maybe Int)
 - evaluateConstructionResult :: StaticOptions -> Int -> IO String
 - readCMstat :: String -> IO (Either ParseError CMstat)
 - parseCMstat :: String -> Either ParseError CMstat
 - checkNCBIConnection :: IO (Either String String)
 - preprocessClustalForRNAz :: String -> String -> IO (Either String String)
 - preprocessClustalForRNAzExternal :: String -> String -> IO (Either String String)
 - rnaZEvalOutput :: Either ParseError RNAz -> String
 - reformatFasta :: Sequence -> Sequence
 - checkTaxonomyRestriction :: Maybe String -> Maybe String
 - evaluePartitionTrimCMsearchHits :: Double -> [(CMsearch, (Sequence, Int, String, Char))] -> ([(CMsearch, (Sequence, Int, String, Char))], [(CMsearch, (Sequence, Int, String, Char))], [(CMsearch, (Sequence, Int, String, Char))])
 
Documentation
module Bio.RNAlienData
logMessage :: String -> String -> IO () Source
modelConstructer :: StaticOptions -> ModelConstruction -> IO ModelConstruction Source
Initial RNA family model construction - generates iteration number, seed alignment and model
resultSummary :: ModelConstruction -> StaticOptions -> IO () Source
Used for passing progress to Alien server
setVerbose :: Verbosity -> Bool Source
logToolVersions :: String -> IO () Source
readCMSearch :: String -> IO (Either ParseError CMsearch) Source
parse from input filePath
parseCMSearch :: String -> Either ParseError CMsearch Source
parse from input filePath
cmSearchsubString :: Int -> Int -> String -> String Source
Extract a substring with coordinates from cmsearch, first nucleotide has index 1
evaluateConstructionResult :: StaticOptions -> Int -> IO String Source
readCMstat :: String -> IO (Either ParseError CMstat) Source
parse from input filePath
parseCMstat :: String -> Either ParseError CMstat Source
parse from input filePath
preprocessClustalForRNAz :: String -> String -> IO (Either String String) Source
RNAz can process 500 sequences at max. Using rnazSelectSeqs to isolate representative sample. rnazSelectSeqs only accepts - gap characters, alignment is reformatted accordingly.
preprocessClustalForRNAzExternal :: String -> String -> IO (Either String String) Source
Call for external preprocessClustalForRNAz
reformatFasta :: Sequence -> Sequence Source
evaluePartitionTrimCMsearchHits :: Double -> [(CMsearch, (Sequence, Int, String, Char))] -> ([(CMsearch, (Sequence, Int, String, Char))], [(CMsearch, (Sequence, Int, String, Char))], [(CMsearch, (Sequence, Int, String, Char))]) Source
Partitions sequences by containing a cmsearch hit and extracts the hit region as new sequence