module BioInf.GeneCluEDO.EdgeProb where
import Control.Arrow (second)
import Control.Monad (forM_)
import Data.List (nub,sort)
import Data.Text (Text,unpack)
import Data.Vector.Unboxed (Unbox)
import Numeric.Log
import qualified Data.Map.Strict as MS
import qualified Data.Text as T
import qualified Data.Vector.Fusion.Stream.Monadic as SM
import Text.Printf
import ADP.Fusion.Core
import ADP.Fusion.EdgeBoundary
import ADP.Fusion.Set1
import Data.PrimitiveArray hiding (toList)
import Data.PrimitiveArray.ScoreMatrix
import Diagrams.TwoD.ProbabilityGrid
import FormalLanguage
import ShortestPath.SHP.Grammar.EdgeProb
aMinDist :: Monad m => ScoreMatrix Double -> SigEdgeProb m Double Double (From:.To) (Int:.To)
aMinDist s = SigEdgeProb
{ edge = \x (From ff:.To tt) -> x + (s .!. (ff,tt))
, mpty = \() -> 0
, node = \n -> 0
, fini = \l (From ff:.To tt) f -> l + (s .!. (ff,tt)) + f
, h = SM.foldl' min 999999
}
aInside :: Monad m => ScoreMatrix (Log Double) -> SigEdgeProb m (Log Double) (Log Double) (From:.To) (Int:.To)
aInside s = SigEdgeProb
{ edge = \x (From ff:.To tt) -> s .!. (ff,tt) * x
, mpty = \() -> 1
, node = \n -> 1
, fini = \l (From ff:.To tt) f -> l * (s .!. (ff,tt)) * f
, h = SM.foldl' (+) 0
}
type TF1 x = TwITbl Id Unboxed EmptyOk (BS1 First I) x
type TL1 x = TwITbl Id Unboxed EmptyOk (BS1 Last I) x
type EB x = TwITbl Id Unboxed EmptyOk (EdgeBoundary I) x
type BF1 x b = TwITblBt Unboxed EmptyOk (BS1 First I) x Id Id b
type BL1 x b = TwITblBt Unboxed EmptyOk (BS1 Last I) x Id Id b
type BEB x b = TwITblBt Unboxed EmptyOk (EdgeBoundary I) x Id Id b
edgeProbPartFun :: Double -> ScoreMatrix Double -> [(EdgeBoundary I, Log Double)]
edgeProbPartFun temperature scoreMat =
let n = numRows scoreMat
partMat = toPartMatrix temperature scoreMat
(Z:.sF:.sL:.sZ) = mutateTablesST $ gEdgeProb (aInside partMat)
(ITbl 0 0 EmptyOk (fromAssocs (BS1 0 (1)) (BS1 (2^n1) (Boundary $ n1)) 0 []))
(ITbl 1 0 EmptyOk (fromAssocs (BS1 0 (1)) (BS1 (2^n1) (Boundary $ n1)) 0 []))
(ITbl 2 0 EmptyOk (fromAssocs (0 :-> 0) (0 :-> (n1)) 0 []))
Edge
Singleton
:: Z:.TF1 (Log Double):.TL1 (Log Double):.EB (Log Double)
TW (ITbl _ _ _ pf) _ = sZ
bs' = assocs pf
pssum = (Numeric.Log.sum $ Prelude.map snd bs') / (fromIntegral n 1)
bs = Prelude.map (second (/pssum)) bs'
in bs
edgeProbScoreMatrix :: (Unbox t) => ScoreMatrix t -> [(EdgeBoundary I, Log Double)] -> ScoreMatrix (Log Double)
edgeProbScoreMatrix (ScoreMatrix mat _ zn sn) xs' = ScoreMatrix m endProbs zn sn
where m = fromAssocs l h 0 xs
(Z:._:.n) = h
(l,h) = bounds mat
xs = [ ((Z:.f:.t),p) | (f :-> t, p) <- xs' ]
eP = MS.fromListWith (+) [ (f,p) | (f :-> t, p) <- xs' ]
endProbs = fromAssocs 0 n 1 [ (k, 1 eP MS.! k) | k <- [0..n] ]
bP = MS.fromListWith (+) [ (t,p) | (f :-> t, p) <- xs' ]
beginProbs = fromAssocs 0 n 1 [ (k, 1 eP MS.! k) | k <- [0..n] ] `asTypeOf` endProbs