nsis-0.3.3: DSL for producing Windows Installer using NSIS.

Safe HaskellNone
LanguageHaskell2010

Development.NSIS

Contents

Description

NSIS (Nullsoft Scriptable Install System, http://nsis.sourceforge.net/) is a tool that allows programmers to create installers for Windows. This library provides an alternative syntax for NSIS scripts, as an embedded Haskell language, removing much of the hard work in developing an install script. Simple NSIS installers should look mostly the same, complex ones should be significantly more maintainable.

As a simple example of using this library:

import Development.NSIS

main = writeFile "example1.nsi" $ nsis $ do
     name "Example1"                  -- The name of the installer
     outFile "example1.exe"           -- Where to produce the installer
     installDir "$DESKTOP/Example1"   -- The default installation directory
     requestExecutionLevel User       -- Request application privileges for Windows Vista
     -- Pages to display
     page Directory                   -- Pick where to install
     page InstFiles                   -- Give a progress bar while installing
     -- Groups fo files to install
     section "" [] $ do
         setOutPath "$INSTDIR"        -- Where to install files in this section
         file [] "Example1.hs"        -- File to put into this section
 

The file example1.nsi can now be processed with makensis to produce the installer example1.exe. For more examples, see the Examples source directory.

Much of the documentation from the Installer section is taken from the NSIS documentation.

Synopsis

Core types

nsis :: Action a -> String Source #

Create the contents of an NSIS script from an installer specification.

Beware, unsafeInject and unsafeInjectGlobal may break nsis. The optimizer relies on invariants that may not hold when arbitrary lines are injected. Consider using nsisNoOptimise if problems arise.

nsisNoOptimise :: Action a -> String Source #

Like nsis, but don't try and optimise the resulting NSIS script.

Useful to figure out how the underlying installer works, or if you believe the optimisations are introducing bugs. Please do report any such bugs, especially if you aren't using unsafeInject or unsafeInjectGlobal!

data Action a Source #

Monad in which installers are defined. A useful command to start with is section.

Instances
Monad Action Source # 
Instance details

Defined in Development.NSIS.Sugar

Methods

(>>=) :: Action a -> (a -> Action b) -> Action b #

(>>) :: Action a -> Action b -> Action b #

return :: a -> Action a #

fail :: String -> Action a #

Functor Action Source # 
Instance details

Defined in Development.NSIS.Sugar

Methods

fmap :: (a -> b) -> Action a -> Action b #

(<$) :: a -> Action b -> Action a #

Applicative Action Source # 
Instance details

Defined in Development.NSIS.Sugar

Methods

pure :: a -> Action a #

(<*>) :: Action (a -> b) -> Action a -> Action b #

liftA2 :: (a -> b -> c) -> Action a -> Action b -> Action c #

(*>) :: Action a -> Action b -> Action b #

(<*) :: Action a -> Action b -> Action a #

Enum (Exp Int) Source # 
Instance details

Defined in Development.NSIS.Sugar

Eq (Exp a) Source # 
Instance details

Defined in Development.NSIS.Sugar

Methods

(==) :: Exp a -> Exp a -> Bool #

(/=) :: Exp a -> Exp a -> Bool #

Fractional (Exp Int) Source # 
Instance details

Defined in Development.NSIS.Sugar

Integral (Exp Int) Source # 
Instance details

Defined in Development.NSIS.Sugar

Methods

quot :: Exp Int -> Exp Int -> Exp Int #

rem :: Exp Int -> Exp Int -> Exp Int #

div :: Exp Int -> Exp Int -> Exp Int #

mod :: Exp Int -> Exp Int -> Exp Int #

quotRem :: Exp Int -> Exp Int -> (Exp Int, Exp Int) #

divMod :: Exp Int -> Exp Int -> (Exp Int, Exp Int) #

toInteger :: Exp Int -> Integer #

Num (Exp Int) Source # 
Instance details

Defined in Development.NSIS.Sugar

Methods

(+) :: Exp Int -> Exp Int -> Exp Int #

(-) :: Exp Int -> Exp Int -> Exp Int #

(*) :: Exp Int -> Exp Int -> Exp Int #

negate :: Exp Int -> Exp Int #

abs :: Exp Int -> Exp Int #

signum :: Exp Int -> Exp Int #

fromInteger :: Integer -> Exp Int #

Ord (Exp Int) Source # 
Instance details

Defined in Development.NSIS.Sugar

Methods

compare :: Exp Int -> Exp Int -> Ordering #

(<) :: Exp Int -> Exp Int -> Bool #

(<=) :: Exp Int -> Exp Int -> Bool #

(>) :: Exp Int -> Exp Int -> Bool #

(>=) :: Exp Int -> Exp Int -> Bool #

max :: Exp Int -> Exp Int -> Exp Int #

min :: Exp Int -> Exp Int -> Exp Int #

Real (Exp Int) Source # 
Instance details

Defined in Development.NSIS.Sugar

Methods

toRational :: Exp Int -> Rational #

Show (Exp a) Source # 
Instance details

Defined in Development.NSIS.Sugar

Methods

showsPrec :: Int -> Exp a -> ShowS #

show :: Exp a -> String #

showList :: [Exp a] -> ShowS #

Typeable a => IsString (Exp a) Source # 
Instance details

Defined in Development.NSIS.Sugar

Methods

fromString :: String -> Exp a #

Semigroup (Exp String) Source # 
Instance details

Defined in Development.NSIS.Sugar

Monoid (Exp String) Source # 
Instance details

Defined in Development.NSIS.Sugar

Bits (Exp Int) Source # 
Instance details

Defined in Development.NSIS.Sugar

type Exp ty = Action (Value ty) Source #

The type of expressions - namely an Action producing a Value. There are instances for Num and IsString, and turning on {-# LANGUAGE OverloadedStrings #-} is strongly recommended.

The fromString function converts any embedded $VAR into a variable lookup, which may refer to one of the builtin NSIS variables (e.g. $SMPROGRAMS, $TEMP, $PROGRAMFILES), or a named variable created with constant or mutable. The string $$ is used to escape $ values. Bracket the variables to put text characters afterwards (e.g. $(SMPROGRAMS)XXX). In contrast to standard strings, / is treated as \ and // is treated as /. Remember to escape any slashes occuring in URLs.

If the string is Exp String then any Int variables used will be automatically shown (see strShow). If the string is Exp ty then it must be of the form "$VAR" where $VAR is a variable of type ty.

The Eq and Ord instances for Exp throw errors for all comparisons (use %==, %<= etc), but min and max are defined. The Num (arithmetic) and Monoid (string concatenation) instances are both fully implemented. From Integral and Fractional, only /, mod and div are implemented, and all as integer arithmetic. No functions from Enum or Real are implemented.

When using a single expression multiple times, to ensure it is not evaluated repeatedly, use share.

data Value ty Source #

A Value, only used by Exp, which can be produced using return. The ty argument should be one of String, Int or Bool.

Instances
Enum (Exp Int) Source # 
Instance details

Defined in Development.NSIS.Sugar

Eq (Exp a) Source # 
Instance details

Defined in Development.NSIS.Sugar

Methods

(==) :: Exp a -> Exp a -> Bool #

(/=) :: Exp a -> Exp a -> Bool #

Fractional (Exp Int) Source # 
Instance details

Defined in Development.NSIS.Sugar

Integral (Exp Int) Source # 
Instance details

Defined in Development.NSIS.Sugar

Methods

quot :: Exp Int -> Exp Int -> Exp Int #

rem :: Exp Int -> Exp Int -> Exp Int #

div :: Exp Int -> Exp Int -> Exp Int #

mod :: Exp Int -> Exp Int -> Exp Int #

quotRem :: Exp Int -> Exp Int -> (Exp Int, Exp Int) #

divMod :: Exp Int -> Exp Int -> (Exp Int, Exp Int) #

toInteger :: Exp Int -> Integer #

Num (Exp Int) Source # 
Instance details

Defined in Development.NSIS.Sugar

Methods

(+) :: Exp Int -> Exp Int -> Exp Int #

(-) :: Exp Int -> Exp Int -> Exp Int #

(*) :: Exp Int -> Exp Int -> Exp Int #

negate :: Exp Int -> Exp Int #

abs :: Exp Int -> Exp Int #

signum :: Exp Int -> Exp Int #

fromInteger :: Integer -> Exp Int #

Ord (Exp Int) Source # 
Instance details

Defined in Development.NSIS.Sugar

Methods

compare :: Exp Int -> Exp Int -> Ordering #

(<) :: Exp Int -> Exp Int -> Bool #

(<=) :: Exp Int -> Exp Int -> Bool #

(>) :: Exp Int -> Exp Int -> Bool #

(>=) :: Exp Int -> Exp Int -> Bool #

max :: Exp Int -> Exp Int -> Exp Int #

min :: Exp Int -> Exp Int -> Exp Int #

Real (Exp Int) Source # 
Instance details

Defined in Development.NSIS.Sugar

Methods

toRational :: Exp Int -> Rational #

Show (Exp a) Source # 
Instance details

Defined in Development.NSIS.Sugar

Methods

showsPrec :: Int -> Exp a -> ShowS #

show :: Exp a -> String #

showList :: [Exp a] -> ShowS #

Typeable a => IsString (Exp a) Source # 
Instance details

Defined in Development.NSIS.Sugar

Methods

fromString :: String -> Exp a #

Semigroup (Exp String) Source # 
Instance details

Defined in Development.NSIS.Sugar

Monoid (Exp String) Source # 
Instance details

Defined in Development.NSIS.Sugar

Bits (Exp Int) Source # 
Instance details

Defined in Development.NSIS.Sugar

Scripting

Variables

share :: Exp t -> (Exp t -> Action a) -> Action a Source #

The Exp language is call-by-name, meaning you must use share to avoid evaluating an exression multiple times. Using share, if the expression has any side effects they will be run immediately, but not on subsequent uses. When defining functions operating on Exp, if you use the same input expression twice, you should share it. For example:

strPalindrom x = share x $ \x -> x %== strReverse x

If the expression was not shared, and x read from a file, then the file would be read twice.

scope :: Action a -> Action a Source #

Introduce a variable scope. Scopes are automatically introduced by operations such as iff, loop, while etc. Inside a scope you may define new variables whose names may clash with variables outside the scope, but the local versions will be used.

If you have any non-evaluated expressions, before introducing any potentially clashing variables in the scope you should share them or use constant_ on them. For example:

operate x = do
    x <- constant_ x
    scope $ do
        constant "TEST" 0

It is important to turn x into a constant_ before defining a new constant $TEST, since if x refers to $TEST after the new definition, it will pick up the wrong variable.

constant :: Typeable t => String -> Exp t -> Action (Exp t) Source #

Create a constant with a name, ensuring the expression is shared. After defining the expression, you can refer to it with $NAME in a String. To introduce a new scope, see scope.

constant "HELLO" "Hello World"
alert "$HELLO!"

constant_ :: Exp t -> Action (Exp t) Source #

Create a constant with no name, ensuring the expression is shared. Equivalent to share return.

mutable :: Typeable t => String -> Exp t -> Action (Exp t) Source #

Create a mutable variable a name, which can be modified with @=. After defining the expression, you can refer to it with $NAME in a String. To introduce a new scope, see scope.

h <- mutable "HELLO" "Hello World"
"$HELLO" @= "$HELLO!"
h        @= "$HELLO!" -- equivalent to the above
alert "$HELLO"        -- with 2 exclamation marks

mutable_ :: Exp t -> Action (Exp t) Source #

Create an unnamed mutable variable, which can be modified with @=.

h <- mutable "Hello World"
h @= h & "!"
alert h

(@=) :: Exp t -> Exp t -> Action () infix 1 Source #

Assign a value to a mutable variable. The variable must have been originally created with mutable or mutable_, or there will be an error when generating the install file.

Typed variables

mutableInt :: String -> Exp Int -> Action (Exp Int) Source #

Versions of mutable and constant restricted to Exp Int, used to avoid ambiguous type errors.

constantInt :: String -> Exp Int -> Action (Exp Int) Source #

Versions of mutable and constant restricted to Exp Int, used to avoid ambiguous type errors.

mutableInt_ :: Exp Int -> Action (Exp Int) Source #

Versions of mutable_ and constant_ restricted to Exp Int, used to avoid ambiguous type errors.

constantInt_ :: Exp Int -> Action (Exp Int) Source #

Versions of mutable_ and constant_ restricted to Exp Int, used to avoid ambiguous type errors.

mutableStr :: String -> Exp String -> Action (Exp String) Source #

Versions of mutable and constant restricted to Exp String, used to avoid ambiguous type errors.

constantStr :: String -> Exp String -> Action (Exp String) Source #

Versions of mutable and constant restricted to Exp String, used to avoid ambiguous type errors.

mutableStr_ :: Exp String -> Action (Exp String) Source #

Versions of mutable_ and constant_ restricted to Exp String, used to avoid ambiguous type errors.

constantStr_ :: Exp String -> Action (Exp String) Source #

Versions of mutable_ and constant_ restricted to Exp String, used to avoid ambiguous type errors.

Control Flow

iff :: Exp Bool -> Action () -> Action () -> Action () Source #

Test a boolean expression, reunning the first action if it is true and the second if it is false. The appropriate branch action will be run within a scope. See ? for an expression orientated version.

iff (x %== 12) (alert "is 12") (alert "is not 12")

iff_ :: Exp Bool -> Action () -> Action () Source #

A version of iff where there is no else action.

while :: Exp Bool -> Action () -> Action () Source #

A while loop, run the second argument while the first argument is true. The action is run in a scope. See also loop.

x <- mutable_ x
while (x %< 10) $ do
   x @= x + 1

loop :: (Action () -> Action ()) -> Action () Source #

A loop with a break command. Run the action repeatedly until the breaking action is called. The action is run in a scope. See also while.

x <- mutable_ x
loop $ \break -> do
    iff_ (x %>= 10) break
    x @= x + 1

onError :: Action () -> Action () -> Action () Source #

Run an intitial action, and if that action causes an error, run the second action. Unlike other programming languages, any uncaught errors are silently ignored. All actions are run in scope.

onError (exec "\"$WINDIR/notepad.exe\"") (alert "Failed to run notepad")

(?) :: Exp Bool -> (Exp t, Exp t) -> Exp t infix 2 Source #

An expression orientated version of iff, returns the first component if the first argument is true or the second if it is false.

x %== 12 ? (x, x + 5)

(%&&) :: Exp Bool -> Exp Bool -> Exp Bool infixr 3 Source #

Short circuiting boolean operators, equivalent to && and || but on Exp.

(%||) :: Exp Bool -> Exp Bool -> Exp Bool infixr 2 Source #

Short circuiting boolean operators, equivalent to && and || but on Exp.

data Label Source #

A code label, used for goto programming, see newLabel.

Instances
Eq Label Source # 
Instance details

Defined in Development.NSIS.Type

Methods

(==) :: Label -> Label -> Bool #

(/=) :: Label -> Label -> Bool #

Data Label Source # 
Instance details

Defined in Development.NSIS.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Label -> c Label #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Label #

toConstr :: Label -> Constr #

dataTypeOf :: Label -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Label) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Label) #

