Browse Source

Separate into files, consolidate calling to avoid passing.

Josh Bicking 6 years ago
parent
commit
512e4a2339
6 changed files with 169 additions and 154 deletions
  1. 2 2
      README.md
  2. 1 145
      app/Main.hs
  3. 7 1
      pi-digits.cabal
  4. 0 6
      src/Lib.hs
  5. 37 0
      src/Logic.hs
  6. 122 0
      src/Parsing.hs

+ 2 - 2
README.md

@@ -18,7 +18,7 @@ Run `stack exec pi-digits-exe`, or execute the binary found in `./.stack-work/in
 - [X] Implement threading.
 - [X] Implement `optparse-applicative` for more formal/extensive arg parsing.
 - [X] ~~Replace the mess in `prompt` with a monad.~~ Issue corrected by using `optparse-applicative`.
+- [X] Separate into different files. Possibly parsing and logic files.
+- [X] ~~Find a better way to transfer "globals", like `delim` and `printFun`.~~ `parseIndex` handles all parsing and calling logic now.
 - [ ] Implement a faster mod operation, to allow for larger numbers (like 12345678901234567890). It will likely be implemented with the algorithm explained in the paper.
 - [ ] Customize print behavior and frequency. Flush output every N digits, or something similar.
-- [ ] Find a better way to transfer "globals", like `delim` and `printFun`.
-- [ ] Separate into different files. Possibly parsing and logic files.

+ 1 - 145
app/Main.hs

@@ -1,95 +1,9 @@
 module Main where
-import Numeric (showHex, showIntAtBase)
-import Data.List (isInfixOf, genericIndex)
-import Data.List.Split(splitOn)
-import Text.Read (readMaybe)
-import System.IO (hFlush, stdout)
-import Control.Parallel
 
 import Options.Applicative
 import Data.Semigroup ((<>))
 
--- Get the hex digit of Pi at place n.
-hexPi :: Integer -> Integer
-hexPi n =
-  let
-    summation = let
-      sone = (4 * sumPi n 1)
-      sfour = (2 * sumPi n 4)
-      sfive = (sumPi n 5)
-      ssix = (sumPi n 6)
-      in
-      sone `par` sfour `par` sfive `par` ssix `par` sone - sfour - sfive - ssix
-
-    skimmedSum = summation - (fromIntegral (floor summation :: Integer)) -- Take only the decimal portion
-  in
-    floor (16 * skimmedSum) :: Integer
-
-
--- Calculate the summation.
--- 5000 is used in place of Infinity. This value drops off quickly, so no need to go too far.
-sumPi :: Integer -> Integer -> Double
-sumPi n x =
-  let
-    summation1 = sum [(fromIntegral ((16^(n-k) `mod` ((8*k)+x)))) / (fromIntegral ((8*k)+x)) | k <- [0..n]]
-    summation2 = sum [16^^(n-k) / (fromIntegral ((8*k)+x)) | k <- [(n+1)..5000]]
-  in
-    summation1 + summation2
-
-
--- Get a range of digits.
-rangePi :: (Integer -> String) -> String -> Maybe Integer -> Maybe Integer -> String
-rangePi printFun delim (Just low) (Just high) =
-  if low >= high then
-    "Error: Please give a proper range."
-  else
-    init $ foldr (++) [] $ separate (map printFun (drop (fromIntegral low) . take (fromIntegral high) $ hexDigits)) delim
-    -- foldl (.) id (map (showString . printFun) (drop (fromIntegral low) . take (fromIntegral high) $ hexDigits)) ""  -- Alternative implementation: not sure about speed
-
-rangePi _ _ _ _ = printErr
-
-
--- Separate a list with some delimiter.
-separate :: [a] -> a -> [a]
-separate (x:xs) delim = x : delim : separate xs delim
-separate [] _ = []
-
-
--- Check if response is valid, then call the appropriate function.
-parseIndex :: (Integer -> String) -> String -> String -> String
-parseIndex printFun delim response =
-  if (isInfixOf ".." response) then
-    let
-      range = splitOn ".." response
-      low = readMaybe $ range !! 0 :: Maybe Integer
-      high = readMaybe $ range !! 1 :: Maybe Integer
-    in
-      rangePi printFun delim low high
-    else do
-      case (readMaybe response :: Maybe Integer) of
-        Nothing -> printErr
-        Just x -> printFun $ hexDigits `genericIndex` x
-
-
--- Continuously prompt for input.
-prompt :: (Integer -> String) -> String -> IO ()
-prompt printFun delim = do
-  putStr ">> "
-  hFlush stdout
-  response <- getLine
-  putStrLn $ parseIndex printFun delim response
-  prompt printFun delim
-
-
--- The list of answers.
-hexDigits :: [Integer]
-hexDigits = [hexPi x | x <- [0..]]
-
-
--- Complain about argument type.
-printErr :: String
-printErr = "Error: Please give an Integer (ex: 3) or a range (ex: 3..5)."
-
+import Parsing (argHandle, arguments)
 
 main :: IO ()
 main = argHandle =<< execParser opts
@@ -99,61 +13,3 @@ main = argHandle =<< execParser opts
      <> progDesc "Generate hexadecimal Pi digits.")
 
 
--- Arguments to parse.
-data Arguments = Arguments
-  { eval  :: Maybe String
-  , print :: Maybe PrintFunc
-  , delimiter :: String}
-
-arguments :: Parser Arguments
-arguments = Arguments
-      <$> optional ( argument str (
-                       help "Evaluate an index/range, and exit."
-                       <> (metavar "eval")))
-      <*> printFunc
-      <*> strOption ( long "delimiter"
-                        <> metavar "delim"
-                        <> value ""
-                        <> help "Delimiter to separate printed values.")
-
-
-
--- Decide which printing function to use.
-data PrintFunc = DecPrint | BinPrint
-
-printFunc :: Parser (Maybe PrintFunc)
-printFunc = optional (decPrint <|> binPrint)
-
-decPrint :: Parser PrintFunc
-decPrint = flag' DecPrint ( long "decimal"
-                            <> short 'd'
-                            <> help "Output in decimal.")
-
-binPrint :: Parser PrintFunc
-binPrint = flag' BinPrint ( long "binary"
-                            <> short 'b'
-                            <> help "Output in binary.")
-
-
--- Handle args, either prompt or eval & quit.
-argHandle :: Arguments -> IO ()
-argHandle (Arguments toEval outputType delim) = do
-  let
-    printFunIO =
-      case outputType of
-        Just DecPrint -> do
-          putStrLn "Outputting in decimal."
-          return (\n -> show n ++ "")
-        Just BinPrint -> do
-          putStrLn "Outputting in binary."
-          return (\n -> showIntAtBase 2 (\x -> show x !! 0) n "")
-        _ -> do
-          putStrLn "Outputting in hex."
-          return (\n -> showHex n "")
-    in do
-    printFun <- printFunIO
-    case toEval of
-      (Just s) -> putStrLn $ parseIndex printFun delim s
-      _ -> do
-        putStrLn "Enter a digit or range (Ctrl-C to exit)."
-        prompt printFun delim

+ 7 - 1
pi-digits.cabal

@@ -15,8 +15,14 @@ cabal-version:       >=1.10
 
 library
   hs-source-dirs:      src
-  exposed-modules:     Lib
+  exposed-modules:     Logic
+                     , Parsing
   build-depends:       base >= 4.7 && < 5
+                     , optparse-applicative
+                     , parallel
+                     , split
+                     , transformers-compat
+                     , ansi-terminal
   default-language:    Haskell2010
 
 executable pi-digits-exe

+ 0 - 6
src/Lib.hs

@@ -1,6 +0,0 @@
-module Lib
-    ( someFunc
-    ) where
-
-someFunc :: IO ()
-someFunc = putStrLn "someFunc"

+ 37 - 0
src/Logic.hs

@@ -0,0 +1,37 @@
+-- Calculate and store values of Pi.
+module Logic (hexDigits) where
+
+import Control.Parallel (par)
+
+
+-- Get the hex digit of Pi at place n.
+hexPi :: Integer -> Integer
+hexPi n =
+  let
+    summation = let
+      sone = (4 * sumPi n 1)
+      sfour = (2 * sumPi n 4)
+      sfive = (sumPi n 5)
+      ssix = (sumPi n 6)
+      in
+      sone `par` sfour `par` sfive `par` ssix `par` sone - sfour - sfive - ssix
+
+    skimmedSum = summation - (fromIntegral (floor summation :: Integer)) -- Take only the decimal portion
+  in
+    floor (16 * skimmedSum) :: Integer
+
+
+-- Calculate the summation.
+-- 5000 is used in place of Infinity. This value drops off quickly, so no need to go too far.
+sumPi :: Integer -> Integer -> Double
+sumPi n x =
+  let
+    summation1 = sum [(fromIntegral ((16^(n-k) `mod` ((8*k)+x)))) / (fromIntegral ((8*k)+x)) | k <- [0..n]]
+    summation2 = sum [16^^(n-k) / (fromIntegral ((8*k)+x)) | k <- [(n+1)..5000]]
+  in
+    summation1 + summation2
+
+
+-- The list of answers.
+hexDigits :: [Integer]
+hexDigits = [hexPi x | x <- [0..]]

+ 122 - 0
src/Parsing.hs

@@ -0,0 +1,122 @@
+-- Do IO with user input.
+module Parsing (argHandle, arguments) where
+
+import Numeric (showHex, showIntAtBase)
+import Data.List (isInfixOf, intersperse, genericTake, genericDrop)
+import Data.List.Split (splitOn)
+import Text.Read (readMaybe)
+import System.IO (hFlush, stdout)
+
+import Logic (hexDigits)
+
+import Options.Applicative
+import Data.Semigroup ((<>))
+
+
+-- Continuously prompt for input.
+prompt :: (Integer -> String) -> String -> IO ()
+prompt printFun delim = do
+  putStr ">> "
+  hFlush stdout
+  response <- getLine
+  putStrLn $ parseIndex printFun delim response
+  prompt printFun delim
+
+
+-- Check if response is valid, then call the appropriate function.
+parseIndex :: (Integer -> String) -> String -> String -> String
+parseIndex printFun delim response =
+  let
+    digits =
+      if (isInfixOf ".." response) then
+        let
+          range = splitOn ".." response
+          jlow = readMaybe $ range !! 0 :: Maybe Integer
+          jhigh = readMaybe $ range !! 1 :: Maybe Integer
+        in
+          case (jlow, jhigh) of
+            (Just low, Just high) -> getDigitsFrom low high
+            _ -> []
+      else
+        case (readMaybe response :: Maybe Integer) of
+          Just n -> getDigitsFrom n (n+1)
+          Nothing -> []
+  in
+    case digits of
+      _:_ -> foldr (++) [] $ intersperse delim (map printFun digits)
+      -- _:_ -> foldl (.) id (map showString (intersperse delim (map printFun digits))) "" -- Alternative implementation: not sure about speed
+      [] -> printErr
+
+
+-- Pull digits in a range.
+getDigitsFrom :: Integer -> Integer -> [Integer]
+getDigitsFrom low high 
+  | low < 0 = []
+  | high < 0 = []
+  | otherwise = genericDrop low . genericTake high $ hexDigits
+
+
+
+-- Complain about argument type.
+printErr :: String
+printErr = "Error: Please give a positive Integer (ex: 3) or a valid range of positive Integers (ex: 3..5)."
+
+
+-- Arguments to parse.
+data Arguments = Arguments
+  { eval  :: Maybe String
+  , print :: Maybe PrintFunc
+  , delimiter :: String}
+
+arguments :: Parser Arguments
+arguments = Arguments
+      <$> optional ( argument str (
+                       help "Evaluate an index/range, and exit."
+                       <> (metavar "eval")))
+      <*> printFunc
+      <*> strOption ( long "delimiter"
+                        <> metavar "delim"
+                        <> value ""
+                        <> help "Delimiter to separate printed values.")
+
+
+
+-- Decide which printing function to use.
+data PrintFunc = DecPrint | BinPrint
+
+printFunc :: Parser (Maybe PrintFunc)
+printFunc = optional (decPrint <|> binPrint)
+
+decPrint :: Parser PrintFunc
+decPrint = flag' DecPrint ( long "decimal"
+                            <> short 'd'
+                            <> help "Output in decimal.")
+
+binPrint :: Parser PrintFunc
+binPrint = flag' BinPrint ( long "binary"
+                            <> short 'b'
+                            <> help "Output in binary.")
+
+
+-- Handle args, either prompt or eval & quit.
+argHandle :: Arguments -> IO ()
+argHandle (Arguments toEval outputType delim) = do
+  let
+    printFunIO =
+      case outputType of
+        Just DecPrint -> do
+          putStrLn "Outputting in decimal."
+          return (\n -> show n ++ "")
+        Just BinPrint -> do
+          putStrLn "Outputting in binary."
+          return (\n -> showIntAtBase 2 (\x -> show x !! 0) n "")
+        _ -> do
+          putStrLn "Outputting in hex."
+          return (\n -> showHex n "")
+    in do
+    printFun <- printFunIO
+    case toEval of
+      Just s -> putStrLn $ parseIndex printFun delim s
+      _ -> do
+        putStrLn "Enter a digit or range (Ctrl-C to exit)."
+        prompt printFun delim