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.
|
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
|
||||||
--}
|
--}
|
||||||
|
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
|
||||||
{-# OPTIONS_HADDOCK ignore-exports #-}
|
{-# 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.
|
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
|
||||||
--}
|
--}
|
||||||
|
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
|
||||||
{-# OPTIONS_HADDOCK ignore-exports #-}
|
{-# OPTIONS_HADDOCK ignore-exports #-}
|
||||||
|
|
||||||
|
|
||||||
@ -67,7 +66,7 @@ instance GlibString BS.ByteString where
|
|||||||
newUTFStringLen = newUTFStringLen . toString
|
newUTFStringLen = newUTFStringLen . toString
|
||||||
genUTFOfs = genUTFOfs . toString
|
genUTFOfs = genUTFOfs . toString
|
||||||
stringLength = BS.length
|
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
|
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.
|
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
|
||||||
--}
|
--}
|
||||||
|
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
|
||||||
{-# OPTIONS_HADDOCK ignore-exports #-}
|
{-# OPTIONS_HADDOCK ignore-exports #-}
|
||||||
|
|
||||||
module Main where
|
module Main where
|
||||||
|
|
||||||
|
|
||||||
|
import qualified Data.ByteString as BS
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
(
|
(
|
||||||
fromJust
|
fromJust
|
||||||
, fromMaybe
|
, fromMaybe
|
||||||
)
|
)
|
||||||
|
import Data.Word8
|
||||||
import Graphics.UI.Gtk
|
import Graphics.UI.Gtk
|
||||||
import qualified HPath as P
|
import qualified HPath as P
|
||||||
import HSFM.FileSystem.FileType
|
import HSFM.FileSystem.FileType
|
||||||
@ -45,15 +46,17 @@ import System.IO.Error
|
|||||||
)
|
)
|
||||||
import qualified System.Posix.Env.ByteString as SPE
|
import qualified System.Posix.Env.ByteString as SPE
|
||||||
|
|
||||||
|
slash :: BS.ByteString
|
||||||
|
slash = BS.singleton _slash
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
args <- SPE.getArgs
|
args <- SPE.getArgs
|
||||||
let mdir = fromMaybe (fromJust $ P.parseAbs "/")
|
let mdir = fromMaybe (fromJust $ P.parseAbs slash)
|
||||||
(P.parseAbs . headDef "/" $ args)
|
(P.parseAbs . headDef slash $ args)
|
||||||
|
|
||||||
file <- catchIOError (pathToFile getFileInfo mdir) $
|
file <- catchIOError (pathToFile getFileInfo mdir) $
|
||||||
\_ -> pathToFile getFileInfo . fromJust $ P.parseAbs "/"
|
\_ -> pathToFile getFileInfo . fromJust $ P.parseAbs slash
|
||||||
|
|
||||||
_ <- initGUI
|
_ <- initGUI
|
||||||
mygui <- createMyGUI
|
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.
|
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
|
||||||
--}
|
--}
|
||||||
|
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
|
||||||
{-# LANGUAGE TupleSections #-}
|
{-# LANGUAGE TupleSections #-}
|
||||||
{-# OPTIONS_HADDOCK ignore-exports #-}
|
{-# 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.
|
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
|
||||||
--}
|
--}
|
||||||
|
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
{-# OPTIONS_HADDOCK ignore-exports #-}
|
{-# OPTIONS_HADDOCK ignore-exports #-}
|
||||||
|
|
||||||
|
@ -254,9 +254,9 @@ withErrorDialog io =
|
|||||||
|
|
||||||
-- |Asks the user which directory copy mode he wants via dialog popup
|
-- |Asks the user which directory copy mode he wants via dialog popup
|
||||||
-- and returns 'DirCopyMode'.
|
-- and returns 'DirCopyMode'.
|
||||||
textInputDialog :: GlibString string
|
textInputDialog :: (GlibString s1, GlibString s2)
|
||||||
=> string -- ^ window title
|
=> s1 -- ^ window title
|
||||||
-> string -- ^ initial text in input widget
|
-> s2 -- ^ initial text in input widget
|
||||||
-> IO (Maybe String)
|
-> IO (Maybe String)
|
||||||
textInputDialog title inittext = do
|
textInputDialog title inittext = do
|
||||||
chooserDialog <- messageDialogNew Nothing
|
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.
|
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
|
||||||
--}
|
--}
|
||||||
|
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
|
||||||
{-# OPTIONS_HADDOCK ignore-exports #-}
|
{-# OPTIONS_HADDOCK ignore-exports #-}
|
||||||
|
|
||||||
|
|
||||||
@ -27,6 +26,7 @@ import Data.ByteString
|
|||||||
(
|
(
|
||||||
ByteString
|
ByteString
|
||||||
)
|
)
|
||||||
|
import qualified Data.ByteString.UTF8 as BU
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import System.Posix.Env.ByteString
|
import System.Posix.Env.ByteString
|
||||||
import System.Posix.Process.ByteString
|
import System.Posix.Process.ByteString
|
||||||
@ -50,9 +50,9 @@ terminalCommand :: ByteString -- ^ current directory of the FM
|
|||||||
-> IO a
|
-> IO a
|
||||||
terminalCommand cwd =
|
terminalCommand cwd =
|
||||||
executeFile -- executes the given command
|
executeFile -- executes the given command
|
||||||
"sakura" -- the terminal command
|
(BU.fromString "sakura") -- the terminal command
|
||||||
True -- whether to search PATH
|
True -- whether to search PATH
|
||||||
["-d", cwd] -- arguments for the command
|
[BU.fromString "-d", cwd] -- arguments for the command
|
||||||
Nothing -- optional custom environment: `Just [(String, String)]`
|
Nothing -- optional custom environment: `Just [(String, String)]`
|
||||||
|
|
||||||
|
|
||||||
@ -63,5 +63,5 @@ terminalCommand cwd =
|
|||||||
-- home = return "\/home\/wurst"
|
-- home = return "\/home\/wurst"
|
||||||
-- @
|
-- @
|
||||||
home :: IO ByteString
|
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