gmapT :: (forall b. Data b => b -> b) -> Label -> Label #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Label -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Label -> r #

gmapQ :: (forall d. Data d => d -> u) -> Label -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Label -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Label -> m Label #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Label -> m Label #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Label -> m Label #

Show Label Source # 
Instance details

Defined in Development.NSIS.Type

Methods

showsPrec :: Int -> Label -> ShowS #

show :: Label -> String #

showList :: [Label] -> ShowS #

newLabel :: Action Label Source #

Create a new label, used with goto and label to write line jump based programming. Where possible you should use structured alternatives, such as iff, while and loop. Each created label must be used with one call to label, and any number of calls to goto. As an example:

abort <- newLabel
while var $ do
    iff_ cond1 $ goto abort
    iff_ cond2 $ goto abort
    var @= strDrop 1 var
label abort

Note that the above example could have been written in a simpler manner with loop.

label :: Label -> Action () Source #

Define the location of a label, see newLabel for details. This function will fail if the same Label is passed to label more than once.

goto :: Label -> Action () Source #

Jump to a label, see newLabel for details. This function will fail if label is not used on the Label.

Expressions

str :: String -> Exp String Source #

Lift a String into an Exp

int :: Int -> Exp Int Source #

Lift an Int into an Exp

bool :: Bool -> Exp Bool Source #

