module Data.PrimitiveArray.ScoreMatrix where
import Control.Monad (when,unless)
import Data.Text (Text)
import Data.Vector.Unboxed (Unbox)
import Numeric.Log
import qualified Data.Text as T
import qualified Data.Vector as V
import System.Exit (exitFailure)
import Data.PrimitiveArray hiding (map)
import qualified Data.PrimitiveArray as PA
data ScoreMatrix t = ScoreMatrix
{ scoreMatrix :: !(Unboxed (Z:.Int:.Int) t)
, scoreNodes :: !(Unboxed Int t)
, rowNames :: !(V.Vector Text)
, colNames :: !(V.Vector Text)
} deriving (Eq,Show)
(.!.) :: Unbox t => ScoreMatrix t -> (Int,Int) -> t
ScoreMatrix mat _ _ _ .!. (f,t) = mat ! (Z:.f:.t)
nodeDist :: Unbox t => ScoreMatrix t -> Int -> t
nodeDist ScoreMatrix{..} k = scoreNodes ! k
rowNameOf :: ScoreMatrix t -> Int -> Text
rowNameOf ScoreMatrix{..} k = rowNames V.! k
colNameOf :: ScoreMatrix t -> Int -> Text
colNameOf ScoreMatrix{..} k = colNames V.! k
numRows :: Unbox t => ScoreMatrix t -> Int
numRows ScoreMatrix{..} = let ((Z:.0:.0),(Z:.n':._)) = bounds scoreMatrix in n' + 1
numCols :: Unbox t => ScoreMatrix t -> Int
numCols ScoreMatrix{..} = let ((Z:.0:.0),(Z:._:.n')) = bounds scoreMatrix in n' + 1
listOfRowNames :: ScoreMatrix t -> [Text]
listOfRowNames ScoreMatrix{..} = V.toList rowNames
listOfColNames :: ScoreMatrix t -> [Text]
listOfColNames ScoreMatrix{..} = V.toList colNames
toPartMatrix
:: Double
-> ScoreMatrix Double
-> ScoreMatrix (Log Double)
toPartMatrix t scoreMat@(ScoreMatrix mat sn rns cns) = ScoreMatrix p psn rns cns
where p = PA.map (\k -> Exp $ negate k / (r * t)) mat
psn = PA.map (\k -> Exp $ negate k) sn
n = numRows scoreMat
d = Prelude.sum [ mat ! (Z:.i:.j) | i <- [0..n1], j <- [i+1..n1] ] / fromIntegral (n*(n1))
r = fromIntegral (n1) * d
fromFile :: FilePath -> IO (ScoreMatrix Double)
fromFile fp = do
ls <- lines <$> readFile fp
when (null ls) $ do
putStrLn $ fp ++ " is empty"
exitFailure
let mat' = map (map read . tail . words) $ tail ls
let n = length mat'
unless (all ((==n) . length) mat') $ do
putStrLn $ fp ++ " is not a NxN matrix"
print mat'
exitFailure
let scoreMatrix = PA.fromAssocs (Z:.0:.0) (Z:.n1:.n1) 0
$ concatMap (\(r,es) -> [ ((Z:.r:.c),e) | (c,e) <- zip [0..] es ])
$ zip [0..] mat'
let scoreNodes = PA.fromAssocs 0 (n1) 0 []
let rowNames = V.fromList . map T.pack . drop 1 . words $ head ls
let colNames = V.fromList . map (T.pack . head . words) $ tail ls
return $ ScoreMatrix{..}