debugging.. split Module in more files
This commit is contained in:
		
							
								
								
									
										71
									
								
								src/Main.hs
									
									
									
									
									
								
							
							
						
						
									
										71
									
								
								src/Main.hs
									
									
									
									
									
								
							| @@ -17,9 +17,10 @@ | ||||
| -- | ||||
| ----------------------------------------------------------------------------- | ||||
|  | ||||
| module Main where | ||||
| module DCB.DCBn where | ||||
|  | ||||
| import           DCB | ||||
| import           DCB.DCB | ||||
| import           DCB.IO | ||||
| import           Util | ||||
|  | ||||
| import           Control.DeepSeq | ||||
| @@ -118,7 +119,7 @@ emptyLine a | ||||
| --doCalculation :: Matrix Int -> B.ByteString | ||||
| doCalculation adj attr = | ||||
|         let | ||||
|                 dens = 0.7 | ||||
|                 dens = 0.75 | ||||
|                 omega = (A.fromListUnboxed (ix1 3) [0.5,0.5,0.5]) | ||||
|                 delta = 2 | ||||
|                 (adj_, graph_) = preprocess adj attr {--0.8--} omega delta | ||||
| @@ -126,9 +127,9 @@ doCalculation adj attr = | ||||
|                 B.concat $ | ||||
|                         [ | ||||
|                                 outputArray $ trace ("After: "++ show (sumAllS adj_)++"\n") adj_, | ||||
|                                 outputGraph $ L.sort $ doAll graph_ adj attr dens omega delta, | ||||
|                                 outputGraph $ L.sort $ (step graph_ adj attr dens omega delta) ++  | ||||
|                                                         (step (step graph_ adj attr dens omega delta) adj attr dens omega delta) | ||||
|                                 outputGraph $ L.sort $ doAll graph_ adj_ attr dens omega delta | ||||
| --                                outputGraph $ L.sort $ (step graph_ adj attr dens omega delta) | ||||
| --                                                       ++ (step (step graph_ adj attr dens omega delta) adj attr dens omega delta) | ||||
|                         ] | ||||
|                 where | ||||
|                         doAll [] _ _ _ _ _ = [] | ||||
| @@ -136,57 +137,6 @@ doCalculation adj attr = | ||||
|                         doAll' [] _ _ _ _ _ = [] | ||||
|                         doAll' gs a b c d e = gs ++ doAll' (step gs a b c d e) a b c d e | ||||
|  | ||||
| -- | creates a default-formatted output with \",\" in between elements | ||||
| --   and \"\\n\" in between dimensions | ||||
| -- | ||||
| --   calls '_outputArray' with preset properties | ||||
| outputArray :: (Unbox a, Show a) => Array U DIM2 a -> B.ByteString | ||||
| outputArray a = _outputArray a "\t" "\n" | ||||
|  | ||||
| -- | creates a formatted output from a DIM2 repa-Array | ||||
| -- | ||||
| --   * First String is the between-element-separator | ||||
| -- | ||||
| --   * Second String is the between-dimensions-separator | ||||
| _outputArray :: (Unbox a, Show a) => Array U DIM2 a -> String -> String -> B.ByteString | ||||
| _outputArray a itt lt = B.concat $ | ||||
|                                 (B.pack $ "Matrix "++(show $ listOfShape $ extent a)++ "\n") | ||||
|                                 : (L.map B.pack (_outputArray' (extent a) a itt lt)) | ||||
|         where | ||||
|         _outputArray' :: (Unbox a, Show a) => DIM2 -> Array U DIM2 a -> String -> String -> [String] | ||||
|         _outputArray' shape@(Z :. si :. sj) a itt lt = [(_outputArray'' shape i 0 a itt) ++ lt | i <- [0..(si - 1)]] | ||||
|  | ||||
|         _outputArray'' :: (Unbox a, Show a) => DIM2 -> Int -> Int -> Array U DIM2 a -> String -> String | ||||
|         _outputArray'' shape@(Z :. si :. sj) i j a itt | ||||
|                         | sj-1 == j = show (a!(ix2 i j))  -- no "," for last one.. | ||||
|                         | otherwise = show (a!(ix2 i j)) ++ itt ++ (_outputArray'' shape i (j+1) a itt) | ||||
|  | ||||
| outputGraph :: [Graph] -> B.ByteString | ||||
| outputGraph gs = B.concat $ L.map (flipto3 _outputGraph "," "\n") (L.sort gs) | ||||
|                                         +|| (parBuffer 25 rseq) --run parallel | ||||
|  | ||||
| _outputGraph :: Graph -> String -> String -> B.ByteString | ||||
| _outputGraph (indices, (constdim, constmat), dens) itt lt = | ||||
|                                     let | ||||
|                                             plt = B.pack lt | ||||
|                                             pitt = B.pack itt | ||||
|                                     in | ||||
|                                         B.concat $ | ||||
|                                         [ | ||||
|                                                 (B.pack $ "Density: " ++ lt ++ show dens), | ||||
|                                                 plt, | ||||
|                                                 (B.pack $ "Indices used:" ++ lt ++ V.foldl (appendS itt) "" (toUnboxed indices)), | ||||
|                                                 plt, | ||||
|                                                 (B.pack $ "Attribute-Dimensions satisfied:" ++ lt ++ V.foldl (appendS itt) "" (toUnboxed constdim)), | ||||
|                                                 plt, | ||||
|                                                 outputArray $ computeS $ transpose constmat, | ||||
|                                                 plt, | ||||
|                                                 plt | ||||
|                                         ] | ||||
|  | ||||
| appendS :: (Show a) => String -> String -> a -> String | ||||
| appendS sep a b = (a ++ show b) ++ sep | ||||
|  | ||||
| -- | gets the length of the Left a. | ||||
| -- | ||||
| --   0 if Left a empty or no valid constructor. | ||||
| @@ -212,13 +162,6 @@ showHelp = do | ||||
|                            "\n" | ||||
|                 exitSuccess | ||||
|  | ||||
| infixl 1 +|| | ||||
|  | ||||
| -- | short for a `using` b. We don't need brackets this way and are able to comment out parallelism. | ||||
| (+||) :: a -> Strategy a -> a | ||||
| a +|| b = a `using` b | ||||
|  | ||||
|  | ||||
| -- | checks if the submitted Text is empty. If not it will be printed out and the program aborts | ||||
| checkError :: T.Text -> IO () | ||||
| checkError a | ||||
|   | ||||
		Reference in New Issue
	
	Block a user