Lift a Bool into an Exp

(%==) :: Exp a -> Exp a -> Exp Bool infix 4 Source #

The standard equality operators, lifted to Exp.

(%/=) :: Exp a -> Exp a -> Exp Bool infix 4 Source #

The standard equality operators, lifted to Exp.

(%<=) :: Exp Int -> Exp Int -> Exp Bool infix 4 Source #

The standard comparison operators, lifted to Exp.

(%<) :: Exp Int -> Exp Int -> Exp Bool infix 4 Source #

The standard comparison operators, lifted to Exp.

(%>=) :: Exp Int -> Exp Int -> Exp Bool infix 4 Source #

The standard comparison operators, lifted to Exp.

(%>) :: Exp Int -> Exp Int -> Exp Bool infix 4 Source #

The standard comparison operators, lifted to Exp.

true :: Exp Bool Source #

Boolean constants corresponding to True and False

false :: Exp Bool Source #

Boolean constants corresponding to True and False

not_ :: Exp Bool -> Exp Bool Source #

Boolean negation.

strRead :: Exp String -> Exp Int Source #

Convert a String to an Int, any errors are silently ignored.

strShow :: Exp Int -> Exp String Source #

Convert an Int to a String by showing it.

(&) :: Exp String -> Exp String -> Exp String infixr 5 Source #

