Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module contains functions for RNAlien
Synopsis
- module Biobase.RNAlien.Types
- 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 -> String -> IO ()
- checkTools :: [String] -> String -> String -> IO (Either String String)
- systemCMsearch :: Int -> String -> String -> String -> String -> IO ExitCode
- readCMSearch :: String -> IO (Either ParseError CMsearch)
- readCMSearches :: String -> IO (Either ParseError CMsearch)
- compareCM :: String -> String -> String -> IO (Either String Double)
- parseCMSearch :: String -> Either ParseError CMsearch
- cmSearchsubString :: Int -> Int -> String -> String
- setInitialTaxId :: Bool -> Int -> Maybe String -> String -> Maybe Int -> Fasta () () -> IO (Maybe Int)
- evaluateConstructionResult :: StaticOptions -> ModelConstruction -> IO String
- readCMstat :: String -> IO (Either ParseError CMstat)
- parseCMstat :: String -> Either ParseError CMstat
- checkNCBIConnection :: IO (Either String String)
- preprocessClustalForRNAz :: String -> String -> Int -> Double -> Double -> Bool -> IO (Either String (String, String))
- preprocessClustalForRNAzExternal :: String -> String -> Int -> Int -> Int -> Bool -> IO (Either String (String, String))
- preprocessClustalForRNAcodeExternal :: String -> String -> Int -> Int -> Int -> Bool -> IO (Either String (String, String))
- rnaZEvalOutput :: Either ParseError RNAz -> String
- reformatFasta :: Fasta () () -> Fasta () ()
- checkTaxonomyRestriction :: Maybe String -> Maybe String
- evaluePartitionTrimCMsearchHits :: Double -> [(CMsearch, (Fasta () (), Int, ByteString))] -> ([(CMsearch, (Fasta () (), Int, ByteString))], [(CMsearch, (Fasta () (), Int, ByteString))], [(CMsearch, (Fasta () (), Int, ByteString))])
- readFastaFile :: String -> IO [Fasta () ()]
- writeFastaFile :: String -> [Fasta () ()] -> IO ()
Documentation
module Biobase.RNAlien.Types
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 #
readCMSearch :: String -> IO (Either ParseError CMsearch) Source #
parse from input filePath
readCMSearches :: 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
setInitialTaxId :: Bool -> Int -> Maybe String -> String -> Maybe Int -> Fasta () () -> IO (Maybe Int) 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 -> Int -> Double -> Double -> Bool -> IO (Either String (String, String)) Source #
preprocessClustalForRNAzExternal :: String -> String -> Int -> Int -> Int -> Bool -> IO (Either String (String, String)) Source #
Call for external preprocessClustalForRNAz
preprocessClustalForRNAcodeExternal :: String -> String -> Int -> Int -> Int -> Bool -> IO (Either String (String, String)) Source #
Call for external preprocessClustalForRNAcode - RNAcode additionally to RNAz requirements does not accept pipe,underscore, doublepoint symbols
rnaZEvalOutput :: Either ParseError RNAz -> String Source #
reformatFasta :: Fasta () () -> Fasta () () Source #
evaluePartitionTrimCMsearchHits :: Double -> [(CMsearch, (Fasta () (), Int, ByteString))] -> ([(CMsearch, (Fasta () (), Int, ByteString))], [(CMsearch, (Fasta () (), Int, ByteString))], [(CMsearch, (Fasta () (), Int, ByteString))]) Source #
Partitions sequences by containing a cmsearch hit and extracts the hit region as new sequence