Safe Haskell | None |
---|---|
Language | Haskell2010 |
Calculate minimum-distance Hamiltonian Shortest Paths and probabilities for starting nodes.
NOTE: We explicitly model starting nodes. For symmetrical distance
matrices, this reports begin/end probabilities. For asymmetrical
distance matrices, a second instances with Last
instead of First
boundary should be created to calculate begin/end probabilities
separately.
- aMinDist :: Monad m => ScoreMatrix Double -> SigMinDist m Double Double (From :. To) (Int :. To)
- aMaxEdgeProb :: Monad m => ScoreMatrix (Log Double) -> SigMinDist m (Log Double) (Log Double) (From :. To) (Int :. To)
- data PathBT
- aPathBT :: Monad m => ScoreMatrix t -> SigMinDist m [PathBT] [[PathBT]] (From :. To) (Int :. To)
- aPretty :: Monad m => ScoreMatrix t -> SigMinDist m Text [Text] (From :. To) (Int :. To)
- aInside :: Monad m => ScoreMatrix (Log Double) -> SigMinDist m (Log Double) (Log Double) (From :. To) (Int :. To)
- type TS1 x = TwITbl Id Unboxed EmptyOk (BS1 First I) x
- type U x = TwITbl Id Unboxed EmptyOk (Unit I) x
- type PF x = TwITbl Id Unboxed EmptyOk (Boundary First I) x
- type TS1L x = TwITbl Id Unboxed EmptyOk (BS1 Last I) x
- type UL x = TwITbl Id Unboxed EmptyOk (Unit I) x
- type PFL x = TwITbl Id Unboxed EmptyOk (Boundary Last I) x
- type BT1 x b = TwITblBt Unboxed EmptyOk (BS1 First I) x Id Id b
- type BTU x b = TwITblBt Unboxed EmptyOk (Unit I) x Id Id b
- type BT1L x b = TwITblBt Unboxed EmptyOk (BS1 Last I) x Id Id b
- type BTUL x b = TwITblBt Unboxed EmptyOk (Unit I) x Id Id b
- forwardMinDist1 :: ScoreMatrix Double -> (Z :. TS1 Double) :. U Double
- backtrackMinDist1 :: ScoreMatrix Double -> ((Z :. TS1 Double) :. U Double) -> [Text]
- pathbtMinDist :: ScoreMatrix Double -> ((Z :. TS1 Double) :. U Double) -> [[PathBT]]
- runCoOptDist :: ScoreMatrix Double -> (Double, [Text])
- runMinDist :: ScoreMatrix Double -> (Double, [[PathBT]])
- boundaryPartFun :: Double -> ScoreMatrix Double -> [(Boundary First I, Log Double)]
- forwardMaxEdgeProbFirst :: ScoreMatrix (Log Double) -> (Z :. TS1 (Log Double)) :. U (Log Double)
- forwardMaxEdgeProbLast :: ScoreMatrix (Log Double) -> (Z :. TS1L (Log Double)) :. UL (Log Double)
- pathbtMaxEdgeProbFirst :: ScoreMatrix (Log Double) -> ((Z :. TS1 (Log Double)) :. U (Log Double)) -> [[PathBT]]
- pathbtMaxEdgeProbLast :: ScoreMatrix (Log Double) -> ((Z :. TS1L (Log Double)) :. UL (Log Double)) -> [[PathBT]]
- runMaxEdgeProbFirst :: ScoreMatrix (Log Double) -> (Log Double, [[PathBT]])
- runMaxEdgeProbLast :: ScoreMatrix (Log Double) -> (Log Double, [(Boundary Last I, Log Double)], [[PathBT]])
- test :: Double -> FilePath -> IO ()
Documentation
aMinDist :: Monad m => ScoreMatrix Double -> SigMinDist m Double Double (From :. To) (Int :. To) Source #
Minimal distance algebra
TODO The two Ints are the indices of the nodes and could be replaced?
aMaxEdgeProb :: Monad m => ScoreMatrix (Log Double) -> SigMinDist m (Log Double) (Log Double) (From :. To) (Int :. To) Source #
Maximum edge probability following the probabilities generated from
the EdgeProb
grammar.
aPathBT :: Monad m => ScoreMatrix t -> SigMinDist m [PathBT] [[PathBT]] (From :. To) (Int :. To) Source #
This should give the correct order of nodes independent of the
underlying Set1 First
or Set1 Last
because the (From:.To)
system
is agnostic over these.
aPretty :: Monad m => ScoreMatrix t -> SigMinDist m Text [Text] (From :. To) (Int :. To) Source #
This should give the correct order of nodes independent of the
underlying Set1 First
or Set1 Last
because the (From:.To)
system
is agnostic over these.
aInside :: Monad m => ScoreMatrix (Log Double) -> SigMinDist m (Log Double) (Log Double) (From :. To) (Int :. To) Source #
Before using aInside
the ScoreMatrix
needs to be scaled
appropriately! Due to performance reasons we don't want to do this
within aInside
.
forwardMinDist1 :: ScoreMatrix Double -> (Z :. TS1 Double) :. U Double Source #
Run the minimal distance algebra.
This produces one-boundary sets. Meaning that for each boundary we get the total distance within the set.
runCoOptDist :: ScoreMatrix Double -> (Double, [Text]) Source #
Given the Set1
produced in forwardMinDist1
we can now extract the
co-optimal paths using the Set1 -> ()
index change.
TODO do we want this one explicitly or make life easy and just extract
from all forwardMinDist1
paths?
runMinDist :: ScoreMatrix Double -> (Double, [[PathBT]]) Source #
Return the minimal distance and provide a list of co-optimal backtraces.
boundaryPartFun :: Double -> ScoreMatrix Double -> [(Boundary First I, Log Double)] Source #
Extract the individual partition scores.
forwardMaxEdgeProbFirst :: ScoreMatrix (Log Double) -> (Z :. TS1 (Log Double)) :. U (Log Double) Source #
Run the maximal edge probability grammar.
forwardMaxEdgeProbLast :: ScoreMatrix (Log Double) -> (Z :. TS1L (Log Double)) :. UL (Log Double) Source #
pathbtMaxEdgeProbFirst :: ScoreMatrix (Log Double) -> ((Z :. TS1 (Log Double)) :. U (Log Double)) -> [[PathBT]] Source #
pathbtMaxEdgeProbLast :: ScoreMatrix (Log Double) -> ((Z :. TS1L (Log Double)) :. UL (Log Double)) -> [[PathBT]] Source #
runMaxEdgeProbFirst :: ScoreMatrix (Log Double) -> (Log Double, [[PathBT]]) Source #
Given the Set1
produced in forwardMinDist1
we can now extract the
co-optimal paths using the Set1 -> ()
index change.
TODO do we want this one explicitly or make life easy and just extract
from all forwardMinDist1
paths?