Concatenate two strings, for example "$FOO" & "$BAR" is equivalent to "$FOO$BAR".

strConcat :: [Exp String] -> Exp String Source #

Perform string concatenation on a list of expressions.

strLength :: Exp String -> Exp Int Source #

Return the length of a string, strLength "test" %== 4.

strTake :: Exp Int -> Exp String -> Exp String Source #

Take the first n characters from a string, strTake 2 "test" %== "te".

strDrop :: Exp Int -> Exp String -> Exp String Source #

Drop the first n characters from a string, strDrop 2 "test" %== "st".

strReplace :: Exp String -> Exp String -> Exp String -> Exp String Source #

Replace one string with another string, in a target string. As some examples:

strReplace "t" "XX" "test" %== "XXesXX"
strReplace "ell" "" "hello world" %== "ho world"

strIsPrefixOf :: Exp String -> Exp String -> Exp Bool Source #

Is the first string a prefix of the second.

strIsSuffixOf :: Exp String -> Exp String -> Exp Bool Source #

Is the first string a prefix of the second.

strUnlines :: [Exp String] -> Exp String Source #

Join together a list of strings with \r\n after each line. Note that unlike standard unlines, we use the Windows convention line separator.

strCheck :: Exp String -> Exp String -> Exp String Source #

NSIS (the underlying installer, not this library) uses fixed length string buffers, defaulting to 1024 bytes. Any strings longer than the limit may cause truncation or segfaults. You can get builds supporting longer strings from http://nsis.sourceforge.net/Special_Builds.

Given strCheck msg val, if val exceeds the limit it will abort with msg, otherwise it will return val.

File system manipulation

data FileHandle Source #

The type of a file handle, created by fileOpen.

fileOpen :: FileMode -> Exp FilePath -> Action (Exp FileHandle) Source #

Open a file, which must be closed explicitly with fileClose. Often it is better to use writeFile' or withFile instead.

h <- fileOpen ModeWrite "C:/log.txt"
fileWrite h "Hello world!"
fileClose h

fileWrite :: Exp FileHandle -> Exp String -> Action () Source #

Write a string to a file openned with fileOpen.

fileClose :: Exp FileHandle -> Action () Source #

Close a file file openned with fileOpen.

withFile' :: FileMode -> Exp FilePath -> (Exp FileHandle -> Action ()) -> Action () Source #

With a fileOpen perform some action, then automatically call fileClose. If the action argument jumps out of the section then the fileClose call will be missed.

writeFile' :: Exp FilePath -> Exp String -> Action () Source #

Write a file, like writeFile.

writeFileLines :: Exp FilePath -> [Exp String] -> Action () Source #

Write a file comprising of a set of lines.

rmdir :: [Attrib] -> Exp FilePath -> Action () Source #

Remove the specified directory (fully qualified path with no wildcards). Without Recursive, the directory will only be removed if it is completely empty. If Recursive is specified, the directory will be removed recursively, so all directories and files in the specified directory will be removed. If RebootOK is specified, any file or directory which could not have been removed during the process will be removed on reboot -- if any file or directory will be removed on a reboot, the reboot flag will be set. The error flag is set if any file or directory cannot be removed.

rmdir [] "$INSTDIR"
rmdir [] "$INSTDIR/data"
rmdir [Recursive, RebootOK] "$INSTDIR"
rmdir [RebootOK] "$INSTDIR/DLLs"

Note that the current working directory can not be deleted. The current working directory is set by setOutPath. For example, the following example will not delete the directory.

setOutPath "$TEMP/dir"
rmdir [] "$TEMP/dir"

The next example will succeed in deleting the directory.

setOutPath "$TEMP/dir"
setOutPath "$TEMP"
rmdir [] "$TEMP/dir"

Warning: using rmdir [Recursive] "$INSTDIR" in uninstall is not safe. Though it is unlikely, the user might select to install to the Program Files folder and so this command will wipe out the entire Program Files folder, including other programs that has nothing to do with the uninstaller. The user can also put other files but the program's files and would expect them to get deleted with the program. Solutions are available for easily uninstalling only files which were installed by the installer.

delete :: [Attrib] -> Exp FilePath -> Action () Source #

Delete file (which can be a file or wildcard, but should be specified with a full path) from the target system. If RebootOK is specified and the file cannot be deleted then the file is deleted when the system reboots -- if the file will be deleted on a reboot, the reboot flag will be set. The error flag is set if files are found and cannot be deleted. The error flag is not set from trying to delete a file that does not exist.

