Re: [Haskell-cafe] How to get a file path to the program invoked?

Balazs, thanks for your comments!
The first comment works just fine.
With > operator I get this:
Main System.Environment.Executable System.FilePath> "/abc" > "/"
"/"
Instead of getting "/abc/" I get "/". What am I doing wrong?
On Mon, Dec 5, 2011 at 6:03 PM, Balazs Komuves
Two small comments:
1) This should work on Windows too, if you just leave out the word "Posix" from the source: import System.FilePath (splitFileName)
2) In general when dealing with paths, use the > operator (from System.FilePath) instead of ++ "/" ++
Balazs
On Mon, Dec 5, 2011 at 1:44 PM, dokondr
wrote: This is how I finally solved this problem for POSIX complaint system:
-- -- TestRun -- module Main where import System.Cmd (rawSystem) import System.Directory (getCurrentDirectory) import System.Environment.Executable (ScriptPath(..), getScriptPath) import System.FilePath.Posix (splitFileName)
main = do
path <- getMyPath putStrLn $ "myPath = " ++ path let cmdLine = path ++ "args.sh" rawSystem cmdLine ["iphone", "test-twitts.txt"]
{-- data ScriptPath Source
Constructors: Executable FilePath it was (probably) a proper compiled executable RunGHC FilePath it was a script run by runghc/runhaskell Interactive we are in GHCi --}
getMyPath = do curDir <- getCurrentDirectory -- from System.Directory scriptPath <- getScriptPath -- from System.Environment.Executable let path = getMyPath' scriptPath curDir return path
getMyPath' (Executable path) _ = fst (splitFileName path) getMyPath' (RunGHC path) _ = fst (splitFileName path) getMyPath' Interactive curDir = curDir++"/"

Hi.
On 5 December 2011 14:53, dokondr
Main System.Environment.Executable System.FilePath> "/abc" > "/" "/"
Instead of getting "/abc/" I get "/". What am I doing wrong?
It thinks the second path is an absolute path. "Combine two paths, if the second path isAbsolute, then it returns the second." http://hackage.haskell.org/packages/archive/filepath/latest/doc/html/System-... HTH, Ozgur

On Monday 05 December 2011, 15:53:35, dokondr wrote:
Balazs, thanks for your comments! The first comment works just fine. With > operator I get this:
Main System.Environment.Executable System.FilePath> "/abc" > "/" "/"
Instead of getting "/abc/" I get "/". What am I doing wrong?
The second path is absolute. > is an alias for combine, the docs for that say: "Combine two paths, if the second path isAbsolute, then it returns the second."

The operator > is an alias for `combine`, which the documentation says:
Combine two paths, if the second path isAbsolute, then it returns the second.
In this case, "/" is absolute, so it is returned.
If you wish to add a trailing path separator, use `addTrailingPathSeparator`.
Erik
On Mon, Dec 5, 2011 at 15:53, dokondr
Balazs, thanks for your comments! The first comment works just fine. With > operator I get this:
Main System.Environment.Executable System.FilePath> "/abc" > "/" "/"
Instead of getting "/abc/" I get "/". What am I doing wrong?
On Mon, Dec 5, 2011 at 6:03 PM, Balazs Komuves
wrote: Two small comments:
1) This should work on Windows too, if you just leave out the word "Posix" from the source: import System.FilePath (splitFileName)
2) In general when dealing with paths, use the > operator (from System.FilePath) instead of ++ "/" ++
Balazs
On Mon, Dec 5, 2011 at 1:44 PM, dokondr
wrote: This is how I finally solved this problem for POSIX complaint system:
-- -- TestRun -- module Main where import System.Cmd (rawSystem) import System.Directory (getCurrentDirectory) import System.Environment.Executable (ScriptPath(..), getScriptPath) import System.FilePath.Posix (splitFileName)
main = do
path <- getMyPath putStrLn $ "myPath = " ++ path let cmdLine = path ++ "args.sh" rawSystem cmdLine ["iphone", "test-twitts.txt"]
{-- data ScriptPath Source
Constructors: Executable FilePath it was (probably) a proper compiled executable RunGHC FilePath it was a script run by runghc/runhaskell Interactive we are in GHCi --}
getMyPath = do curDir <- getCurrentDirectory -- from System.Directory scriptPath <- getScriptPath -- from System.Environment.Executable let path = getMyPath' scriptPath curDir return path
getMyPath' (Executable path) _ = fst (splitFileName path) getMyPath' (RunGHC path) _ = fst (splitFileName path) getMyPath' Interactive curDir = curDir++"/"
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thanks,
'addTrailingPathSeparator' works just fine !
On Mon, Dec 5, 2011 at 7:52 PM, Erik Hesselink
The operator > is an alias for `combine`, which the documentation says:
Combine two paths, if the second path isAbsolute, then it returns the second.
In this case, "/" is absolute, so it is returned.
If you wish to add a trailing path separator, use `addTrailingPathSeparator`.
Erik
On Mon, Dec 5, 2011 at 15:53, dokondr
wrote: Balazs, thanks for your comments! The first comment works just fine. With > operator I get this:
Main System.Environment.Executable System.FilePath> "/abc" > "/" "/"
Instead of getting "/abc/" I get "/". What am I doing wrong?
On Mon, Dec 5, 2011 at 6:03 PM, Balazs Komuves
wrote: Two small comments:
1) This should work on Windows too, if you just leave out the word
"Posix"
from the source: import System.FilePath (splitFileName)
2) In general when dealing with paths, use the > operator (from System.FilePath) instead of ++ "/" ++
Balazs
On Mon, Dec 5, 2011 at 1:44 PM, dokondr
wrote: This is how I finally solved this problem for POSIX complaint system:
-- -- TestRun -- module Main where import System.Cmd (rawSystem) import System.Directory (getCurrentDirectory) import System.Environment.Executable (ScriptPath(..), getScriptPath) import System.FilePath.Posix (splitFileName)
main = do
path <- getMyPath putStrLn $ "myPath = " ++ path let cmdLine = path ++ "args.sh" rawSystem cmdLine ["iphone", "test-twitts.txt"]
{-- data ScriptPath Source
Constructors: Executable FilePath it was (probably) a proper compiled executable RunGHC FilePath it was a script run by runghc/runhaskell Interactive we are in GHCi --}
getMyPath = do curDir <- getCurrentDirectory -- from System.Directory scriptPath <- getScriptPath -- from System.Environment.Executable let path = getMyPath' scriptPath curDir return path
getMyPath' (Executable path) _ = fst (splitFileName path) getMyPath' (RunGHC path) _ = fst (splitFileName path) getMyPath' Interactive curDir = curDir++"/"
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (4)
-
Daniel Fischer
-
dokondr
-
Erik Hesselink
-
Ozgur Akgun