Remove last remnants of OverloadedStrings
This commit is contained in:
parent
0f247d55ab
commit
111581ef02
@ -16,7 +16,6 @@ along with this program; if not, write to the Free Software
|
||||
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
|
||||
--}
|
||||
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# OPTIONS_HADDOCK ignore-exports #-}
|
||||
|
||||
|
||||
|
@ -16,7 +16,6 @@ along with this program; if not, write to the Free Software
|
||||
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
|
||||
--}
|
||||
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# OPTIONS_HADDOCK ignore-exports #-}
|
||||
|
||||
|
||||
@ -67,7 +66,7 @@ instance GlibString BS.ByteString where
|
||||
newUTFStringLen = newUTFStringLen . toString
|
||||
genUTFOfs = genUTFOfs . toString
|
||||
stringLength = BS.length
|
||||
unPrintf s = BS.intercalate "%%" (BS.split _percent s)
|
||||
unPrintf s = BS.intercalate (BS.pack [_percent, _percent]) (BS.split _percent s)
|
||||
|
||||
|
||||
foreign import ccall unsafe "string.h strlen" c_strlen
|
||||
|
@ -16,17 +16,18 @@ along with this program; if not, write to the Free Software
|
||||
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
|
||||
--}
|
||||
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# OPTIONS_HADDOCK ignore-exports #-}
|
||||
|
||||
module Main where
|
||||
|
||||
|
||||
import qualified Data.ByteString as BS
|
||||
import Data.Maybe
|
||||
(
|
||||
fromJust
|
||||
, fromMaybe
|
||||
)
|
||||
import Data.Word8
|
||||
import Graphics.UI.Gtk
|
||||
import qualified HPath as P
|
||||
import HSFM.FileSystem.FileType
|
||||
@ -45,15 +46,17 @@ import System.IO.Error
|
||||
)
|
||||
import qualified System.Posix.Env.ByteString as SPE
|
||||
|
||||
slash :: BS.ByteString
|
||||
slash = BS.singleton _slash
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
args <- SPE.getArgs
|
||||
let mdir = fromMaybe (fromJust $ P.parseAbs "/")
|
||||
(P.parseAbs . headDef "/" $ args)
|
||||
let mdir = fromMaybe (fromJust $ P.parseAbs slash)
|
||||
(P.parseAbs . headDef slash $ args)
|
||||
|
||||
file <- catchIOError (pathToFile getFileInfo mdir) $
|
||||
\_ -> pathToFile getFileInfo . fromJust $ P.parseAbs "/"
|
||||
\_ -> pathToFile getFileInfo . fromJust $ P.parseAbs slash
|
||||
|
||||
_ <- initGUI
|
||||
mygui <- createMyGUI
|
||||
|
@ -16,7 +16,6 @@ along with this program; if not, write to the Free Software
|
||||
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
|
||||
--}
|
||||
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
{-# OPTIONS_HADDOCK ignore-exports #-}
|
||||
|
||||
|
@ -16,7 +16,6 @@ along with this program; if not, write to the Free Software
|
||||
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
|
||||
--}
|
||||
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{-# OPTIONS_HADDOCK ignore-exports #-}
|
||||
|
||||
|
@ -254,9 +254,9 @@ withErrorDialog io =
|
||||
|
||||
-- |Asks the user which directory copy mode he wants via dialog popup
|
||||
-- and returns 'DirCopyMode'.
|
||||
textInputDialog :: GlibString string
|
||||
=> string -- ^ window title
|
||||
-> string -- ^ initial text in input widget
|
||||
textInputDialog :: (GlibString s1, GlibString s2)
|
||||
=> s1 -- ^ window title
|
||||
-> s2 -- ^ initial text in input widget
|
||||
-> IO (Maybe String)
|
||||
textInputDialog title inittext = do
|
||||
chooserDialog <- messageDialogNew Nothing
|
||||
|
@ -16,7 +16,6 @@ along with this program; if not, write to the Free Software
|
||||
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
|
||||
--}
|
||||
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# OPTIONS_HADDOCK ignore-exports #-}
|
||||
|
||||
|
||||
@ -27,6 +26,7 @@ import Data.ByteString
|
||||
(
|
||||
ByteString
|
||||
)
|
||||
import qualified Data.ByteString.UTF8 as BU
|
||||
import Data.Maybe
|
||||
import System.Posix.Env.ByteString
|
||||
import System.Posix.Process.ByteString
|
||||
@ -49,11 +49,11 @@ import System.Posix.Process.ByteString
|
||||
terminalCommand :: ByteString -- ^ current directory of the FM
|
||||
-> IO a
|
||||
terminalCommand cwd =
|
||||
executeFile -- executes the given command
|
||||
"sakura" -- the terminal command
|
||||
True -- whether to search PATH
|
||||
["-d", cwd] -- arguments for the command
|
||||
Nothing -- optional custom environment: `Just [(String, String)]`
|
||||
executeFile -- executes the given command
|
||||
(BU.fromString "sakura") -- the terminal command
|
||||
True -- whether to search PATH
|
||||
[BU.fromString "-d", cwd] -- arguments for the command
|
||||
Nothing -- optional custom environment: `Just [(String, String)]`
|
||||
|
||||
|
||||
-- |The home directory. If you want to set it explicitly, you might
|
||||
@ -63,5 +63,5 @@ terminalCommand cwd =
|
||||
-- home = return "\/home\/wurst"
|
||||
-- @
|
||||
home :: IO ByteString
|
||||
home = fromMaybe <$> return "/" <*> getEnv "HOME"
|
||||
home = fromMaybe <$> return (BU.fromString "/") <*> getEnv (BU.fromString "HOME")
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user