-- | Performs operations on cyclearrays, most importantly calculating energies -- for "E" cases. -- -- TODO MotifDB -> MotifDB should be the type. -- -- TODO two different cases (i) activate "E" with reasonable defaults (ii) -- generic sparse data correction. If (ii) is used, it should come before (i) -- in order to produce reasonable results for motifs with "E" module Biobase.DataSource.MCFold.Conversions ( maxArray ) where import qualified Data.Vector.Unboxed as VU import Data.PrimitiveArray import Biobase.Constants import Biobase.DataSource.MCFold import Biobase.RNA import Biobase.RNA.Hashes import Biobase.RNA.NucBounds -- * activate -- | Given a CycleArray, create entries for all keys containing at least one E. -- Set said energy to maximum over all non-E containing neighbors. maxArray :: CycleArray -> Int -> CycleArray maxArray arr k = fromAssocs l u eInf xs where (l,u) = bounds arr xs = map (\k -> let p = mkPrimary k in (mkHashedPrimary (minExtended,maxExtended) p,maxOver arr p)) $ genKeys k -- | Perform maximum calculation for one element maxOver :: CycleArray -> Primary -> Double maxOver arr p | VU.all (/=nucE) p = arr ! mkci p | otherwise = maximum $ map ((arr !) . mkci . mkPrimary) keys where mkci = mkHashedPrimary (minExtended,maxExtended) keys = mkKeys $ VU.toList p -- | Create all neighboring keys for a given one mkKeys :: [Nucleotide] -> [[Nucleotide]] mkKeys [x] = if x==nucE then [[y] |y<-acgu] else [[x]] mkKeys (x:xs) = [ head y:ys | y<-mkKeys [x], ys<-mkKeys xs ] -- | Generate all keys of a given size genKeys :: Int -> [[Nucleotide]] genKeys k | k==1 = [[y] | y<-eacgu] | k> 1 = [ y:ys | y<-eacgu, ys<-genKeys (k-1) ]