Fix build
This commit is contained in:
parent
274aabe1f3
commit
5aef692b4f
@ -35,11 +35,12 @@ library
|
||||
data-default,
|
||||
filepath >= 1.3.0.0,
|
||||
hinotify-bytestring,
|
||||
hpath >= 0.6.0,
|
||||
hpath >= 0.7.1,
|
||||
safe,
|
||||
stm,
|
||||
time >= 1.4.2,
|
||||
unix
|
||||
unix,
|
||||
utf8-string
|
||||
hs-source-dirs: src
|
||||
default-language: Haskell2010
|
||||
Default-Extensions: RecordWildCards
|
||||
@ -76,7 +77,7 @@ executable hsfm-gtk
|
||||
glib >= 0.13,
|
||||
gtk3 >= 0.14.1,
|
||||
hinotify-bytestring,
|
||||
hpath >= 0.6.0,
|
||||
hpath >= 0.7.1,
|
||||
hsfm,
|
||||
old-locale >= 1,
|
||||
process,
|
||||
|
@ -38,6 +38,10 @@ module HSFM.FileSystem.FileType where
|
||||
|
||||
|
||||
import Data.ByteString(ByteString)
|
||||
import Data.ByteString.UTF8
|
||||
(
|
||||
toString
|
||||
)
|
||||
import Data.Default
|
||||
import Data.Time.Clock.POSIX
|
||||
(
|
||||
@ -533,7 +537,7 @@ fromFreeVar f df = maybeD f $ getFreeVar df
|
||||
|
||||
|
||||
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`.
|
||||
|
@ -44,6 +44,11 @@ import Data.ByteString
|
||||
(
|
||||
ByteString
|
||||
)
|
||||
import Data.ByteString.UTF8
|
||||
(
|
||||
fromString
|
||||
, toString
|
||||
)
|
||||
import Data.Foldable
|
||||
(
|
||||
for_
|
||||
@ -384,20 +389,20 @@ operationFinal mygui myview mitem = withErrorDialog $ do
|
||||
case op of
|
||||
FMove (PartialMove s) -> do
|
||||
let cmsg = "Really move " ++ imsg s
|
||||
++ " to \"" ++ P.fpToString (P.fromAbs cdir)
|
||||
++ " to \"" ++ toString (P.fromAbs cdir)
|
||||
++ "\"?"
|
||||
withConfirmationDialog cmsg $ doFileOperation (FMove $ Move s cdir)
|
||||
popStatusbar mygui
|
||||
writeTVarIO (operationBuffer mygui) None
|
||||
FCopy (PartialCopy s) -> do
|
||||
let cmsg = "Really copy " ++ imsg s
|
||||
++ " to \"" ++ P.fpToString (P.fromAbs cdir)
|
||||
++ " to \"" ++ toString (P.fromAbs cdir)
|
||||
++ "\"?"
|
||||
withConfirmationDialog cmsg $ doFileOperation (FCopy $ Copy s cdir)
|
||||
_ -> return ()
|
||||
where
|
||||
imsg s = case s of
|
||||
(item:[]) -> "\"" ++ P.fpToString (P.fromAbs item) ++ "\""
|
||||
(item:[]) -> "\"" ++ toString (P.fromAbs item) ++ "\""
|
||||
items -> (show . length $ items) ++ " items"
|
||||
|
||||
|
||||
@ -405,7 +410,7 @@ operationFinal mygui myview mitem = withErrorDialog $ do
|
||||
newFile :: MyGUI -> MyView -> IO ()
|
||||
newFile _ myview = withErrorDialog $ do
|
||||
mfn <- textInputDialog "Enter file name" ("" :: String)
|
||||
let pmfn = P.parseFn =<< P.userStringToFP <$> mfn
|
||||
let pmfn = P.parseFn =<< fromString <$> mfn
|
||||
for_ pmfn $ \fn -> do
|
||||
cdir <- getCurrentDir myview
|
||||
createRegularFile (path cdir P.</> fn)
|
||||
@ -415,7 +420,7 @@ newFile _ myview = withErrorDialog $ do
|
||||
newDir :: MyGUI -> MyView -> IO ()
|
||||
newDir _ myview = withErrorDialog $ do
|
||||
mfn <- textInputDialog "Enter directory name" ("" :: String)
|
||||
let pmfn = P.parseFn =<< P.userStringToFP <$> mfn
|
||||
let pmfn = P.parseFn =<< fromString <$> mfn
|
||||
for_ pmfn $ \fn -> do
|
||||
cdir <- getCurrentDir myview
|
||||
createDir (path cdir P.</> fn)
|
||||
@ -425,11 +430,11 @@ renameF :: [Item] -> MyGUI -> MyView -> IO ()
|
||||
renameF [item] _ _ = withErrorDialog $ do
|
||||
iname <- P.fromRel <$> (P.basename $ path item)
|
||||
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
|
||||
let cmsg = "Really rename \"" ++ getFPasStr item
|
||||
++ "\"" ++ " to \""
|
||||
++ P.fpToString (P.fromAbs $ (P.dirname . path $ item)
|
||||
++ toString (P.fromAbs $ (P.dirname . path $ item)
|
||||
P.</> fn) ++ "\"?"
|
||||
withConfirmationDialog cmsg $
|
||||
HPath.IO.renameFile (path item)
|
||||
|
@ -26,12 +26,18 @@ module HSFM.GUI.Gtk.Callbacks.Utils where
|
||||
|
||||
import Control.Monad
|
||||
(
|
||||
forM_
|
||||
forM
|
||||
, forM_
|
||||
)
|
||||
import Control.Monad.IO.Class
|
||||
(
|
||||
liftIO
|
||||
)
|
||||
import GHC.IO.Exception
|
||||
(
|
||||
IOErrorType(..)
|
||||
)
|
||||
import Graphics.UI.Gtk
|
||||
import qualified HPath as P
|
||||
import HPath.IO
|
||||
import HPath.IO.Errors
|
||||
@ -46,6 +52,10 @@ import HSFM.Utils.IO
|
||||
modifyTVarIO
|
||||
)
|
||||
import Prelude hiding(readFile)
|
||||
import Control.Concurrent.STM.TVar
|
||||
(
|
||||
readTVarIO
|
||||
)
|
||||
|
||||
|
||||
|
||||
|
@ -151,7 +151,7 @@ fileCollisionDialog t = do
|
||||
ResponseUser 4 -> do
|
||||
mfn <- textInputDialog (fromString "Enter new name") (takeFileName t)
|
||||
forM mfn $ \fn -> do
|
||||
pfn <- P.parseFn (P.userStringToFP fn)
|
||||
pfn <- P.parseFn (fromString fn)
|
||||
return $ Rename pfn
|
||||
_ -> throwIO UnknownDialogButton
|
||||
|
||||
@ -176,7 +176,7 @@ renameDialog t = do
|
||||
ResponseUser 2 -> do
|
||||
mfn <- textInputDialog (fromString "Enter new name") (takeFileName t)
|
||||
forM mfn $ \fn -> do
|
||||
pfn <- P.parseFn (P.userStringToFP fn)
|
||||
pfn <- P.parseFn (fromString fn)
|
||||
return $ Rename pfn
|
||||
_ -> throwIO UnknownDialogButton
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user