delete [] "$INSTDIR/somefile.dat"

copyFiles :: [Attrib] -> Exp FilePath -> Exp FilePath -> Action () Source #

Both file paths are on the installing system. Do not use relative paths.

getFileTime :: Exp FilePath -> Exp String Source #

Gets the last write time of the file, you should only use the result to compare for equality with other results from getFileTime. On failure the error flag is set.

fileExists :: Exp FilePath -> Exp Bool Source #

Checks for existence of file(s) (which can be a wildcard, or a directory). If you want to check to see if a file is a directory, use fileExists "DIRECTORY/*.*".

iff_ (fileExists "$WINDIR/notepad.exe") $
    messageBox [MB_OK] "notepad is installed"

findEach :: Exp FilePath -> (Exp FilePath -> Action ()) -> Action () Source #

Performs a search for filespec, running the action with each file found. If no files are found the error flag is set. Note that the filename output is without path.

findEach "$INSTDIR/*.txt" $ \x ->
    detailPrint x

If you jump from inside the loop to after the loop then you may leak a search handle.

createDirectory :: Exp FilePath -> Action () Source #

Creates (recursively if necessary) the specified directory. Errors can be caught using onError. You should always specify an absolute path.

createDirectory "$INSTDIR/some/directory"

createShortcut :: Exp FilePath -> [Attrib] -> Action () Source #

Creates a shortcut file that links to a Traget file, with optional Parameters. The icon used for the shortcut is IconFile,IconIndex. StartOptions should be one of: SW_SHOWNORMAL, SW_SHOWMAXIMIZED, SW_SHOWMINIMIZED. KeyboardShortcut should be in the form of 'flag|c' where flag can be a combination (using |) of: ALT, CONTROL, EXT, or SHIFT. c is the character to use (a-z, A-Z, 0-9, F1-F24, etc). Note that no spaces are allowed in this string. A good example is "ALT|CONTROL|F8". $OUTDIR is used for the working directory. You can change it by using setOutPath before creating the Shortcut. Description should be the description of the shortcut, or comment as it is called under XP. The error flag is set if the shortcut cannot be created (i.e. either of the paths (link or target) does not exist, or some other error).

createDirectory "$SMPROGRAMS/My Company"
createShortcut "$SMPROGRAMS/My Company/My Program.lnk"
   [Target "$INSTDIR/My Program.exe"
   ,Parameters "some command line parameters"
   ,IconFile "$INSTDIR/My Program.exe", IconIndex 2
   ,StartOptions "SW_SHOWNORMAL"
   ,KeyboardShortcut "ALT|CONTROL|SHIFT|F5"
   ,Description "a description"]

Registry manipulation

Environment variables

Process execution

exec :: Exp String -> Action () Source #

Execute the specified program and continue immediately. Note that the file specified must exist on the target system, not the compiling system. $OUTDIR is used for the working directory. Errors can be caught using onError. Note, if the command could have spaces, you should put it in quotes to delimit it from parameters. e.g.: exec "\"$INSTDIR/command.exe\" parameters". If you don't put it in quotes it will not work on Windows 9x with or without parameters.

exec "\"$INSTDIR/someprogram.exe\""
exec "\"$INSTDIR/someprogram.exe\" some parameters"

sleep :: Exp Int -> Action () Source #

Sleep time in milliseconds

Windows

sendMessage :: [Attrib] -> HWND -> Exp Int -> Exp a -> Exp b -> Action (Exp Int) Source #

Plugins

plugin :: String -> String -> [Exp a] -> Action () Source #

Call a plugin. If the arguments are of different types use exp_. As an example:

encrypt x = share x $ \x -> do
    plugin "Base64" "Encrypt" [exp_ x, exp_ $ strLength x]

The only thing to be careful about is that we use the x parameter twice, so should share it to ensure it is only evaluated once.

push :: Exp a -> Action () Source #

Push a value onto the stack. Only useful with plugin.

pop :: Exp String Source #

Pop a value off the stack, will set an error if there is nothing on the stack. Only useful with plugin.

exp_ :: Exp a -> Exp () Source #

Erase the type of an Exp, only useful with plugin.

addPluginDir :: Exp String -> Action () Source #

Add a plugin directory

Installer

Global installer options

name :: Exp String -> Action () Source #

Sets the name of the installer. The name is usually simply the product name such as 'MyApp' or 'Company MyApp'.

name "MyApp"

outFile :: Exp FilePath -> Action () Source #

Specifies the output file that MakeNSIS should write the installer to. This is just the file that MakeNSIS writes, it doesn't affect the contents of the installer. Usually should end with .exe.

outFile "installer.exe"

installDir :: Exp FilePath -> Action () Source #

Sets the default installation directory. Note that the part of this string following the last \ will be used if the user selects browse, and may be appended back on to the string at install time (to disable this, end the directory with a \). If this doesn't make any sense, play around with the browse button a bit.

installDir "$PROGRAMFILES/MyApp"

installIcon :: Exp FilePath -> Action () Source #

Set the icon used for the installer/uninstaller.

installIcon "$NSISDIR/Contrib/Graphics/Icons/modern-install.ico"

uninstallIcon :: Exp FilePath -> Action () Source #

Set the icon used for the installer/uninstaller.

installIcon "$NSISDIR/Contrib/Graphics/Icons/modern-install.ico"

headerImage :: Maybe (Exp FilePath) -> Action () Source #

Set the image used for the header splash. Pass Nothing to use the default header image.

