| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
System.Win32.Shortcut
Description
Working with .lnk format should be a matter of serializing.
This library takes simpler approach, utilizing Component Object Model
(COM) library. Even though COM provides some means of serialization,
they cannot be used in a pure fashion - the library needs
to be initialized and some COM functions still query the
system for data. For this reason this library sticks to IO.
Before calling writeShortcut or readShortcut, COM library
must be initialized with initialize.
Library does not support shortcut's IDLists, so creating or
reading links to devices or network connections is not possible.
Example
import Control.Monad.Except
main = print . runExceptT $ do
let link = empty { targetPath = "notepad.exe" }
ExceptT initialize
ExceptT $ writeShortcut link "c:\\link.lnk"
ret <- ExceptT $ readShortcut "c:\\link.lnk"
liftIO $ uninitialize
return ret
>>> main
Right (Shortcut {targetPath = "C:\\Windows\\system32\\notepad.exe",
arguments = "", workingDirectory = "", showCmd = ShowNormal,
description = "", iconLocation = ("",0), hotkey = 0})
- data Shortcut = Shortcut {
- targetPath :: FilePath
- arguments :: String
- workingDirectory :: FilePath
- showCmd :: ShowCmd
- description :: String
- iconLocation :: (FilePath, Int)
- hotkey :: WORD
- empty :: Shortcut
- data ShowCmd
- writeShortcut :: Shortcut -> FilePath -> IO (Either ShortcutError ())
- unsafeWriteShortcut :: Shortcut -> FilePath -> IO (Either ShortcutError ())
- readShortcut :: FilePath -> IO (Either ShortcutError Shortcut)
- initialize :: IO (Either ShortcutError ())
- uninitialize :: IO ()
- data ShortcutError
- = InitializationError (OrHRESULTError CoInitializeError)
- | CreateIShellLinkInterfaceError (OrHRESULTError CoCreateInstanceError)
- | CreateIPersistFileInterfaceError (OrHRESULTError CoCreateInstanceError)
- | LoadError (OrHRESULTError LoadError)
- | SaveError (OrHRESULTError SaveError)
- | InvalidPath (OrHRESULTError PathError)
- | InvalidArguments (OrHRESULTError ArgumentsError)
- | InvalidWorkingDirectory (OrHRESULTError WorkingDirectoryError)
- | InvalidDescription (OrHRESULTError DescriptionError)
- | InvalidIconLocation (OrHRESULTError IconLocationError)
- | InvalidHotkey HRESULTError
- | InvalidShowCmd HRESULTError
- data LoadError
- data SaveError = SE_S_FALSE
- data PathError
- data ArgumentsError = ArgumentsTooLong
- data WorkingDirectoryError = WorkingDirectoryTooLong
- data DescriptionError = DescriptionTooLong
- data IconLocationError = IconLocationTooLong
- data CoCreateInstanceError
- data CoInitializeError
- data HRESULTError
- data OrHRESULTError err
- = OtherError err
- | HRESULTError HRESULTError
Documentation
A shell link.
It seems that .lnk format permits up to 32767
characters in text fields (259 for targetPath), however
if workingDirectory, description or iconLocation is
longer then 259 characters COM won't be able to read the
shortcut corectly (readShortcut will return faulty link without
raising any error, and explorer.exe may not interpret it properly).
For this reason two write functions are provided. unsafeWriteShortcut
will allow long fields and writeShortcut which will raise
error if workingDirectory, description or iconLocation
is longer then 259 characters.
Constructors
| Shortcut | |
Fields
| |
Defines how a window will be opened when a link is executed.
Constructors
| ShowNormal | Start normally. |
| ShowMaximized | Start maximized. |
| ShowMinimized | Start minimized. |
Basic operations
writeShortcut :: Shortcut -> FilePath -> IO (Either ShortcutError ()) Source #
Create a shortcut under specified location. initialize must be
called beforehand. targetPath will be resolved with
respect to whatever is found in PATH variable or desktop
if saved path is not absolute.
unsafeWriteShortcut :: Shortcut -> FilePath -> IO (Either ShortcutError ()) Source #
Same as writeShortcut, but allows long description,
workingDirectory and iconLocation fields. COM and explorer.exe
may not interpret created link correctly.
readShortcut :: FilePath -> IO (Either ShortcutError Shortcut) Source #
Read a shortcut from the supplied location. initialize must be
called beforehand.
COM initialization
initialize :: IO (Either ShortcutError ()) Source #
Initialize COM library for current thread.
Wraps CoInitializeEx
function.
uninitialize :: IO () Source #
Uninitialize COM library for current thread.
Errors
data ShortcutError Source #
Catch-all type for errors.
Constructors
Instances
File IO Errors
IPersistFile interface failed to load a file.
Constructors
| LE_E_OUTOFMEMORY | The object could not be loaded due to a lack of memory. |
| LE_E_FAIL | The object could not be loaded for some reason other than a lack of memory. |
IPersistFile interface failed to save a file.
Constructors
| SE_S_FALSE | The object was not successfully saved. |
Argument errors
Constructors
| Path_S_FALSE | The operation is successful but no path is retrieved. |
| PathTooLong | Path length >= 260 characters. |
data ArgumentsError Source #
Constructors
| ArgumentsTooLong | Arguments length >= 32768 characters. |
Instances
Other errors
data CoCreateInstanceError Source #
COM cannot create specified interface.
Constructors
| CCI_REGDB_E_CLASSNOTREG | A specified class is not registered in the registration database. Also can indicate that the type of server you requested in the CLSCTX enumeration is not registered or the values for the server types in the registry are corrupt. |
| CCI_CLASS_E_NOAGGREGATION | This class cannot be created as part of an aggregate. |
| CCI_E_NOINTERFACE | The specified class does not implement the requested interface, or the controlling IUnknown does not expose the requested interface. |
| CCI_E_POINTER | The ppv parameter is NULL. |
| CCI_CO_E_NOTINITIALIZED |
|
Instances
data CoInitializeError Source #
COM failed to initialize.
Constructors
| CI_RPC_E_CHANGED_MODE | A previous call to CoInitializeEx specified the concurrency model for this thread as multithread apartment (MTA). This could also indicate that a change from neutral-threaded apartment to single-threaded apartment has occurred. |
| CI_CO_E_NOTINITIALIZED | You need to initialize the |
Instances
data HRESULTError Source #
In Win32 API HRESULT is used to indicate error and warning
conditions. HRESULTError wraps HRESULT to give it some meaning.
Constructors
| E_ABORT | Operation aborted. |
| E_ACCESSDENIED | General access denied error. |
| E_FAIL | Unspecified failure. |
| E_HANDLE | Handle that is not valid. |
| E_INVALIDARG | One or more arguments are not valid. |
| E_NOINTERFACE | No such interface supported. |
| E_NOTIMPL | Not implemented. |
| E_OUTOFMEMORY | Failed to allocate necessary memory. |
| E_POINTER | Pointer that is not valid. |
| E_UNEXPECTED | Unexpected failure. |
| HRESULTUnknown HRESULT | Other, unknown |
Instances
data OrHRESULTError err Source #
Some error that comes from HRESULT.
Constructors
| OtherError err |
|
| HRESULTError HRESULTError |
|
Instances
| Show err => Show (OrHRESULTError err) Source # | |