Skip to content

Commit 1a44b65

Browse files
committed
Concert from String to Text
1 parent 6ae206b commit 1a44b65

22 files changed

+198
-130
lines changed

vcsgui/src/VCSGui/Common/Commit.hs

Lines changed: 11 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE OverloadedStrings #-}
12
-----------------------------------------------------------------------------
23
--
34
-- Module : Main
@@ -30,6 +31,8 @@ import Control.Monad
3031
import Control.Monad.Reader
3132
import Data.Maybe
3233
import Paths_vcsgui(getDataFileName)
34+
import qualified Data.Text as T (unpack, pack)
35+
import Data.Text (Text)
3336

3437
--
3538
-- glade path and object accessors
@@ -47,7 +50,7 @@ accessorActTxtViewMsg = "txtViewMsg"
4750
--
4851

4952
-- | This function will be called after the ok action is called.
50-
type OkCallBack = String -- ^ Commit message as specified in the GUI.
53+
type OkCallBack = Text -- ^ Commit message as specified in the GUI.
5154
-> [FilePath] -- ^ List of 'FilePath's of the files that were selected.
5255
-> [Option] -- ^ options (this is currently not implemented i.e. '[]' is passed)
5356
-> Wrapper.Ctx ()
@@ -66,8 +69,8 @@ data CommitGUI = CommitGUI {
6669
}
6770

6871
-- | Represents a file which can be selected for commiting.
69-
data SCFile = GITSCFile Bool FilePath String |
70-
SVNSCFile Bool FilePath String Bool
72+
data SCFile = GITSCFile Bool FilePath Text |
73+
SVNSCFile Bool FilePath Text Bool
7174
deriving (Show)
7275

7376
-- | Return 'True' if the 'SCFile' is flagged as selected.
@@ -81,7 +84,7 @@ filePath (GITSCFile _ fp _ ) = fp
8184
filePath (SVNSCFile _ fp _ _) = fp
8285

8386
-- | Return the status of this file.
84-
status :: SCFile -> String
87+
status :: SCFile -> Text
8588
status (GITSCFile _ _ s) = s
8689
status (SVNSCFile _ _ s _) = s
8790

@@ -92,7 +95,7 @@ isLocked _ = False
9295

9396

9497
-- | Options to the 'OkCallBack'.
95-
type Option = String
98+
type Option = Text
9699

97100

98101
-- | Display a window to enter a commit message and select files to be commited.
@@ -150,7 +153,7 @@ getSelectedFiles listStore = do
150153
return (selectedFiles)
151154

152155
getTreeViewFromGladeCustomStore :: Builder
153-
-> String
156+
-> Text
154157
-> TreeViewSetter
155158
-> Wrapper.Ctx (H.TreeViewItem SCFile)
156159
getTreeViewFromGladeCustomStore builder name setupListStore = do
@@ -166,9 +169,9 @@ getTreeViewFromGladeCustomStore builder name setupListStore = do
166169
wrapWidget :: GObjectClass objClass =>
167170
Builder
168171
-> (GObject -> objClass)
169-
-> String -> IO (String, objClass)
172+
-> Text -> IO (Text, objClass)
170173
wrapWidget builder cast name = do
171-
putStrLn $ " cast " ++ name
174+
putStrLn $ " cast " ++ T.unpack name
172175
gobj <- builderGetObject builder cast name
173176
return (name, gobj)
174177

vcsgui/src/VCSGui/Common/ConflictsResolved.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE OverloadedStrings #-}
12
-----------------------------------------------------------------------------
23
--
34
-- Module : VCSGui.Common.ConflictsResolved

vcsgui/src/VCSGui/Common/Error.hs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE OverloadedStrings #-}
12
-----------------------------------------------------------------------------
23
--
34
-- Module : VCSGui.Common.Error
@@ -15,11 +16,12 @@
1516
module VCSGui.Common.Error (
1617
showErrorGUI
1718
) where
18-
import Graphics.UI.Gtk
1919

20+
import Graphics.UI.Gtk
21+
import Data.Text (Text)
2022

2123
-- | Displays a simple window displaying given 'String' as an error message.
22-
showErrorGUI :: String -- ^ Message to display.
24+
showErrorGUI :: Text -- ^ Message to display.
2325
-> IO ()
2426
showErrorGUI msg = do
2527
dialog <- messageDialogNew Nothing [] MessageError ButtonsOk msg

vcsgui/src/VCSGui/Common/ExceptionHandler.hs

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE OverloadedStrings #-}
12
-----------------------------------------------------------------------------
23
--
34
-- Module : VCSGui.Common.ExceptionHandler
@@ -20,6 +21,8 @@ import qualified Control.Exception as Exc
2021

2122
import VCSWrapper.Common
2223
import VCSGui.Common.Error
24+
import qualified Data.Text as T (unwords, unlines)
25+
import Data.Monoid ((<>))
2326

2427

2528
-- | Wraps an IO computation to display an error message if a 'VCSException' occurs.
@@ -30,7 +33,7 @@ defaultVCSExceptionHandler vcsRunner = do
3033
case o of
3134
Left (VCSException exitCode out err repoLocation (cmd:opts)) -> do
3235
putStrLn $ "exception caught"
33-
showErrorGUI $ unlines ["An error occured.", err, "Details:", "command: " ++ cmd, "options: " ++ unwords opts]
36+
showErrorGUI $ T.unlines ["An error occured.", err, "Details:", "command: " <> cmd, "options: " <> T.unwords opts]
3437
Right _ -> do
3538
putStrLn $ "no exception"
3639
return ()

