More refactoring. Way nicer prompts
[xyz.git] / app / Main.hs
index 3838536..4ddb724 100644 (file)
@@ -1,29 +1,29 @@
-{-# LANGUAGE OverloadedStrings #-}
-
 module Main where
 
+import Data.List (intercalate)
+import Data.String hiding (unlines)
+import Data.Text hiding (map, init, length, splitAt)
+import Data.Text.IO (putStrLn, putStr)
+import Data.Text.Lazy (toStrict)
+import Data.Text.Template
+import Data.Time.Clock.POSIX
 import Lib
+import Prelude hiding (putStrLn, putStr, init, unlines)
 import Prompts
+import System.Directory
+import System.Directory (doesFileExist)
 import System.Environment
 import System.Exit
-import System.Directory
-import Prelude hiding (init)
-import Data.List (intercalate)
+import System.File.Tree hiding (map, mapM, mapM_)
+import System.Process
 import Text.JSON
 import Text.JSON.Generic
-import Data.Text hiding (intercalate, unlines, init, length, splitAt)
-import Data.Time.Clock.POSIX
-import System.File.Tree hiding (mapM, mapM_)
-import System.Directory (doesFileExist)
-import System.Process
-import Data.Text.Template
-import Data.String
-import Data.Text.Lazy (toStrict)
+import Util
 
 main :: IO ()
 main = getArgs >>= parse
 
-continueIfValidProject :: IO() -> IO ()
+continueIfValidProject :: IO () -> IO ()
 continueIfValidProject nextfn = do
   jsonExists <- doesFileExist "xyz.json"
   if jsonExists
@@ -35,17 +35,12 @@ init = do
   dirExists <- doesFileExist "xyz.json"
   if dirExists
     then putStrLn "Project already initialised"
-    else do createDirectory "entries"
-            home <- getHomeDirectory
-            templates <- allFilesIn $ home ++ "/.xyz/themes"
-            putStrLn "Enter a name for your project:"
-            projectName <- getLine
-            putStrLn "Enter short description for your project:"
-            projectDescription <- getLine
-            putStrLn $ "Which theme would you like to use?\n\n" ++ (ununlines templates)
-            theme <- getLine
-            writeFile "xyz.json" . encode . toJSObject $ [("name", projectName), ("description", projectDescription), ("theme", theme)]
-            putStrLn "Initialised empty project"
+    else do home <- getHomeDirectory
+            themes <- allFilesIn $ home ++ "/.xyz/themes"
+            projectSpec <- initPrompt (map pack themes)
+            createDirectory "entries"
+            writeFile "xyz.json" . encode . toJSObject $ projectSpec
+            putStrLn "\n\nInitialised empty project"
 
 build :: IO ()
 build = do
@@ -55,43 +50,48 @@ build = do
         files <- allFilesIn "entries"
         home <- getHomeDirectory
         config <- readFile "xyz.json"
-        someFunc (decodeJSON config :: ProjectConfig) files >> putStrLn "Build successful"
+        writeOutProject (decodeJSON config :: ProjectConfig) files >> putStrLn "Build successful"
     else putStrLn "This does not appear to be a valid project directory"
 
-ununlines :: [String] -> String
-ununlines = intercalate "\n\n"
-
 entry :: IO ()
 entry = do
   homeDir <- getHomeDirectory
-  entryName <- textPrompt "Name for this entry:"
-  video <- (fmap . fmap) (\(a,b) -> (a, b ++ ".webm"::String)) $ dependantPrompt "Video ID (leave blank to skip):" "Local video filename:"
-  entryNum <- fmap ((+1) . length) $ allFilesIn "entries"
-  stamp <- fmap round getPOSIXTime
+  entrySpec <- entryPrompt
+  entryNum <- fmap (show . (+1) . length) $ allFilesIn "entries"
+  stamp <- fmap (show . round) getPOSIXTime
   videoTemplate <- readFile (homeDir ++ "/.xyz/entry-video.txt") >>= return . template . fromString
   normalTemplate <- readFile (homeDir ++ "/.xyz/entry.txt") >>= return . template . fromString
-  let filename = "entries/" ++ (show entryNum) ++ "-" ++ (unpack . (toLower. replace " " "-") $ pack entryName) ++ ".txt"
+  --let filename = "entries/" ++ (show entryNum) ++ "-" ++ (unpack . (toLower. replace " " "-") $ pack entryName) ++ ".txt"
+
+  case entrySpec of
+    Just (title, videoSpec) -> do
+      let filename = "entries/" ++ entryNum ++ "-" ++ (unpack . slugify $ title) ++ ".txt"
+      case videoSpec of
+        Just (videoId, videoFilename) -> putStrLn "oh jimmy"
+        Nothing -> putStrLn "oh bimmy"
+
 
-  case video of
-     Just (videoId, videoFilename) -> do
-       let tmplContext = context $ [("timestamp", fromString . show $ (stamp::Integer)), ("title", pack entryName), ("videofilename", pack $ videoFilename), ("videoid", pack videoId)]
-       let rawEntry = unpack . toStrict $ render videoTemplate tmplContext
-       writeFile filename rawEntry
-       callCommand $ "youtube-dl -f 'webm[height<1080]+bestaudio' \"https://www.youtube.com/watch?v=" ++ videoId ++ "\" -o 'build/videos/" ++ videoFilename ++ "'"
-     Nothing -> do
-       let tmplContext = context $ [("timestamp", fromString . show $ (stamp::Integer)), ("title", pack entryName)]
-       let rawEntry = unpack . toStrict $ render normalTemplate tmplContext
-       writeFile filename rawEntry
+  putStrLn "lel"
+  -- case video of
+  --    Just (videoId, videoFilename) -> do
+  --      let tmplContext = context $ [("timestamp", fromString . show $ (stamp::Integer)), ("title", pack entryName), ("videofilename", pack $ videoFilename), ("videoid", pack videoId)]
+  --      let rawEntry = unpack . toStrict $ render videoTemplate tmplContext
+  --      writeFile filename rawEntry
+  --      callCommand $ "youtube-dl -f 'webm[height<1080]+bestaudio' \"https://www.youtube.com/watch?v=" ++ videoId ++ "\" -o 'build/videos/" ++ videoFilename ++ "'"
+  --    Nothing -> do
+  --      let tmplContext = context $ [("timestamp", fromString . show $ (stamp::Integer)), ("title", pack entryName)]
+  --      let rawEntry = unpack . toStrict $ render normalTemplate tmplContext
+  --      writeFile filename rawEntry
 
-  (putStrLn $ ("Created " ++ filename)) >> build
+  -- (putStrLn $ ("Created " ++ filename)) >> build
 
-  push <- yornPrompt "Do you want to push this entry?"
+  -- push <- yornPrompt "Do you want to push this entry?"
 
-  case push of
-    True -> do callCommand $ "git add . && git commit -m \"" ++ entryName ++ "\" && git push"
-    False -> return ()
+  -- case push of
+  --   True -> do callCommand $ "git add . && git commit -m \"" ++ entryName ++ "\" && git push"
+  --   False -> return ()
 
-  putStrLn "Thanks for using xyz!"
+  -- putStrLn "Thanks for using xyz!"
 
 usage :: IO ()
 usage =  putStr . ununlines $ [