module BioInf.GeneCluEDO
( runGeneCluEDO
, FillWeight (..)
, FillStyle (..)
) where
import Control.Monad (forM_)
import Data.Function (on)
import Data.List (groupBy)
import Numeric.Log
import qualified Data.Text as T
import qualified Data.Text.IO as T
import System.FilePath (addExtension)
import System.IO (withFile,IOMode(WriteMode))
import Text.Printf
import ADP.Fusion.Term.Edge.Type (From(..),To(..))
import Data.PrimitiveArray (fromEdgeBoundaryFst,(:.)(..))
import Data.PrimitiveArray.ScoreMatrix
import Diagrams.TwoD.ProbabilityGrid
import ShortestPath.SHP.Edge.MinDist (runMaxEdgeProbLast, runCoOptDist, boundaryPartFun,PathBT(..))
import BioInf.GeneCluEDO.EdgeProb (edgeProbScoreMatrix, edgeProbPartFun)
runGeneCluEDO
:: FillWeight
-> FillStyle
-> Double
-> FilePath
-> String
-> IO ()
runGeneCluEDO fw fs temperature inFile filePrefix = do
scoreMat <- fromFile inFile
let lon = listOfRowNames scoreMat
let n = length lon
let lns = map T.unpack lon
let bcols = max 4 . maximum $ map T.length $ lon
withFile (filePrefix `addExtension` ".run") WriteMode $ \hrun -> do
hPrintf hrun ("Input File: %s\n") inFile
hPrintf hrun ("Temperature: %f\n") temperature
hPrintf hrun ("\n")
let (minD, minDcoopts) = runCoOptDist scoreMat
hPrintf hrun "Minimal Distance: %6.3f\n" minD
hPrintf hrun "Optimal Paths:\n"
forM_ minDcoopts (T.hPutStrLn hrun)
hPrintf hrun "\n"
hPrintf hrun "Chain Begin/End Probabilities:\n"
let bps = boundaryPartFun temperature scoreMat
forM_ lon $ hPrintf hrun ("%" ++ show (bcols + 4) ++ "s")
hPrintf hrun "\n"
forM_ bps $ \(_, Exp p) -> hPrintf hrun ("%" ++ show (bcols + 4) ++ ".4f") (exp p)
hPrintf hrun "\n"
hPrintf hrun "\n"
svgGridFile (filePrefix `addExtension` "boundary.svg") fw fs 1 n [] lns (Prelude.map snd bps)
hPrintf hrun "Edge Probabilities:\n"
let eps = edgeProbPartFun temperature scoreMat
hPrintf hrun ("%" ++ show (bcols + 4) ++ "s") ("" :: String)
forM_ lon $ hPrintf hrun ("%" ++ show (bcols + 4) ++ "s")
hPrintf hrun "\n"
forM_ (groupBy ((==) `on` (fromEdgeBoundaryFst . fst)) eps) $ \rps -> do
let (eb,_) = head rps
hPrintf hrun ("%" ++ show (bcols + 4) ++ "s") (lon !! fromEdgeBoundaryFst eb)
forM_ rps $ \(eb,Exp p) -> hPrintf hrun ("%" ++ show (bcols + 4) ++ ".4f") (exp p)
hPrintf hrun "\n"
svgGridFile (filePrefix `addExtension` "edge.svg") fw fs n n lns lns (Prelude.map snd eps)
hPrintf hrun "\n"
let probMat = edgeProbScoreMatrix scoreMat eps
let (Exp maxP, _, maxPcoopts) = runMaxEdgeProbLast probMat
hPrintf hrun "Maximal Log-Probability Path Score: %6.3f\n" maxP
forM_ (map reverse maxPcoopts) $ \path -> do
forM_ path $ \case
BTnode (_:.To n) -> hPrintf hrun "%s" (lns !! n)
BTedge (From ff:.To tt) -> hPrintf hrun " -> %s" (lns !! tt)
hPrintf hrun "\n"
hPrintf hrun "\n"