-
Notifications
You must be signed in to change notification settings - Fork 0
/
GrnSim.hs
191 lines (173 loc) · 6.49 KB
/
GrnSim.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
-- |
-- Module : Main
-- Copyright : (c) 2011 Jason Knight
-- License : BSD3
--
-- Maintainer : [email protected]
-- Stability : experimental
-- Portability : portable
--
-- See the help information by executing the generated executable with no
-- parameters.
--
module Main where
import GRN.Parse
import GRN.StateTransition
import GRN.Render
import GRN.Types
import GRN.Density
import GRN.Sparse
import GRN.EM
import GRN.Uncertainty
import GRN.DataFlow
import GRN.Utils
import qualified Data.Map as M
import Data.List
import Data.Ord
import Control.Monad
import Text.Printf
import System.Environment
import System.Cmd
import System.Console.ParseArgs
import System.FilePath
import System.Directory
import Data.Graph.Analysis
import Data.Vector (Vector)
import qualified Data.Vector as V
import qualified Data.Vector.Generic as G
import Statistics.Sample.KernelDensity
import Statistics.Sample
import Graphics.Gnuplot.Simple
argList :: [Arg String]
argList =
[ Arg "output" (Just 'o') (Just "output")
(argDataDefaulted "FILE" ArgtypeString "out.svg") "Output file."
, Arg "extra" (Just 'e') (Just "extra")
(argDataDefaulted "PW_ARGS" ArgtypeString "")
"Extra Pathway arguments; space delimited."
, Arg "extra2" (Just 'f') (Just "extra2")
(argDataDefaulted "PW_ARGS" ArgtypeString "")
"Extra Pathway arguments; space delimited For SM runs."
, Arg "reduce" (Just 'r') (Just "reduce") Nothing
"Reduce output graph to attractor cycles."
, Arg "generate" (Just 'g') (Just "generate") Nothing
"Generate an image"
, Arg "open" (Just 'x') (Just "open") Nothing
"Open generated image automatically"
, Arg "avg" Nothing (Just "avg")
(argDataDefaulted "INT" ArgtypeInt 8)
"Averaging sums to perform"
, Arg "n1" Nothing (Just "n1")
(argDataDefaulted "INT" ArgtypeInt 15)
"First elimination (reduction) pass amount"
, Arg "n2" Nothing (Just "n2")
(argDataDefaulted "INT" ArgtypeInt 150)
"Second pass (only simulation) amount. "
, Arg "n3" Nothing (Just "n3")
(argDataDefaulted "INT" ArgtypeInt 140)
"Runs for Density estimation ignored if m!=d"
, Arg "n4" Nothing (Just "n4")
(argDataDefaulted "INT" ArgtypeInt 0)
("If mode=d, then this is the seed, otherwise 0:deterministic equal valued "++
"outgoing edge probabilities. Also number of samples in \
\sampling dataflow mode.")
, Arg "mode" (Just 'm') (Just "mode")
(argDataRequired "MODE" ArgtypeString)
("s:state transition graph, ss:state transition matrix, p:pathway diagram, \
\sm:modified stg, d:density estimation, em:expectation maximization, \
\m:Mohammad output, df: DataFlow, c: Control")
, Arg "submode" Nothing (Just "submode")
(argDataDefaulted "SUBMODE" ArgtypeString "m")
"m: Matrix multiplication, g: graph, \
\When control: e: exact, s: sampling."
, Arg "prog" (Nothing) (Just "prog")
(argDataDefaulted "PROG" ArgtypeString "dot")
"Graphviz Draw Program to generate output"
, Arg "knock" (Just 'k') (Just "knock")
(argDataDefaulted "KNOCK" ArgtypeString "stoch")
"Knockouts in Dataflow mode: det(erministic), stoch(astic)"
, Arg "gamma" Nothing (Just "gamma")
(argDataDefaulted "DOUBLE" ArgtypeDouble 0.1)
"Amount to modify edges in dataflow mode."
, Arg "perturb" (Just 'p') (Just "perturb")
(argDataDefaulted "DOUBLE" ArgtypeDouble 0.0)
"In Mohammad output, set the perturbation probability."
, Arg "input" Nothing Nothing
(argDataRequired "FILE" ArgtypeString) "Input File."
]
main = do
args <- parseArgsIO ArgsComplete argList
let inFile = getRequiredArg args "input"
n1 = getRequiredArg args "n1" :: Int
n2 = getRequiredArg args "n2" :: Int
mode = getRequiredArg args "mode"
gen = gotArg args "generate"
modes = ["s","p","sm","d","ss","em","m","df","c"]
if (length (modes\\[mode]) == length mode)
then error $ usageError args ("Choose a valid mode.")
else return ()
con <- readFile inFile
let start = parsePW $ (unlines.words $ getRequiredArg args "extra2") ++ con
p = parsePW $ (unlines.words $ getRequiredArg args "extra") ++ con
when (mode == "s") $ do
let initg = kmapToStateGraph.buildKmaps $ p
finalGraph = simulate args initg
if (n1+n2 < 50) then print "WARNING: Number of simulation iterations \
\less than 50. Please consider increasing n1 or n2. Also consider \
\using the far superior 'ss' method for simulation." else return ()
mapM_ (printf "%7s") (M.keys p)
putStrLn ""
printSSA $ genSSA finalGraph
when gen $ drawStateGraph finalGraph args
return ()
when (mode == "ss") $ do
let initm = (kmapToDOK.buildKmaps $ p) 0
finalSSD = simulateDOKUnif args initm
(DOK (n,_) m) = initm
mapM_ (printf "%7s") (M.keys p)
putStrLn ""
--print $ maximum $ map (snd) $ M.keys m
--print $ G.length $ colIndices $ dokToCSC initm
--print $ G.length $ rowIndices $ dokToCSC initm
--print $ G.length $ cscValues $ dokToCSC initm
printSSA $ ssdToSSA finalSSD
--Cant draw a graph when we have a matrix... well we could, but we'd
--have to convert:
--when gen $ drawStateGraph finalGraph args
return ()
when (mode == "df") $ do
let initm = parseToDataFlow args p
finalSSD = simulateDOKUnif args initm
graph = convertProbsVG finalSSD $ dataFlowToGraph initm
(DOK (n,_) m) = initm
mapM_ (printf "%7s") (M.keys p)
putStrLn ""
printSSA $ ssdToSSA finalSSD
when gen $ drawDataFlow graph args
return ()
when (mode == "c") $ do
let pcon = parseControl con
simControl args p pcon
return ()
when (mode == "d") $ do
simRuns args p
return ()
when (mode == "m") $ do
uncertaintyPrint args p
return ()
when (mode == "sm") $ do
let initm = (kmapToDOK.buildKmaps $ start) 0
secm = (kmapToDOK.buildKmaps $ p) 0
interSSD = simulateDOKUnif args initm
(DOK (n,_) m) = initm
finalSSD = simulateDOK args secm interSSD
mapM_ (printf "%7s") (M.keys p)
putStrLn ""
printSSA $ ssdToSSA finalSSD
return ()
when (mode == "p") $ do
let finalGraph = mkSimple $ buildGeneGraph p
when gen $ drawGeneGraph finalGraph args
return ()
defArgs :: Args String
defArgs = parseArgs ArgsComplete argList "./grnsim" ["-m","df","pws/doesntmatter.pw"]