{- |

The documentation of "System.Environment.getProgName" says that

\"However, this is hard-to-impossible to implement on some non-Unix OSes, 
so instead, for maximum portability, we just return the leafname 
of the program as invoked. Even then there are some differences 
between platforms: on Windows, for example, a program invoked as 
foo is probably really FOO.EXE, and that is what "getProgName" will 
return.\"

This library tries to fix this issue.
It also provides some platform-specific functions (most notably getting
the path of the application bundle on OSX). Supported operating
systems:
 
 * Win32 (tested on Windows XP \/ x86 only)
 
 * Mac OS X (tested on Leopard \/ x86 only)
 
 * Linux

 * FreeBSD (tested on FreeBSD 6.4)

 * \*BSD (untested)
 
 * Solaris (untested, and probably works on Solaris 10 only) 
 
-}

{-# LANGUAGE CPP #-}

module System.Environment.Executable
  ( getExecutablePath 
  , splitExecutablePath

#ifdef mingw32_HOST_OS 
  , getModulePath
#endif
 
#ifdef darwin_HOST_OS 
  , getApplicationBundlePath
#endif
  
  )
  where

import Control.Monad (liftM)
import System.FilePath (splitFileName)

--------------------------------------------------------------------------------

#ifdef mingw32_HOST_OS
#define SUPPORTED_OS
import System.Environment.Executable.Win32
#endif

#ifdef darwin_HOST_OS
#define SUPPORTED_OS
import System.Environment.Executable.MacOSX
#endif

#ifdef linux_HOST_OS
#define SUPPORTED_OS
import System.Environment.Executable.Linux
#endif

#ifdef freebsd_HOST_OS
#define SUPPORTED_OS
import System.Environment.Executable.FreeBSD
#endif

#ifdef netbsd_HOST_OS
#define SUPPORTED_OS
import System.Environment.Executable.BSD
#endif

#ifdef openbsd_HOST_OS
#define SUPPORTED_OS
import System.Environment.Executable.BSD
#endif

#ifdef solaris_HOST_OS
#define SUPPORTED_OS
import System.Environment.Executable.Solaris
#endif

--------------------------------------------------------------------------------

splitExecutablePath :: IO (FilePath,FilePath)
splitExecutablePath = liftM splitFileName getExecutablePath

--------------------------------------------------------------------------------

#ifndef SUPPORTED_OS
{-# WARNING getExecutablePath "the host OS is not supported!" #-}
getExecutablePath :: IO String
getExecutablePath = error "host OS not supported"
#endif

--------------------------------------------------------------------------------