1 {-# OPTIONS -fglasgow-exts #-} 2 3 module Bio.Util.TestBase where 4 5 import System.CPUTime 6 import System.Time 7 import Test.QuickCheck 8 import Random 9 import Data.Char (ord) 10 import Data.Word 11 import Data.ByteString.Lazy (pack) 12 13 import Bio.Sequence.SeqData 14 15 data Test = forall t . Testable t => T String t 16 17 newtype Nucleotide = N Char deriving Show 18 newtype Quality = Q Word8 deriving Show 19 20 fromN (N c) = c 21 fromQ (Q c) = c 22 23 -- | For testing, variable lengths 24 newtype EST = E Sequence deriving Show 25 newtype ESTq = Eq Sequence deriving Show 26 newtype Protein = P Sequence deriving Show 27 28 -- | For benchmarking, fixed lengths 29 newtype EST_short = ES Sequence deriving Show 30 newtype EST_long = EL Sequence deriving Show 31 newtype EST_set = ESet [Sequence] deriving Show 32 33 -- | Take time (CPU and wall clock) and report it 34 time :: String -> IO () -> IO () 35 time msg action = do 36 d1 <- getClockTime 37 t1 <- getCPUTime 38 action 39 t2 <- getCPUTime 40 d2 <- getClockTime 41 putStrLn $ "\n"++msg++", CPU time: " ++ showT (t2-t1) ++ ", wall clock: " 42 ++ timeDiffToString (diffClockTimes d2 d1) 43 44 -- | Print a CPUTime difference 45 showT :: Integral a => a -> String 46 showT t = show (fromIntegral t/1e12)++"s" 47 48 -- | Shamelessly stolen from FPS 49 integralRandomR :: (Integral a, RandomGen g) => (a,a) -> g -> (a,g) 50 integralRandomR (a,b) g = case randomR (fromIntegral a :: Integer, 51 fromIntegral b :: Integer) g of 52 (x,g) -> (fromIntegral x, g) 53 54 instance Random Word8 where 55 randomR = integralRandomR 56 random = randomR (minBound,maxBound) 57 58 instance Arbitrary Word8 where 59 arbitrary = choose (0,255) 60 61 instance Arbitrary Nucleotide where 62 arbitrary = elements (map N "aaacccgggtttn") 63 64 instance Arbitrary Quality where 65 arbitrary = do c <- choose (0,60) 66 return (Q c) 67 68 instance Arbitrary ESTq where 69 arbitrary = do n <- choose (1,100) 70 s <- vector n 71 q <- vector n 72 return $ Eq $ Seq (fromStr "qctest") 73 (fromStr $ map fromN s) (Just $ pack $ map fromQ q) 74 75 instance Arbitrary EST where 76 arbitrary = do n <- choose (1,100) 77 s <- vector n 78 return $ E $ Seq (fromStr "qctest") 79 (fromStr $ map fromN s) Nothing 80 81 instance Arbitrary Char where 82 arbitrary = elements (['A'..'Z']++['a'..'z']++" \t\n\r") 83 84 instance Arbitrary EST_short where 85 arbitrary = do let n = 200 86 s <- vector n 87 q <- vector n 88 return $ ES $ Seq (fromStr "qctest") 89 (fromStr $ map fromN s) (Just $ pack $ map fromQ q) 90 91 instance Arbitrary EST_long where 92 arbitrary = do let n = 1000 93 s <- vector n 94 q <- vector n 95 return $ EL $ Seq (fromStr "qctest") 96 (fromStr $ map fromN s) (Just $ pack $ map fromQ q) 97 98 -- 1000 ESTs of length 1000 99 instance Arbitrary EST_set where 100 arbitrary = do let n = 1000 101 s <- vector n 102 return (ESet $ map (\(EL x) -> x) s)