From 5ce7e3baac18497f586208ef563d4009f5e8f2dd Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Juan=20Jos=C3=A9=20Rodr=C3=ADguez=20L=C3=B3pez?= Date: Fri, 4 Aug 2017 15:00:31 +0100 Subject: [PATCH 1/6] PDF exporting Added the functionality to export PDFs to the ToolBar --- src/common/HaskellDo/Compilation/State.hs | 1 - src/common/HaskellDo/State.hs | 1 - src/common/HaskellDo/Toolbar/State.hs | 16 ++++++++++++++++ src/common/HaskellDo/Toolbar/Types.hs | 1 + src/common/HaskellDo/Toolbar/View.hs | 22 +++++++++++++++++++++- src/common/HaskellDo/View.hs | 4 ++++ 6 files changed, 42 insertions(+), 3 deletions(-) diff --git a/src/common/HaskellDo/Compilation/State.hs b/src/common/HaskellDo/Compilation/State.hs index 08467c0..91a48f2 100644 --- a/src/common/HaskellDo/Compilation/State.hs +++ b/src/common/HaskellDo/Compilation/State.hs @@ -95,7 +95,6 @@ buildOutput state = do System.ExitSuccess -> return state { compiledOutput = preprocessOutput out, compilationError = "", dirtyCompile = True } - preprocessOutput :: String -> String preprocessOutput out = Text.pack out diff --git a/src/common/HaskellDo/State.hs b/src/common/HaskellDo/State.hs index a485650..72a5b0a 100644 --- a/src/common/HaskellDo/State.hs +++ b/src/common/HaskellDo/State.hs @@ -168,4 +168,3 @@ handleRead :: Either SomeException String -> IO (Maybe String) handleRead = \case Left _ -> return Nothing Right txt -> return (Just txt) - diff --git a/src/common/HaskellDo/Toolbar/State.hs b/src/common/HaskellDo/Toolbar/State.hs index bbecc08..d598565 100644 --- a/src/common/HaskellDo/Toolbar/State.hs +++ b/src/common/HaskellDo/Toolbar/State.hs @@ -17,6 +17,8 @@ module HaskellDo.Toolbar.State where import System.Directory (listDirectory, doesFileExist, doesDirectoryExist, getHomeDirectory, createDirectory) import System.FilePath (()) +import System.Process (readProcess, callCommand) +import Data.List (isInfixOf) import Control.Monad (filterM, unless) @@ -25,6 +27,8 @@ import Transient.Move import HaskellDo.Toolbar.Types import Foreign.Materialize import Foreign.JQuery +--import System.Process (callCommand, readProcess) +--import Data.List (isInfixOf) initialState :: State initialState = State @@ -134,6 +138,18 @@ update ToggleError state = do localIO toggleError return state +update ConvertToPDF state = do + isInstalled <- atRemote . localIO $ readProcess "find" ["/usr/bin","-name","wkhtmltopdf"] [] + environmentVar <- atRemote . localIO $ readProcess "which" ["wkhtmltopdf"] [] + let path = projectPath state + if ((isInstalled /= "") || (isInfixOf "bin" environmentVar)) && (projectOpened state) == True + then do + atRemote . localIO $ callCommand ("cd " ++ path ++ " && stack exec run-test > index.html && wkhtmltopdf index.html index.pdf" :: String) + localIO $ openModal "#convertToPDFModal" + else + localIO $ openModal "#convertToPDFModalFail" + return state + update _ state = return state shakeErrorDisplay :: IO () diff --git a/src/common/HaskellDo/Toolbar/Types.hs b/src/common/HaskellDo/Toolbar/Types.hs index ca2fe95..636b8fc 100644 --- a/src/common/HaskellDo/Toolbar/Types.hs +++ b/src/common/HaskellDo/Toolbar/Types.hs @@ -40,4 +40,5 @@ data Action | ClosePackageModal | ToggleEditor | ToggleError + | ConvertToPDF deriving (Read, Show) diff --git a/src/common/HaskellDo/Toolbar/View.hs b/src/common/HaskellDo/Toolbar/View.hs index e2b791f..8f075b9 100644 --- a/src/common/HaskellDo/Toolbar/View.hs +++ b/src/common/HaskellDo/Toolbar/View.hs @@ -40,9 +40,12 @@ toolbar = rawHtml $ do li ! id "packageEditorButton" $ noHtml li ! id "toggleEditorButton" $ noHtml li ! id "toggleErrorButton" $ noHtml + li ! id "convertToPDFButton" $ noHtml packageEditorModal -- Apparently, if we put this line openProjectModal -- under this one. The open project modal doesn't work modalPromptPlaceholder "newDirectoryModal" "New Directory" "Choose a name for the new directory" + convertToPDFModal + convertToPDFModalFail openProjectModal :: Perch openProjectModal = @@ -62,8 +65,20 @@ openProjectModal = div ! atr "class" "modal-footer" $ div ! id "closeModalButton" $ noHtml +convertToPDFModal :: Perch +convertToPDFModal = + div ! id "convertToPDFModal" ! atr "class" "modal" $ do + div ! atr "class" "modal-content" $ do + h4 ("PDF saved on project path" :: String) + +convertToPDFModalFail :: Perch +convertToPDFModalFail = + div ! id "convertToPDFModalFail" ! atr "class" "modal" $ do + div ! atr "class" "modal-content" $ do + h4 ("wkhtmltopdf is not installed or a project has not been loaded" :: String) + modalPromptPlaceholder :: String -> String -> String -> Perch -modalPromptPlaceholder id' htitle text = +modalPromptPlaceholder id' htitle text = div ! id id' ! atr "class" "modal" $ do div ! atr "class" "modal-content" $ do if (not . null) htitle then h4 htitle else noHtml @@ -125,6 +140,11 @@ toggleErrorButton _ = Ulmus.newWidget "toggleErrorButton" $ wlink ToggleError $ a ! atr "class" "btn-floating purple darken-2 tooltipped" ! atr "data-position" "bottom" ! atr "data-tooltip" "Toggle error" ! atr "data-delay" "50"$ i ! atr "class" "material-icons" $ ("error" :: String) +convertToPDFButton :: State -> Widget Action +convertToPDFButton _ = Ulmus.newWidget "convertToPDFButton" $ wlink ConvertToPDF $ + a ! atr "class" "btn-floating purple darken-2 tooltipped" ! atr "data-position" "bottom" ! atr "data-tooltip" "Convert to PDF" ! atr "data-delay" "50"$ + i ! atr "class" "material-icons" $ ("picture_as_pdf" :: String) + closeModalButton :: State -> Widget Action closeModalButton _ = Ulmus.newWidget "closeModalButton" $ wlink LoadProject $ diff --git a/src/common/HaskellDo/View.hs b/src/common/HaskellDo/View.hs index 5a98644..a3f9100 100644 --- a/src/common/HaskellDo/View.hs +++ b/src/common/HaskellDo/View.hs @@ -68,6 +68,7 @@ widgets state = do **> packageEditorButtonWidget **> toggleEditorButtonWidget **> toggleErrorButtonWidget + **> convertToPDFButtonWidget **> compileButtonWidget **> pathInputWidget **> closeModalButtonWidget @@ -98,6 +99,9 @@ widgets state = do toggleErrorButtonWidget = Ulmus.mapAction ToolbarAction $ Toolbar.toggleErrorButton (toolbarState state) + convertToPDFButtonWidget = Ulmus.mapAction ToolbarAction $ + Toolbar.convertToPDFButton (toolbarState state) + pathInputWidget = Ulmus.mapAction ToolbarAction $ Toolbar.pathInput (toolbarState state) From c79fea05cd65435dfabf5e29f33e26c3f28ad49b Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Juan=20Jos=C3=A9=20Rodr=C3=ADguez=20L=C3=B3pez?= Date: Fri, 4 Aug 2017 17:50:42 +0100 Subject: [PATCH 2/6] Fixed a bug with PDF export Fixed the way Haskell-do reacts when wkhtmltopdf is not installed. --- src/common/HaskellDo/Toolbar/State.hs | 10 ++++------ src/common/HaskellDo/Toolbar/View.hs | 2 +- 2 files changed, 5 insertions(+), 7 deletions(-) diff --git a/src/common/HaskellDo/Toolbar/State.hs b/src/common/HaskellDo/Toolbar/State.hs index d598565..247a209 100644 --- a/src/common/HaskellDo/Toolbar/State.hs +++ b/src/common/HaskellDo/Toolbar/State.hs @@ -17,7 +17,7 @@ module HaskellDo.Toolbar.State where import System.Directory (listDirectory, doesFileExist, doesDirectoryExist, getHomeDirectory, createDirectory) import System.FilePath (()) -import System.Process (readProcess, callCommand) +import System.Process (callCommand, shell, readProcess,readCreateProcessWithExitCode) import Data.List (isInfixOf) import Control.Monad (filterM, unless) @@ -27,8 +27,6 @@ import Transient.Move import HaskellDo.Toolbar.Types import Foreign.Materialize import Foreign.JQuery ---import System.Process (callCommand, readProcess) ---import Data.List (isInfixOf) initialState :: State initialState = State @@ -139,10 +137,10 @@ update ToggleError state = do return state update ConvertToPDF state = do - isInstalled <- atRemote . localIO $ readProcess "find" ["/usr/bin","-name","wkhtmltopdf"] [] - environmentVar <- atRemote . localIO $ readProcess "which" ["wkhtmltopdf"] [] + checkIfInstalled <- atRemote . localIO $ readProcess "find" ["/usr/bin","-name","wkhtmltopdf"] [] + (_,environmentVar,_) <- atRemote . localIO $ readCreateProcessWithExitCode (shell "which") "wkhtmltopdf" let path = projectPath state - if ((isInstalled /= "") || (isInfixOf "bin" environmentVar)) && (projectOpened state) == True + if ((checkIfInstalled /= "") || (isInfixOf "bin" environmentVar)) && ((projectOpened state) == True) then do atRemote . localIO $ callCommand ("cd " ++ path ++ " && stack exec run-test > index.html && wkhtmltopdf index.html index.pdf" :: String) localIO $ openModal "#convertToPDFModal" diff --git a/src/common/HaskellDo/Toolbar/View.hs b/src/common/HaskellDo/Toolbar/View.hs index 8f075b9..7b5eb5f 100644 --- a/src/common/HaskellDo/Toolbar/View.hs +++ b/src/common/HaskellDo/Toolbar/View.hs @@ -75,7 +75,7 @@ convertToPDFModalFail :: Perch convertToPDFModalFail = div ! id "convertToPDFModalFail" ! atr "class" "modal" $ do div ! atr "class" "modal-content" $ do - h4 ("wkhtmltopdf is not installed or a project has not been loaded" :: String) + h4 ("Error: wkhtmltopdf is not installed or a project has not been loaded" :: String) modalPromptPlaceholder :: String -> String -> String -> Perch modalPromptPlaceholder id' htitle text = From 80ca3bea409b67070f56bfe560611b7606dc1504 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Juan=20Jos=C3=A9=20Rodr=C3=ADguez=20L=C3=B3pez?= Date: Fri, 4 Aug 2017 18:54:18 +0100 Subject: [PATCH 3/6] Fixed a bug with PDF export Changed the way Haskell-do detects that wkhtmltopdf is not in $PATH. --- src/common/HaskellDo/Toolbar/State.hs | 16 ++++++++++++---- 1 file changed, 12 insertions(+), 4 deletions(-) diff --git a/src/common/HaskellDo/Toolbar/State.hs b/src/common/HaskellDo/Toolbar/State.hs index 247a209..d7dc5cc 100644 --- a/src/common/HaskellDo/Toolbar/State.hs +++ b/src/common/HaskellDo/Toolbar/State.hs @@ -18,7 +18,8 @@ module HaskellDo.Toolbar.State where import System.Directory (listDirectory, doesFileExist, doesDirectoryExist, getHomeDirectory, createDirectory) import System.FilePath (()) import System.Process (callCommand, shell, readProcess,readCreateProcessWithExitCode) -import Data.List (isInfixOf) +--import Data.List (isInfixOf) +import System.Exit import Control.Monad (filterM, unless) @@ -138,17 +139,24 @@ update ToggleError state = do update ConvertToPDF state = do checkIfInstalled <- atRemote . localIO $ readProcess "find" ["/usr/bin","-name","wkhtmltopdf"] [] - (_,environmentVar,_) <- atRemote . localIO $ readCreateProcessWithExitCode (shell "which") "wkhtmltopdf" + (errorCode,_,_) <- atRemote . localIO $ readCreateProcessWithExitCode (shell "which wkhtmltopdf") "" + let environmentVar = checkError errorCode :: Bool let path = projectPath state - if ((checkIfInstalled /= "") || (isInfixOf "bin" environmentVar)) && ((projectOpened state) == True) + if (checkIfInstalled /= "") && (environmentVar == True) && ((projectOpened state) == True) then do - atRemote . localIO $ callCommand ("cd " ++ path ++ " && stack exec run-test > index.html && wkhtmltopdf index.html index.pdf" :: String) localIO $ openModal "#convertToPDFModal" + atRemote . localIO $ callCommand ("cd " ++ path ++ " && stack exec run-test > index.html && wkhtmltopdf index.html index.pdf" :: String) else localIO $ openModal "#convertToPDFModalFail" return state update _ state = return state +checkError :: ExitCode -> Bool +checkError exitCode = + case exitCode of + ExitSuccess -> True + ExitFailure _ -> False + shakeErrorDisplay :: IO () shakeErrorDisplay = shake "#errorDisplay" From d24a3fab93e5c7103710b6dba2c1c636f90be4dd Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Juan=20Jos=C3=A9=20Rodr=C3=ADguez=20L=C3=B3pez?= Date: Wed, 23 Aug 2017 14:00:58 +0100 Subject: [PATCH 4/6] Code refactoring on PDF export Changed the way haskell-do checks if wkhtmltopdf is installed. --- src/common/HaskellDo/Toolbar/State.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/common/HaskellDo/Toolbar/State.hs b/src/common/HaskellDo/Toolbar/State.hs index d7dc5cc..f96ecfc 100644 --- a/src/common/HaskellDo/Toolbar/State.hs +++ b/src/common/HaskellDo/Toolbar/State.hs @@ -138,11 +138,10 @@ update ToggleError state = do return state update ConvertToPDF state = do - checkIfInstalled <- atRemote . localIO $ readProcess "find" ["/usr/bin","-name","wkhtmltopdf"] [] (errorCode,_,_) <- atRemote . localIO $ readCreateProcessWithExitCode (shell "which wkhtmltopdf") "" let environmentVar = checkError errorCode :: Bool let path = projectPath state - if (checkIfInstalled /= "") && (environmentVar == True) && ((projectOpened state) == True) + if (environmentVar == True) && ((projectOpened state) == True) then do localIO $ openModal "#convertToPDFModal" atRemote . localIO $ callCommand ("cd " ++ path ++ " && stack exec run-test > index.html && wkhtmltopdf index.html index.pdf" :: String) From 4868e688762149b2786c72ea710dfd44ad4841a4 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Juan=20Jos=C3=A9=20Rodr=C3=ADguez=20L=C3=B3pez?= Date: Wed, 23 Aug 2017 14:08:14 +0100 Subject: [PATCH 5/6] Remove an unnecesary import There is no need to keep the "readProcess" function. --- src/common/HaskellDo/Toolbar/State.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/common/HaskellDo/Toolbar/State.hs b/src/common/HaskellDo/Toolbar/State.hs index f96ecfc..b59d461 100644 --- a/src/common/HaskellDo/Toolbar/State.hs +++ b/src/common/HaskellDo/Toolbar/State.hs @@ -17,7 +17,7 @@ module HaskellDo.Toolbar.State where import System.Directory (listDirectory, doesFileExist, doesDirectoryExist, getHomeDirectory, createDirectory) import System.FilePath (()) -import System.Process (callCommand, shell, readProcess,readCreateProcessWithExitCode) +import System.Process (callCommand, shell,readCreateProcessWithExitCode) --import Data.List (isInfixOf) import System.Exit From 8ccbac05b628cec7aad000839a23cf9b12048712 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Juan=20Jos=C3=A9=20Rodr=C3=ADguez=20L=C3=B3pez?= Date: Wed, 30 Aug 2017 14:43:46 +0100 Subject: [PATCH 6/6] Change how the error looks like Now It's in the same color as compilation errors --- src/common/HaskellDo/Toolbar/View.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/common/HaskellDo/Toolbar/View.hs b/src/common/HaskellDo/Toolbar/View.hs index 7b5eb5f..f517a8e 100644 --- a/src/common/HaskellDo/Toolbar/View.hs +++ b/src/common/HaskellDo/Toolbar/View.hs @@ -74,7 +74,7 @@ convertToPDFModal = convertToPDFModalFail :: Perch convertToPDFModalFail = div ! id "convertToPDFModalFail" ! atr "class" "modal" $ do - div ! atr "class" "modal-content" $ do + div ! atr "class" "modal-content red darken-1 white-text" $ do h4 ("Error: wkhtmltopdf is not installed or a project has not been loaded" :: String) modalPromptPlaceholder :: String -> String -> String -> Perch