headerImage $ Just "$NSISDIR/Contrib/Graphics/Header/win.bmp"

installDirRegKey :: HKEY -> Exp String -> Exp String -> Action () Source #

This attribute tells the installer to check a string in the registry, and use it for the install dir if that string is valid. If this attribute is present, it will override the installDir attribute if the registry key is valid, otherwise it will fall back to the installDir default. When querying the registry, this command will automatically remove any quotes. If the string ends in ".exe", it will automatically remove the filename component of the string (i.e. if the string is "C:program filesfoo/foo.exe", it will know to use "C:program filesfoo").

installDirRegKey HKLM "Software/NSIS" ""
installDirRegKey HKLM "Software/ACME/Thingy" "InstallLocation"

unicode :: Bool -> Action () Source #

Note: Requires NSIS 3.0

Sections

data SectionId Source #

Instances
Data SectionId Source # 
Instance details

Defined in Development.NSIS.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SectionId -> c SectionId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SectionId #

toConstr :: SectionId -> Constr #

dataTypeOf :: SectionId -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SectionId) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SectionId) #

gmapT :: (forall b. Data b => b -> b) -> SectionId -> SectionId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SectionId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SectionId -> r #

gmapQ :: (forall d. Data d => d -> u) -> SectionId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SectionId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SectionId -> m SectionId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SectionId -> m SectionId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SectionId -> m SectionId #

Show SectionId Source # 
Instance details

Defined in Development.NSIS.Type

Events

event :: String -> Action () -> Action () Source #

Create a function, useful for registering actions

Section commands

alwaysNonFatal :: Action () -> Action () Source #

Set all file actions to automatically take NonFatal.

writeUninstaller :: Exp FilePath -> Action () Source #

Writes the uninstaller to the filename (and optionally path) specified. Only valid from within an install section, and requires that you have an uninstall section in your script. You can call this one or more times to write out one or more copies of the uninstaller.

writeUninstaller "$INSTDIR/uninstaller.exe"

alert :: Exp String -> Action () Source #

Show an alert, equivalent to messageBox [MB_ICONEXCLAMATION].

setOutPath :: Exp FilePath -> Action () Source #

Sets the output path ($OUTDIR) and creates it (recursively if necessary), if it does not exist. Must be a full pathname, usually is just $INSTDIR.

setOutPath "$INSTDIR"

hideProgress :: Action a -> Action a Source #

While the action is executing, do not update the progress bar. Useful for functions which do a large amount of computation, or have loops.

Escape hatch

unsafeInject :: String -> Action () Source #

Inject arbitrary text into a non-global section of the script.

unsafeInjectGlobal :: String -> Action () Source #

Inject arbitrary text into the script's global header section.

Settings

data Compressor Source #

Constructors

LZMA 
ZLIB 
BZIP2 
Instances
Data Compressor Source # 
Instance details

Defined in Development.NSIS.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Compressor -> c Compressor #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Compressor #

toConstr :: Compressor -> Constr #

dataTypeOf :: Compressor -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Compressor) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Compressor) #

gmapT :: (forall b. Data b => b -> b) -> Compressor -> Compressor #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Compressor -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Compressor -> r #

gmapQ :: (forall d. Data d => d -> u) -> Compressor -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Compressor -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Compressor -> m Compressor #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Compressor -> m Compressor #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Compressor -> m Compressor #

Show Compressor Source # 
Instance details

Defined in Development.NSIS.Type

data HKEY Source #

Instances
Bounded HKEY Source # 
Instance details

Defined in Development.NSIS.Type

Enum HKEY Source # 
Instance details

Defined in Development.NSIS.Type

Methods

succ :: HKEY -> HKEY #

pred :: HKEY -> HKEY #

toEnum :: Int -> HKEY #

fromEnum :: HKEY -> Int #

enumFrom :: HKEY -> [HKEY] #

enumFromThen :: HKEY -> HKEY -> [HKEY] #

enumFromTo :: HKEY -> HKEY -> [HKEY] #

enumFromThenTo :: HKEY -> HKEY -> HKEY -> [HKEY] #

Eq HKEY Source # 
Instance details

Defined in Development.NSIS.Type

Methods

(==) :: HKEY -> HKEY -> Bool #

(/=) :: HKEY -> HKEY -> Bool #

Data HKEY Source # 
Instance details

Defined in Development.NSIS.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HKEY -> c HKEY #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HKEY #

toConstr :: HKEY -> Constr #

dataTypeOf :: HKEY -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HKEY) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HKEY) #

gmapT :: (forall b. Data b => b -> b) -> HKEY -> HKEY #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HKEY -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HKEY -> r #

gmapQ :: (forall d. Data d => d -> u) -> HKEY -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HKEY -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HKEY -> m HKEY #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HKEY -> m HKEY #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HKEY -> m HKEY #

Ord HKEY Source # 
Instance details

Defined in Development.NSIS.Type

Methods

compare :: HKEY -> HKEY -> Ordering #

(<) :: HKEY -> HKEY -> Bool #

(<=) :: HKEY -> HKEY -> Bool #

(>) :: HKEY -> HKEY -> Bool #

(>=) :: HKEY -> HKEY -> Bool #

max :: HKEY -> HKEY -> HKEY #

min :: HKEY -> HKEY -> HKEY #

Read HKEY Source # 
Instance details

Defined in Development.NSIS.Type

Show HKEY Source # 
Instance details

Defined in Development.NSIS.Type

Methods

showsPrec :: Int -> HKEY -> ShowS #

show :: HKEY -> String #

showList :: [HKEY] -> ShowS #

data MessageBoxType Source #

Constructors

