module Bio.GFF3.Test (tests) where import Control.Monad import Control.Monad.Error import qualified Data.ByteString.Lazy.Char8 as LBS import Data.Char import Test.QuickCheck import Bio.GFF3.Escape import qualified Bio.GFF3.Feature as F import Bio.Location.Strand import Bio.Sequence.SeqData import Bio.Util.TestBase tests :: [Test] tests = [ T "%-escape inversion" test_Escape_invert , T "%-escape completeness" test_Escape_completeness , T "GFF3 parse inversion" test_GFF3_unparseParse ] instance Arbitrary LBS.ByteString where arbitrary = liftM LBS.pack $ arbitrary -- Bio.GFF3.Escape test_Escape_invert :: [Char] -> LBS.ByteString -> Bool test_Escape_invert escchrs str = let escstr = escapeAllOf ('%':escchrs) str unescstr :: Either String LBS.ByteString unescstr = unEscapeByteString escstr in unescstr == Right str test_Escape_completeness :: [Char] -> LBS.ByteString -> Bool test_Escape_completeness escchrs str = let allescchrs = ('%':escchrs) nescchrs = length $ LBS.findIndices (flip elem allescchrs) str in (length $ LBS.elemIndices '%' $ escapeAllOf allescchrs str) == nescchrs -- Bio.GFF3.Feature instance Arbitrary F.GFFAttr where arbitrary = liftM2 F.GFFAttr arbitrary (sized vector) instance Arbitrary Strand where arbitrary = elements [Fwd, RevCompl] instance Arbitrary F.Feature where arbitrary = do seqid <- arbitrary source <- arbitrary stype <- arbitrary seq5 <- genNonNegOffset len <- genPositiveOffset score <- return Nothing -- Tricky to ask strict equality in a Double strand <- arbitrary phase <- oneof [return Nothing, liftM (Just . fromIntegral) $ choose ((0::Int),2)] attrs <- sized vector return $ F.Feature seqid source stype seq5 (seq5 + len - 1) score strand phase attrs test_GFF3_unparseParse :: F.Feature -> Bool test_GFF3_unparseParse f = let fline = F.unparse f f' :: Either String F.Feature f' = F.parse fline in f' == Right f