{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} -- | Internal representation of RNA complexes. Ideally, each DataSource should -- define an instance of 'MkComplex' for easy importing of foreign data. -- -- TODO unify with Biobase.Structure.Complex module Biobase.RNA.Complex where import Control.DeepSeq import qualified Data.Vector.Unboxed as VU import Biobase.RNA import Biobase.RNA.Pairs -- | An RNA complex. One or more RNA molecules linearly encoding as a -- 'sequence'. Structure is stored as an unboxed vector. The (unspecified) type -- is most likely either a 'CwwPair' or an 'ExtPair'. The 'chain' encodes (for -- more than one participating nucleotide sequence) to which chain each -- nucleotide in the sequence belongs. -- -- NOTE 'chain' may be empty and there may be "ampersand" markers in the -- 'sequence' which then define split positions. data (VU.Unbox a, Show a, Read a) => Complex a = Complex { sequence :: Primary , structure :: Pairs a , chain :: VU.Vector Char } deriving (Read,Show) -- | Create 'Complex'es from data sources. class MkComplex a b where mkComplex :: a -> Complex b -- * 'CwwPair' instances -- | Create a complex where only sequence is given. instance MkComplex String CwwPair where mkComplex s = error "write me" -- Complex (mkPrimary s) (mkSecondary "") (VU.empty) -- | Default interactive instance. Given sequence and dot-bracket string, both -- as strings, create an instance. instance MkComplex (String,String) CwwPair where mkComplex (s,p) = error "write me" -- Complex (mkPrimary s) (mkSecondary p) (VU.empty) -- * 'ExtPair' instances instance MkComplex String ExtPair where mkComplex s = error "write me" -- Complex (mkPrimary s) (mkExtended "") (VU.empty) -- * Instances for Complex -- | The NFData instance. Since these are unboxed vectors, we just need to make -- sure that evaluation begins. instance (NFData a, Read a, Show a, VU.Unbox a) => NFData (Complex a) where rnf Complex{..} = rnf (VU.length sequence) `seq` rnf structure `seq` rnf (VU.length chain) `seq` ()