Merge branch 'master' of pwning.de:/hgraph
This commit is contained in:
commit
f814020d5a
92
src/Main.hs
92
src/Main.hs
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE DoAndIfThenElse #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
-----------------------------------------------------------------------------
|
||||
--
|
||||
@ -14,9 +15,7 @@
|
||||
--
|
||||
-----------------------------------------------------------------------------
|
||||
|
||||
module Main (
|
||||
main
|
||||
) where
|
||||
module Main where
|
||||
|
||||
import DCB
|
||||
|
||||
@ -28,6 +27,7 @@ import Data.Array.Repa as A hiding ((++))
|
||||
import Data.Array.Repa.Repr.Unboxed
|
||||
import Data.ByteString.Char8 (ByteString)
|
||||
import qualified Data.ByteString.Char8 as B
|
||||
import Data.Char (isSpace)
|
||||
import Data.Either (lefts, rights)
|
||||
import Data.Functor.Identity
|
||||
import qualified Data.List as L
|
||||
@ -40,8 +40,18 @@ import System.Exit (exitFailure, exitSuccess)
|
||||
import Test.QuickCheck.All (quickCheckAll)
|
||||
|
||||
|
||||
-- TODO: Give createGraph a presized Array and no dynamic [Int].
|
||||
-- should be createGraph :: T.Text -> Either (Vector Int) T.Text
|
||||
-- | Parses the graph
|
||||
-- a graph consists of NxN chars layouted like
|
||||
--
|
||||
-- > 10101
|
||||
-- > 01010
|
||||
-- > 00100
|
||||
-- > 01010
|
||||
-- > 10101
|
||||
--
|
||||
-- * Valid Chars: 0, 1, \\n
|
||||
--
|
||||
-- * Invalid: \\r
|
||||
createGraph :: T.Text -> Either [Int] T.Text
|
||||
createGraph input = createGraph' input (Left [])
|
||||
where
|
||||
@ -49,16 +59,30 @@ createGraph input = createGraph' input (Left [])
|
||||
createGraph' a r
|
||||
| T.null a = r
|
||||
| otherwise =
|
||||
let next = (createGraph' (T.tail a) r) in -- flip cases for less function-calls?
|
||||
case next of
|
||||
Left xs ->
|
||||
case T.head a of
|
||||
'0' -> Left $ 0:xs
|
||||
'1' -> Left $ 1:xs
|
||||
'0' -> createGraph'' 0 (T.tail a) r
|
||||
'1' -> createGraph'' 1 (T.tail a) r
|
||||
_ -> Right $ T.append (T.pack "cannot parse ") a
|
||||
-- call recursion as last resort -> ensure not much happens on the heap
|
||||
where
|
||||
createGraph'' :: Int -> T.Text -> Either [Int] T.Text -> Either [Int] T.Text
|
||||
createGraph'' x cs r =
|
||||
case createGraph' cs r of
|
||||
Left xs -> Left (x:xs)
|
||||
Right errstr ->
|
||||
Right errstr
|
||||
|
||||
-- | Parses the attribute-Matrix
|
||||
-- the matrix consists of NxM tab-delimeted double-lines like
|
||||
--
|
||||
-- > 1 2.3
|
||||
-- > -1 2.1
|
||||
-- > 4 2.7
|
||||
-- > 2.2 -3e-4
|
||||
-- > 3 2.3
|
||||
--
|
||||
-- * Valid: Doubles, Tabs (\\t)
|
||||
--
|
||||
createAttr :: T.Text -> Either [Double] T.Text
|
||||
createAttr input = createAttr' (T.split (=='\t') input) (Left [])
|
||||
where
|
||||
@ -74,33 +98,32 @@ createAttr input = createAttr' (T.split (=='\t') input) (Left [])
|
||||
Left rs -> Left (this : rs)
|
||||
_ -> next))
|
||||
|
||||
-- | checks if a given Text is empty ("", whitespaces)
|
||||
emptyLine :: T.Text -> Bool
|
||||
emptyLine a
|
||||
| T.null a = True
|
||||
| T.all isSpace a = True
|
||||
| otherwise = False
|
||||
|
||||
emptyLog :: [T.Text] -> Bool
|
||||
emptyLog [] = True
|
||||
emptyLog a = False --emptyLine $ foldl True (&&) (map emptyLine a)
|
||||
|
||||
-- TODO: implement calculation
|
||||
--doCalculation :: Matrix Int -> B.ByteString
|
||||
doCalculation graph attr = createOutput attr
|
||||
|
||||
-- | creates a default-formatted output with "," in between elements
|
||||
-- and "\n" in between dimensions
|
||||
-- calls just _createOutput with preset properties
|
||||
|
||||
--default output with "," within items and "\n" within dimensions
|
||||
-- | creates a default-formatted output with \",\" in between elements
|
||||
-- and \"\\n\" in between dimensions
|
||||
--
|
||||
-- calls '_createOutput' with preset properties
|
||||
createOutput :: (Unbox a, Show a) => Array U DIM2 a -> B.ByteString
|
||||
createOutput a = _createOutput a "," "\n"
|
||||
|
||||
-- | creates a formatted output from a DIM2 repa-Array
|
||||
|
||||
--output Array a with "itt" within items and "lt" within dimensions
|
||||
--
|
||||
-- * First String is the between-element-separator
|
||||
--
|
||||
-- * Second String is the between-dimensions-separator
|
||||
_createOutput :: (Unbox a, Show a) => Array U DIM2 a -> String -> String -> B.ByteString
|
||||
_createOutput a itt lt = B.concat $ L.map B.pack (_createOutput' (extent a) a itt lt)
|
||||
|
||||
where
|
||||
_createOutput' :: (Unbox a, Show a) => DIM2 -> Array U DIM2 a -> String -> String -> [String]
|
||||
_createOutput' shape@(Z :. si :. sj) a itt lt = [(_createOutput'' shape i 0 a itt) ++ lt | i <- [0..(si - 1)]]
|
||||
|
||||
@ -111,6 +134,7 @@ _createOutput'' shape@(Z :. si :. sj) i j a itt
|
||||
|
||||
|
||||
-- | gets the length of the Left a.
|
||||
--
|
||||
-- 0 if Left a empty or no valid constructor.
|
||||
getLength :: Either [a] T.Text -> Int
|
||||
getLength (Left a) = length a
|
||||
@ -144,15 +168,18 @@ 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
|
||||
| T.null a = return ()
|
||||
| emptyLine a = return ()
|
||||
| otherwise = do
|
||||
B.putStr $ encodeUtf8 $ T.append (T.append (T.pack "Error detected:\n") a) (T.pack "\n\n")
|
||||
exitFailure
|
||||
|
||||
--change Debug to return () lateron.
|
||||
-- | convinience debug-function. Needs to be
|
||||
-- changed to return () to disable Debug.
|
||||
debug a = putStrLn a
|
||||
|
||||
exeMain = do
|
||||
|
||||
-- | The main-function to bootstrap our application
|
||||
main = do
|
||||
-- args <- getArgs
|
||||
-- input <- case args of
|
||||
-- ["--help"] -> showHelp
|
||||
@ -203,18 +230,3 @@ exeMain = do
|
||||
----- CALCULATE & OUTPUT
|
||||
|
||||
B.putStr $ doCalculation graph attr
|
||||
|
||||
|
||||
-- Entry point for unit tests.
|
||||
testMain = do
|
||||
allPass <- $quickCheckAll -- Run QuickCheck on all prop_ functions
|
||||
unless allPass exitFailure
|
||||
|
||||
-- This is a clunky, but portable, way to use the same Main module file
|
||||
-- for both an application and for unit tests.
|
||||
-- MAIN_FUNCTION is preprocessor macro set to exeMain or testMain.
|
||||
-- That way we can use the same file for both an application and for tests.
|
||||
#ifndef MAIN_FUNCTION
|
||||
#define MAIN_FUNCTION exeMain
|
||||
#endif
|
||||
main = MAIN_FUNCTION
|
||||
|
Loading…
Reference in New Issue
Block a user