vcsgui/src/VCSGui/Common/FilesInConflict.hs

Lines changed: 12 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE ScopedTypeVariables #-}
2+
{-# LANGUAGE OverloadedStrings #-}
23
-----------------------------------------------------------------------------
34
--
45
-- Module : VCSGui.Common.FilesInConflict
@@ -29,6 +30,8 @@ import Control.Monad.Trans(liftIO)
2930
import Control.Monad
3031
import Control.Monad.Reader
3132
import Paths_vcsgui(getDataFileName)
33+
import Data.Text (Text)
34+
import qualified Data.Text as T (unpack, pack)
3235

3336
--
3437
-- glade path and object accessors
@@ -94,7 +97,7 @@ showFilesInConflictGUI (Just setUpTreeView) filesInConflict filesToResolveGetter
9497
gui <- loadGUI $ setUpTreeView cwd filesInConflict filesToResolveGetter resolveMarker eMergeToolSetter
9598
mbMergeToolSetter <- case eMergeToolSetter of
9699
Left (Merge.MergeTool path) -> do
97-
liftIO $ H.set (entPath gui) path
100+
liftIO $ H.set (entPath gui) $ T.pack path
98101
return Nothing
99102
Right setter -> return $ Just setter
100103

@@ -112,7 +115,7 @@ showFilesInConflictGUI (Just setUpTreeView) filesInConflict filesToResolveGetter
112115
Nothing -> return ()
113116
Just path -> do
114117
-- update gui
115-
H.set (entPath gui) path
118+
H.set (entPath gui) $ T.pack path
116119
-- call setter
117120
case mbMergeToolSetter of
118121
Nothing -> return ()
@@ -155,7 +158,7 @@ defaultSetUpTreeView mbcwd conflictingFiles filesToResolveGetter resolveMarker e
155158
H.addColumnToTreeView' treeViewItem
156159
renderer
157160
"File"
158-
$ \scf -> [cellText := filePath scf]
161+
$ \scf -> [cellText := T.pack $ filePath scf]
159162

160163
renderer <- cellRendererToggleNew
161164
H.addColumnToTreeView' treeViewItem
@@ -164,7 +167,7 @@ defaultSetUpTreeView mbcwd conflictingFiles filesToResolveGetter resolveMarker e
164167
$ \scf -> [cellToggleActive := isResolved scf]
165168

166169
-- connect select action
167-
on renderer cellToggled $ \(columnId::String) -> do
170+
on renderer cellToggled $ \(columnId :: Text) -> do
168171
putStrLn $ "Checkbutton clicked at column " ++ (show columnId)
169172
--TODO only call tool if button is not checked, move this code to being called if a click on row is received
170173
let callTool' = (\path -> Wrapper.runVcs config $ callTool columnId listStore path)
@@ -182,7 +185,7 @@ defaultSetUpTreeView mbcwd conflictingFiles filesToResolveGetter resolveMarker e
182185
Just treeIter <- liftIO $ treeModelGetIterFromString listStore columnId
183186
value <- liftIO $ listStoreGetValue listStore $ listStoreIterToIndex treeIter
184187
filesToResolve <- filesToResolveGetter $ filePath value
185-
resolvedByTool <- liftIO $ Process.exec mbcwd pathToTool filesToResolve
188+
resolvedByTool <- liftIO $ Process.exec mbcwd pathToTool $ map T.pack filesToResolve
186189
let setResolved' = setResolved listStore treeIter value
187190
case resolvedByTool of
188191
False -> ConflictsResolvedGUI.showConflictsResolvedGUI
@@ -204,7 +207,7 @@ defaultSetUpTreeView mbcwd conflictingFiles filesToResolveGetter resolveMarker e
204207
----
205208

206209
getTreeViewFromGladeCustomStore :: Builder
207-
-> String
210+
-> Text
208211
-> (TreeView -> Wrapper.Ctx (ListStore SCFile)) -- ^ fn defining how to setup the liststore
209212
-> Wrapper.Ctx (H.TreeViewItem SCFile)
210213
getTreeViewFromGladeCustomStore builder name setupListStore = do
@@ -220,9 +223,9 @@ getTreeViewFromGladeCustomStore builder name setupListStore = do
220223
wrapWidget :: GObjectClass objClass =>
221224
Builder
222225
-> (GObject -> objClass)
223-
-> String -> IO (String, objClass)
226+
-> Text -> IO (Text, objClass)
224227
wrapWidget builder cast name = do
225-
putStrLn $ " cast " ++ name
228+
putStrLn $ " cast " ++ T.unpack name
226229
gobj <- builderGetObject builder cast name
227230
return (name, gobj)
228231

@@ -245,7 +248,7 @@ setToListStore (store, view) newList = do
245248
-- HELPER
246249

247250
-- | shows a dialog to choose a folder, returns Just FilePath to folder if succesfull, Nothing if cancelled
248-
showFolderChooserDialog :: String -- ^ title of the window
251+
showFolderChooserDialog :: Text -- ^ title of the window
249252
-> Window -- ^ parent window
250253
-> FileChooserAction
251254
-> IO (Maybe FilePath)

0 commit comments

Comments
 (0)