Fix build

This commit is contained in:
Julian Ospald 2016-05-29 13:26:21 +02:00
parent 274aabe1f3
commit 5aef692b4f
No known key found for this signature in database
GPG Key ID: 511B62C09D50CD28
5 changed files with 34 additions and 14 deletions

View File

@ -35,11 +35,12 @@ library
data-default, data-default,
filepath >= 1.3.0.0, filepath >= 1.3.0.0,
hinotify-bytestring, hinotify-bytestring,
hpath >= 0.6.0, hpath >= 0.7.1,
safe, safe,
stm, stm,
time >= 1.4.2, time >= 1.4.2,
unix unix,
utf8-string
hs-source-dirs: src hs-source-dirs: src
default-language: Haskell2010 default-language: Haskell2010
Default-Extensions: RecordWildCards Default-Extensions: RecordWildCards
@ -76,7 +77,7 @@ executable hsfm-gtk
glib >= 0.13, glib >= 0.13,
gtk3 >= 0.14.1, gtk3 >= 0.14.1,
hinotify-bytestring, hinotify-bytestring,
hpath >= 0.6.0, hpath >= 0.7.1,
hsfm, hsfm,
old-locale >= 1, old-locale >= 1,
process, process,

View File

@ -38,6 +38,10 @@ module HSFM.FileSystem.FileType where
import Data.ByteString(ByteString) import Data.ByteString(ByteString)
import Data.ByteString.UTF8
(
toString
)
import Data.Default import Data.Default
import Data.Time.Clock.POSIX import Data.Time.Clock.POSIX
( (
@ -533,7 +537,7 @@ fromFreeVar f df = maybeD f $ getFreeVar df
getFPasStr :: File a -> String getFPasStr :: File a -> String
getFPasStr = P.fpToString . P.fromAbs . path getFPasStr = toString . P.fromAbs . path
-- |Gets the free variable. Returns Nothing if the constructor is of `Failed`. -- |Gets the free variable. Returns Nothing if the constructor is of `Failed`.

View File

@ -44,6 +44,11 @@ import Data.ByteString
( (
ByteString ByteString
) )
import Data.ByteString.UTF8
(
fromString
, toString
)
import Data.Foldable import Data.Foldable
( (
for_ for_
@ -384,20 +389,20 @@ operationFinal mygui myview mitem = withErrorDialog $ do
case op of case op of
FMove (PartialMove s) -> do FMove (PartialMove s) -> do
let cmsg = "Really move " ++ imsg s let cmsg = "Really move " ++ imsg s
++ " to \"" ++ P.fpToString (P.fromAbs cdir) ++ " to \"" ++ toString (P.fromAbs cdir)
++ "\"?" ++ "\"?"
withConfirmationDialog cmsg $ doFileOperation (FMove $ Move s cdir) withConfirmationDialog cmsg $ doFileOperation (FMove $ Move s cdir)
popStatusbar mygui popStatusbar mygui
writeTVarIO (operationBuffer mygui) None writeTVarIO (operationBuffer mygui) None
FCopy (PartialCopy s) -> do FCopy (PartialCopy s) -> do
let cmsg = "Really copy " ++ imsg s let cmsg = "Really copy " ++ imsg s
++ " to \"" ++ P.fpToString (P.fromAbs cdir) ++ " to \"" ++ toString (P.fromAbs cdir)
++ "\"?" ++ "\"?"
withConfirmationDialog cmsg $ doFileOperation (FCopy $ Copy s cdir) withConfirmationDialog cmsg $ doFileOperation (FCopy $ Copy s cdir)
_ -> return () _ -> return ()
where where
imsg s = case s of imsg s = case s of
(item:[]) -> "\"" ++ P.fpToString (P.fromAbs item) ++ "\"" (item:[]) -> "\"" ++ toString (P.fromAbs item) ++ "\""
items -> (show . length $ items) ++ " items" items -> (show . length $ items) ++ " items"
@ -405,7 +410,7 @@ operationFinal mygui myview mitem = withErrorDialog $ do
newFile :: MyGUI -> MyView -> IO () newFile :: MyGUI -> MyView -> IO ()
newFile _ myview = withErrorDialog $ do newFile _ myview = withErrorDialog $ do
mfn <- textInputDialog "Enter file name" ("" :: String) mfn <- textInputDialog "Enter file name" ("" :: String)
let pmfn = P.parseFn =<< P.userStringToFP <$> mfn let pmfn = P.parseFn =<< fromString <$> mfn
for_ pmfn $ \fn -> do for_ pmfn $ \fn -> do
cdir <- getCurrentDir myview cdir <- getCurrentDir myview
createRegularFile (path cdir P.</> fn) createRegularFile (path cdir P.</> fn)
@ -415,7 +420,7 @@ newFile _ myview = withErrorDialog $ do
newDir :: MyGUI -> MyView -> IO () newDir :: MyGUI -> MyView -> IO ()
newDir _ myview = withErrorDialog $ do newDir _ myview = withErrorDialog $ do
mfn <- textInputDialog "Enter directory name" ("" :: String) mfn <- textInputDialog "Enter directory name" ("" :: String)
let pmfn = P.parseFn =<< P.userStringToFP <$> mfn let pmfn = P.parseFn =<< fromString <$> mfn
for_ pmfn $ \fn -> do for_ pmfn $ \fn -> do
cdir <- getCurrentDir myview cdir <- getCurrentDir myview
createDir (path cdir P.</> fn) createDir (path cdir P.</> fn)
@ -425,11 +430,11 @@ renameF :: [Item] -> MyGUI -> MyView -> IO ()
renameF [item] _ _ = withErrorDialog $ do renameF [item] _ _ = withErrorDialog $ do
iname <- P.fromRel <$> (P.basename $ path item) iname <- P.fromRel <$> (P.basename $ path item)
mfn <- textInputDialog "Enter new file name" (iname :: ByteString) mfn <- textInputDialog "Enter new file name" (iname :: ByteString)
let pmfn = P.parseFn =<< P.userStringToFP <$> mfn let pmfn = P.parseFn =<< fromString <$> mfn
for_ pmfn $ \fn -> do for_ pmfn $ \fn -> do
let cmsg = "Really rename \"" ++ getFPasStr item let cmsg = "Really rename \"" ++ getFPasStr item
++ "\"" ++ " to \"" ++ "\"" ++ " to \""
++ P.fpToString (P.fromAbs $ (P.dirname . path $ item) ++ toString (P.fromAbs $ (P.dirname . path $ item)
P.</> fn) ++ "\"?" P.</> fn) ++ "\"?"
withConfirmationDialog cmsg $ withConfirmationDialog cmsg $
HPath.IO.renameFile (path item) HPath.IO.renameFile (path item)

View File

@ -26,12 +26,18 @@ module HSFM.GUI.Gtk.Callbacks.Utils where
import Control.Monad import Control.Monad
( (
forM_ forM
, forM_
)
import Control.Monad.IO.Class
(
liftIO
) )
import GHC.IO.Exception import GHC.IO.Exception
( (
IOErrorType(..) IOErrorType(..)
) )
import Graphics.UI.Gtk
import qualified HPath as P import qualified HPath as P
import HPath.IO import HPath.IO
import HPath.IO.Errors import HPath.IO.Errors
@ -46,6 +52,10 @@ import HSFM.Utils.IO
modifyTVarIO modifyTVarIO
) )
import Prelude hiding(readFile) import Prelude hiding(readFile)
import Control.Concurrent.STM.TVar
(
readTVarIO
)

View File

@ -151,7 +151,7 @@ fileCollisionDialog t = do
ResponseUser 4 -> do ResponseUser 4 -> do
mfn <- textInputDialog (fromString "Enter new name") (takeFileName t) mfn <- textInputDialog (fromString "Enter new name") (takeFileName t)
forM mfn $ \fn -> do forM mfn $ \fn -> do
pfn <- P.parseFn (P.userStringToFP fn) pfn <- P.parseFn (fromString fn)
return $ Rename pfn return $ Rename pfn
_ -> throwIO UnknownDialogButton _ -> throwIO UnknownDialogButton
@ -176,7 +176,7 @@ renameDialog t = do
ResponseUser 2 -> do ResponseUser 2 -> do
mfn <- textInputDialog (fromString "Enter new name") (takeFileName t) mfn <- textInputDialog (fromString "Enter new name") (takeFileName t)
forM mfn $ \fn -> do forM mfn $ \fn -> do
pfn <- P.parseFn (P.userStringToFP fn) pfn <- P.parseFn (fromString fn)
return $ Rename pfn return $ Rename pfn
_ -> throwIO UnknownDialogButton _ -> throwIO UnknownDialogButton