MB_OK

Display with an OK button

MB_OKCANCEL

Display with an OK and a cancel button

MB_ABORTRETRYIGNORE

Display with abort, retry, ignore buttons

MB_RETRYCANCEL

Display with retry and cancel buttons

MB_YESNO

Display with yes and no buttons

MB_YESNOCANCEL

Display with yes, no, cancel buttons

MB_ICONEXCLAMATION

Display with exclamation icon

MB_ICONINFORMATION

Display with information icon

MB_ICONQUESTION

Display with question mark icon

MB_ICONSTOP

Display with stop icon

MB_USERICON

Display with installer's icon

MB_TOPMOST

Make messagebox topmost

MB_SETFOREGROUND

Set foreground

MB_RIGHT

Right align text

MB_RTLREADING

RTL reading order

MB_DEFBUTTON1

Button 1 is default

MB_DEFBUTTON2

Button 2 is default

MB_DEFBUTTON3

Button 3 is default

MB_DEFBUTTON4

Button 4 is default

Instances
Bounded MessageBoxType Source # 
Instance details

Defined in Development.NSIS.Type

Enum MessageBoxType Source # 
Instance details

Defined in Development.NSIS.Type

Eq MessageBoxType Source # 
Instance details

Defined in Development.NSIS.Type

Data MessageBoxType Source # 
Instance details

Defined in Development.NSIS.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MessageBoxType -> c MessageBoxType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MessageBoxType #

toConstr :: MessageBoxType -> Constr #

dataTypeOf :: MessageBoxType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MessageBoxType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MessageBoxType) #

gmapT :: (forall b. Data b => b -> b) -> MessageBoxType -> MessageBoxType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MessageBoxType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MessageBoxType -> r #

gmapQ :: (forall d. Data d => d -> u) -> MessageBoxType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MessageBoxType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MessageBoxType -> m MessageBoxType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageBoxType -> m MessageBoxType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageBoxType -> m MessageBoxType #

Ord MessageBoxType Source # 
Instance details

Defined in Development.NSIS.Type

Read MessageBoxType Source # 
Instance details

Defined in Development.NSIS.Type

Show MessageBoxType Source # 
Instance details

Defined in Development.NSIS.Type

data Page Source #

Instances
Eq Page Source # 
Instance details

Defined in Development.NSIS.Type

Methods

(==) :: Page -> Page -> Bool #

(/=) :: Page -> Page -> Bool #

Data Page Source # 
Instance details

Defined in Development.NSIS.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Page -> c Page #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Page #

toConstr :: Page -> Constr #

dataTypeOf :: Page -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Page) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Page) #

gmapT :: (forall b. Data b => b -> b) -> Page -> Page #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Page -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Page -> r #

gmapQ :: (forall d. Data d => d -> u) -> Page -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Page -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Page -> m Page #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Page -> m Page #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Page -> m Page #

Show Page Source # 
Instance details

Defined in Development.NSIS.Type

Methods

showsPrec :: Int -> Page -> ShowS #

show :: Page -> String #

showList :: [Page] -> ShowS #

data Level Source #

Constructors

None 
User 
Highest 
Admin 
Instances
Bounded Level Source # 
Instance details

Defined in Development.NSIS.Type

Enum Level Source # 
Instance details

Defined in Development.NSIS.Type

Eq Level Source # 
Instance details

Defined in Development.NSIS.Type

Methods

(==) :: Level -> Level -> Bool #

(/=) :: Level -> Level -> Bool #

Data Level Source # 
Instance details

Defined in Development.NSIS.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Level -> c Level #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Level #

toConstr :: Level -> Constr #

dataTypeOf :: Level -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Level) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Level) #

gmapT :: (forall b. Data b => b -> b) -> Level -> Level #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Level -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Level -> r #

gmapQ :: (forall d. Data d => d -> u) -> Level -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Level -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Level -> m Level #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Level -> m Level #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Level -> m Level #

Ord Level Source # 
Instance details

Defined in Development.NSIS.Type

Methods

compare :: Level -> Level -> Ordering #

(<) :: Level -> Level -> Bool #

(<=) :: Level -> Level -> Bool #

(>) :: Level -> Level -> Bool #

(>=) :: Level -> Level -> Bool #

max :: Level -> Level -> Level #

min :: Level -> Level -> Level #

Read Level Source # 
Instance details

Defined in Development.NSIS.Type

Show Level Source # 
Instance details

Defined in Development.NSIS.Type

Methods

showsPrec :: Int -> Level -> ShowS #

show :: Level -> String #

showList :: [Level] -> ShowS #

data Visibility Source #

Constructors

Hide 
Show 
NeverShow 
Instances
Bounded Visibility Source # 
Instance details

Defined in Development.NSIS.Type

Enum Visibility Source # 
Instance details

Defined in Development.NSIS.Type

Eq Visibility Source # 
Instance details

Defined in Development.NSIS.Type

Data Visibility Source # 
Instance details

Defined in Development.NSIS.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Visibility -> c Visibility #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Visibility #

toConstr :: Visibility -> Constr #

dataTypeOf :: Visibility -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Visibility) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Visibility) #

gmapT :: (forall b. Data b => b -> b) -> Visibility -> Visibility #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Visibility -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Visibility -> r #

gmapQ :: (forall d. Data d => d -> u) -> Visibility -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Visibility -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Visibility -> m Visibility #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Visibility -> m Visibility #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Visibility -> m Visibility #

Ord Visibility Source # 
Instance details

Defined in Development.NSIS.Type

Read Visibility Source # 
Instance details

Defined in Development.NSIS.Type

Show Visibility Source # 
Instance details

