module Development.NSIS.Library where
import Control.Monad
import Development.NSIS.Sugar
strReplace :: Exp String -> Exp String -> Exp String -> Exp String
strReplace from to str = do
from <- constant_ from
to <- constant_ to
str <- constant_ str
scope $ do
rest <- mutable "REST" str
res <- mutable "RES" ""
while (rest %/= "") $ do
iff (from `strIsPrefixOf` rest)
(do
res @= res & to
rest @= strDrop (strLength from) rest)
(do
res @= res & strTake 1 rest
rest @= strDrop 1 rest)
res
strIsPrefixOf :: Exp String -> Exp String -> Exp Bool
strIsPrefixOf x y = share x $ \x -> share y $ \y ->
strTake (strLength x) y %== strTake (strLength y) x
strUnlines :: [Exp String] -> Exp String
strUnlines = strConcat . map (& "\r\n")
writeFileLines :: Exp FilePath -> [Exp String] -> Action ()
writeFileLines a b = withFile' ModeWrite a $ \hdl ->
forM_ b $ \s -> fileWrite hdl $ s & "\r\n"
infixr 3 %&&
infixr 2 %||
(%&&), (%||) :: Exp Bool -> Exp Bool -> Exp Bool
(%&&) a b = a ? (b, false)
(%||) a b = a ? (true, b)
withFile' :: FileMode -> Exp FilePath -> (Exp FileHandle -> Action ()) -> Action ()
withFile' mode name act = do
hdl <- fileOpen mode name
act hdl
fileClose hdl
writeFile' :: Exp FilePath -> Exp String -> Action ()
writeFile' name contents = withFile' ModeWrite name $ \hdl -> fileWrite hdl contents