More refactoring
authorCameron Ball <cameron@moodle.com>
Mon, 24 Jun 2019 08:07:39 +0000 (16:07 +0800)
committerCameron Ball <cameron@moodle.com>
Mon, 24 Jun 2019 08:07:39 +0000 (16:07 +0800)
app/Main.hs
src/Lib.hs
src/Prompts.hs
src/Util.hs

index 4ddb724..07f31d8 100644 (file)
@@ -3,12 +3,12 @@ module Main where
 import Data.List (intercalate)
 import Data.String hiding (unlines)
 import Data.Text hiding (map, init, length, splitAt)
 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.IO (putStrLn, putStr, writeFile)
 import Data.Text.Lazy (toStrict)
 import Data.Text.Template
 import Data.Time.Clock.POSIX
 import Lib
 import Data.Text.Lazy (toStrict)
 import Data.Text.Template
 import Data.Time.Clock.POSIX
 import Lib
-import Prelude hiding (putStrLn, putStr, init, unlines)
+import Prelude hiding (putStrLn, putStr, init, unlines, writeFile)
 import Prompts
 import System.Directory
 import System.Directory (doesFileExist)
 import Prompts
 import System.Directory
 import System.Directory (doesFileExist)
@@ -39,7 +39,7 @@ init = do
             themes <- allFilesIn $ home ++ "/.xyz/themes"
             projectSpec <- initPrompt (map pack themes)
             createDirectory "entries"
             themes <- allFilesIn $ home ++ "/.xyz/themes"
             projectSpec <- initPrompt (map pack themes)
             createDirectory "entries"
-            writeFile "xyz.json" . encode . toJSObject $ projectSpec
+            writeFile "xyz.json" . pack . encode . toJSObject $ projectSpec
             putStrLn "\n\nInitialised empty project"
 
 build :: IO ()
             putStrLn "\n\nInitialised empty project"
 
 build :: IO ()
@@ -58,40 +58,28 @@ entry = do
   homeDir <- getHomeDirectory
   entrySpec <- entryPrompt
   entryNum <- fmap (show . (+1) . length) $ allFilesIn "entries"
   homeDir <- getHomeDirectory
   entrySpec <- entryPrompt
   entryNum <- fmap (show . (+1) . length) $ allFilesIn "entries"
-  stamp <- fmap (show . round) getPOSIXTime
+  stamp <- fmap (pack . show . round) getPOSIXTime
   videoTemplate <- readFile (homeDir ++ "/.xyz/entry-video.txt") >>= return . template . fromString
   normalTemplate <- readFile (homeDir ++ "/.xyz/entry.txt") >>= return . template . fromString
   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"
 
 
-  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"
+  let rawEntry = case entrySpec of
+        Just (title, videoSpec) -> do
+          let baseContext = [("timestamp", stamp), ("title", title)]
+          case videoSpec of
+            Just (videoId, videoFilename) -> (title, toStrict . render videoTemplate $ context $ baseContext ++ [("videoid", videoId), ("videofilename", videoFilename)])
+            Nothing -> (title, toStrict . render normalTemplate $ context baseContext)
 
 
+  let fileName = "entries/" ++ entryNum ++ "-" ++ (unpack . slugify $ fst rawEntry) ++ ".txt"
+  writeFile fileName $ snd 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
+  callCommand $ "nano " ++ fileName
 
 
-  -- (putStrLn $ ("Created " ++ filename)) >> build
+  push <- pushPrompt
+  case push of
+    True -> do callCommand . unpack $ "git add . && git commit -m \"" +++ (fst rawEntry) +++ "\" && git push"
+    False -> return ()
 
 
-  -- 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 ()
-
-  -- putStrLn "Thanks for using xyz!"
+  putStrLn "Thanks for using xyz!"
 
 usage :: IO ()
 usage =  putStr . ununlines $ [
 
 usage :: IO ()
 usage =  putStr . ununlines $ [
index b48ddf8..123e315 100644 (file)
@@ -143,8 +143,3 @@ writeOutProject projectConfig files = do
   mapM_ (createDirectoryIfMissing True . takeDirectory . unpack . fst) $ getEntryPages project
   mapM_ (\x -> writeFile (unpack $ fst x) (unpack $ snd x)) $ getEntryPages project
   writeFile "build/index.html" $ unpack $ toStrict $ render (getIndexTemplate project) $ context [("index", entryListToIndex (entries project))]
   mapM_ (createDirectoryIfMissing True . takeDirectory . unpack . fst) $ getEntryPages project
   mapM_ (\x -> writeFile (unpack $ fst x) (unpack $ snd x)) $ getEntryPages project
   writeFile "build/index.html" $ unpack $ toStrict $ render (getIndexTemplate project) $ context [("index", entryListToIndex (entries project))]
-
-context :: [(Text, Text)] -> Context
-context assocs x = case lookup x $ assocs of
-                     Nothing -> "lol could not find that " `append` x
-                     Just a -> a
index 72530d6..aa54876 100644 (file)
@@ -1,11 +1,4 @@
-module Prompts (
-  textPrompt,
-  nonEmptyTextPrompt,
-  yornPrompt,
-  subPrompt,
-  entryPrompt,
-  initPrompt
-  ) where
+module Prompts (entryPrompt, initPrompt, pushPrompt) where
 
 import Util
 import Prelude hiding (getLine, null, putStrLn, putStr, unlines)
 
 import Util
 import Prelude hiding (getLine, null, putStrLn, putStr, unlines)
@@ -50,7 +43,7 @@ yornPrompt xs = do
                    "y" -> Right True
                    "n" -> Right False
                    _ -> Left "Please answer with y or n"
                    "y" -> Right True
                    "n" -> Right False
                    _ -> Left "Please answer with y or n"
-  prompt (xs +++ " (y/n):") getOneText v
+  prompt (xs +++ " (y/n): ") getOneText v
 
 listPrompt :: Text -> [Text] -> IO Text
 listPrompt xs options = do
 
 listPrompt :: Text -> [Text] -> IO Text
 listPrompt xs options = do
@@ -82,3 +75,5 @@ initPrompt themes = fmap (zip ["projectName", "description", "theme"]) $ sequenc
     nonEmptyTextPrompt "Enter a short description for your project: ",
     listPrompt "Which theme would you like to use?" themes
             ]
     nonEmptyTextPrompt "Enter a short description for your project: ",
     listPrompt "Which theme would you like to use?" themes
             ]
+
+pushPrompt = yornPrompt "Do you want to push this entry?"
index d1c5834..caae57c 100644 (file)
@@ -2,6 +2,7 @@ module Util where
 
 import Data.Text hiding (filter)
 import System.Directory
 
 import Data.Text hiding (filter)
 import System.Directory
+import Data.Text.Template
 
 ununlines :: [Text] -> Text
 ununlines = intercalate "\n\n"
 
 ununlines :: [Text] -> Text
 ununlines = intercalate "\n\n"
@@ -12,3 +13,8 @@ urlify = slugify . replace "?" ""
 allFilesIn dir = filter (/= "..")<$>(filter(/= "."))<$>(getDirectoryContents dir)
 
 (+++) = append
 allFilesIn dir = filter (/= "..")<$>(filter(/= "."))<$>(getDirectoryContents dir)
 
 (+++) = append
+
+context :: [(Text, Text)] -> Context
+context assocs x = case lookup x $ assocs of
+                     Nothing -> "[[" +++ x +++ "]]"
+                     Just a -> a