Defined in Development.NSIS.Type

data FileMode Source #

Mode to use with 'Development.

Constructors

ModeRead

Read a file.

ModeWrite 
ModeAppend

Opened for both read and write, contents preserved.

Instances
Bounded FileMode Source # 
Instance details

Defined in Development.NSIS.Type

Enum FileMode Source # 
Instance details

Defined in Development.NSIS.Type

Eq FileMode Source # 
Instance details

Defined in Development.NSIS.Type

Data FileMode Source # 
Instance details

Defined in Development.NSIS.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FileMode -> c FileMode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FileMode #

toConstr :: FileMode -> Constr #

dataTypeOf :: FileMode -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FileMode) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FileMode) #

gmapT :: (forall b. Data b => b -> b) -> FileMode -> FileMode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FileMode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FileMode -> r #

gmapQ :: (forall d. Data d => d -> u) -> FileMode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FileMode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FileMode -> m FileMode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FileMode -> m FileMode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FileMode -> m FileMode #

Ord FileMode Source # 
Instance details

Defined in Development.NSIS.Type

Show FileMode Source # 
Instance details

Defined in Development.NSIS.Type

data SectionFlag Source #

Instances
Bounded SectionFlag Source # 
Instance details

Defined in Development.NSIS.Sugar

Enum SectionFlag Source # 
Instance details

Defined in Development.NSIS.Sugar

Eq SectionFlag Source # 
Instance details

Defined in Development.NSIS.Sugar

Data SectionFlag Source # 
Instance details

Defined in Development.NSIS.Sugar

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SectionFlag -> c SectionFlag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SectionFlag #

toConstr :: SectionFlag -> Constr #

dataTypeOf :: SectionFlag -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SectionFlag) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SectionFlag) #

gmapT :: (forall b. Data b => b -> b) -> SectionFlag -> SectionFlag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SectionFlag -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SectionFlag -> r #

gmapQ :: (forall d. Data d => d -> u) -> SectionFlag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SectionFlag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SectionFlag -> m SectionFlag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SectionFlag -> m SectionFlag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SectionFlag -> m SectionFlag #

Ord SectionFlag Source # 
Instance details

Defined in Development.NSIS.Sugar

Read SectionFlag Source # 
Instance details

Defined in Development.NSIS.Sugar

Show SectionFlag Source # 
Instance details

Defined in Development.NSIS.Sugar

data ShowWindow Source #

Instances
Bounded ShowWindow Source # 
Instance details

Defined in Development.NSIS.Type

Enum ShowWindow Source # 
Instance details

Defined in Development.NSIS.Type

Eq ShowWindow Source # 
Instance details

Defined in Development.NSIS.Type

Data ShowWindow Source # 
Instance details

Defined in Development.NSIS.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ShowWindow -> c ShowWindow #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ShowWindow #

toConstr :: ShowWindow -> Constr #

dataTypeOf :: ShowWindow -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ShowWindow) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ShowWindow) #

gmapT :: (forall b. Data b => b -> b) -> ShowWindow -> ShowWindow #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ShowWindow -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ShowWindow -> r #

gmapQ :: (forall d. Data d => d -> u) -> ShowWindow -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ShowWindow -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ShowWindow -> m ShowWindow #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ShowWindow -> m ShowWindow #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ShowWindow -> m ShowWindow #

Ord ShowWindow Source # 
Instance details

Defined in Development.NSIS.Type

Read ShowWindow Source # 
Instance details

Defined in Development.NSIS.Type

Show ShowWindow Source # 
Instance details

Defined in Development.NSIS.Type

data FinishOptions Source #

Instances
Eq FinishOptions Source # 
Instance details

Defined in Development.NSIS.Type

Data FinishOptions Source # 
Instance details

Defined in Development.NSIS.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FinishOptions -> c FinishOptions #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FinishOptions #

toConstr :: FinishOptions -> Constr #

dataTypeOf :: FinishOptions -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FinishOptions) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FinishOptions) #

gmapT :: (forall b. Data b => b -> b) -> FinishOptions -> FinishOptions #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FinishOptions -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FinishOptions -> r #

gmapQ :: (forall d. Data d => d -> u) -> FinishOptions -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FinishOptions -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FinishOptions -> m FinishOptions #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FinishOptions -> m FinishOptions #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FinishOptions -> m FinishOptions #

Show FinishOptions Source # 
Instance details

Defined in Development.NSIS.Type

data DetailsPrint Source #

Value to use with setDetailsPrint.

Instances
Bounded DetailsPrint Source # 
Instance details

Defined in Development.NSIS.Type

Enum DetailsPrint Source # 
Instance details

Defined in Development.NSIS.Type

Eq DetailsPrint Source # 
Instance details

Defined in Development.NSIS.Type

Data DetailsPrint Source # 
Instance details

Defined in Development.NSIS.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DetailsPrint -> c DetailsPrint #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DetailsPrint #

toConstr :: DetailsPrint -> Constr #

dataTypeOf :: DetailsPrint -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DetailsPrint) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DetailsPrint) #

gmapT :: (forall b. Data b => b -> b) -> DetailsPrint -> DetailsPrint #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DetailsPrint -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DetailsPrint -> r #

gmapQ :: (forall d. Data d => d -> u) -> DetailsPrint -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DetailsPrint -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DetailsPrint -> m DetailsPrint #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DetailsPrint -> m DetailsPrint #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DetailsPrint -> m DetailsPrint #

Ord DetailsPrint Source # 
Instance details

Defined in Development.NSIS.Type

Show DetailsPrint Source # 
Instance details

Defined in Development.NSIS.Type