{-# LANGUAGE StandaloneDeriving #-} module BioInf.RNAFold.Energy ( FoldFunctions (..) , Fold (..) ) where import BioInf.RNAFold import Biobase.Types.Energy import Biobase.Types.Ring import BioInf.RNAFold.Functions instance FoldFunctions Energy instance Fold Energy where backtrack trnr inp tbls = error "write me" {- backtrack trnr inp (weak,strong,mbr1,mbr,extern) = ext 0 n delta where n = VU.length inp -1 delta = one :: Energy overallBest = extern `unsafeIndex` (0,n) ext i j d = let bestE = extern `unsafeIndex` (i,j) in [ [] | i==j , overallBest == one ] ++ -- gives us the unfolded sequence [ r | i Int -> a -> [Pairlist] wea i j d = let bestE = weak `unsafeIndex` (i,j) in [ [(i,j)] | i+3 do putStrLn "" forM [0..n] $ \j -> do if j>=i then do let v = arr `unsafeIndex` (i,j) if isZero v then printf "%5s" "_i_" else printf "%5i" (unEnergy $ arr `unsafeIndex` (i,j)) else do putStr " " putStrLn "" return () -}