Skip to content

Commit

Permalink
prep for 0.1 hackage release
Browse files Browse the repository at this point in the history
  • Loading branch information
atzedijkstra committed Oct 5, 2012
1 parent d2f1735 commit c4e5943
Show file tree
Hide file tree
Showing 8 changed files with 133 additions and 42 deletions.
1 change: 1 addition & 0 deletions LICENSE
@@ -0,0 +1 @@
BSD3
35 changes: 34 additions & 1 deletion README.md
@@ -1,4 +1,37 @@
macosx-make-standalone macosx-make-standalone
====================== ======================


Modify a MacOSX app bundle to include non standard .dylibs, so it can be run without development environment Modify a MacOSX app bundle to include non standard .dylibs, so it can be run without development environment


Installation
============

- Requires Haskell (7.4.1 onwards)
- Installs via hackage or from this source repo via cabal
- Hackage:
cabal install macosx-make-standalone
- From repo:
cabal configure
cabal build
cabal install


Manual
======

Invocation:
macosx-make-standalone <mac app bundle>

What is does, restrictions:
- Copies all non /usr/lib .dylib files into <mac app bundle>/Contents/lib/
- Changes all references to the old library into refs to the copied libraries, in the <mac app bundle>/Contents/MacOS/<app name> as well as the copied libraries
- Resolves symbolic links of referenced libraries (thus not for <mac app bundle>)
- In case of duplicate libraries ending up with the same copy name, an arbitrary one is picked (no problem if they are equal)
- Can only be run once, i.e. is not idempotent


Tested with
===========

A single wxHaskell based application, on MacOSX 10.8
2 changes: 2 additions & 0 deletions Setup.hs
@@ -0,0 +1,2 @@
import Distribution.Simple
main = defaultMain
9 changes: 7 additions & 2 deletions macosx-make-standalone.cabal
Expand Up @@ -3,14 +3,19 @@ Version: 0.1
Synopsis: Make a macosx app standalone deployable Synopsis: Make a macosx app standalone deployable
Description: Make a macosx app standalone by bundling all dylibs into it. Description: Make a macosx app standalone by bundling all dylibs into it.
License: BSD3 License: BSD3
license-file: LICENSE
Author: Atze Dijkstra Author: Atze Dijkstra
Maintainer: atze@uu.nl Maintainer: atze@uu.nl
Homepage: https://github.com/atzedijkstra Homepage: https://github.com/atzedijkstra/macosx-make-standalone
Bug-Reports: https://github.com/atzedijkstra/issues Bug-Reports: https://github.com/atzedijkstra/macosx-make-standalone/issues
Copyright: 2012 Utrecht University Copyright: 2012 Utrecht University
Category: Development Category: Development
Build-type: Simple Build-type: Simple
Cabal-version: >=1.6 Cabal-version: >=1.6
source-repository head
type: git
location: git://github.com/atzedijkstra/macosx-make-standalone.git



Executable macosx-make-standalone Executable macosx-make-standalone
HS-Source-Dirs: src HS-Source-Dirs: src
Expand Down
46 changes: 38 additions & 8 deletions src/Cmds.hs
Expand Up @@ -7,6 +7,9 @@ module Cmds
, cmdOTool , cmdOTool
, cmdCP , cmdCP
, cmdChmod , cmdChmod
, cmdMkdir
, cmdInstallNameToolId
, cmdInstallNameToolChange
) where ) where


------------------------------------------------------------------------- -------------------------------------------------------------------------
Expand Down Expand Up @@ -51,15 +54,22 @@ showCmdSpec (RawCommand f as) = concat $ intersperse " " (f:as)
cmdRunPlain :: Opts -> CreateProcess -> IO () cmdRunPlain :: Opts -> CreateProcess -> IO ()
cmdRunPlain opts p = do cmdRunPlain opts p = do
when (opts ^. optVerbose) (putStrLn (showCmdSpec $ cmdspec p)) when (opts ^. optVerbose) (putStrLn (showCmdSpec $ cmdspec p))
createProcess p (_, _, _, phandle) <-createProcess p
waitForProcess phandle
return () return ()


cmdRunOutputPipe :: Opts -> CreateProcess -> IO Handle cmdRunOutputPipe :: Opts -> CreateProcess -> IO Handle
cmdRunOutputPipe opts p = do cmdRunOutputPipe opts p = do
when (opts ^. optVerbose) (putStrLn (showCmdSpec $ cmdspec p)) when (opts ^. optVerbose) (putStrLn (showCmdSpec $ cmdspec p))
(_, Just hout, _, _) <- createProcess (p {std_out = CreatePipe}) (_, Just hout, _, phandle) <- createProcess (p {std_out = CreatePipe})
waitForProcess phandle
return hout return hout


cmdRun :: String -> String -> [FilePath] -> StRun ()
cmdRun c m fs = do
opts <- access opts
liftIO $ cmdRunPlain opts $ proc c (m : fs)

------------------------------------------------------------------------- -------------------------------------------------------------------------
-- otool -- otool
------------------------------------------------------------------------- -------------------------------------------------------------------------
Expand Down Expand Up @@ -98,15 +108,35 @@ cmdOTool f = do
------------------------------------------------------------------------- -------------------------------------------------------------------------


cmdCP :: String -> FilePath -> FilePath -> StRun () cmdCP :: String -> FilePath -> FilePath -> StRun ()
cmdCP o fFr fTo = do cmdCP o fFr fTo = cmdRun "cp" o [fFr, fTo]
opts <- access opts
liftIO $ cmdRunPlain opts $ proc "cp" [o, fFr, fTo]


------------------------------------------------------------------------- -------------------------------------------------------------------------
-- chmod -- chmod
------------------------------------------------------------------------- -------------------------------------------------------------------------


cmdChmod :: String -> FilePath -> StRun () cmdChmod :: String -> FilePath -> StRun ()
cmdChmod m f = do cmdChmod o f = cmdRun "chmod" o [f]
opts <- access opts
liftIO $ cmdRunPlain opts $ proc "chmod" [m, f] -------------------------------------------------------------------------
-- mkdir
-------------------------------------------------------------------------

cmdMkdir :: String -> FilePath -> StRun ()
cmdMkdir o f = cmdRun "mkdir" o [f]

-------------------------------------------------------------------------
-- install_name_tool
-------------------------------------------------------------------------

cmdInstallNameToolChange :: FilePath -> FilePath -> FilePath -> StRun ()
cmdInstallNameToolChange fIn fFr fTo = cmdRun "install_name_tool" "-change" [fFr, fTo, fIn]

cmdInstallNameToolId :: FilePath -> FilePath -> StRun ()
cmdInstallNameToolId fIn fTo = cmdRun "install_name_tool" "-id" [fTo, fIn]

{-
install_name_tool -id @executable_path/../libs/libwx_osx_cocoau_xrc-2.9.4.0.0.dylib ./Dazzle.app/Contents/libs/libwx_osx_cocoau_xrc-2.9.4.0.0.dylib
* Fixing dependencies on ./Dazzle.app/Contents/libs/libwx_osx_cocoau_xrc-2.9.4.0.0.dylib
install_name_tool -change /Volumes/Work/.cabal/lib/wxc-0.90.0.4/ghc-7.4.1/libwxc.dylib @executable_path/../libs/libwxc.dylib ./Dazzle.app/Contents/libs/libwx_osx_cocoau_xrc-2.9.4.0.0.dylib
-}
40 changes: 24 additions & 16 deletions src/MakeStandalone.hs
Expand Up @@ -66,9 +66,10 @@ doIt opts fnmApp = do
fnm = fpathOfExec opts fnmApp fnm = fpathOfExec opts fnmApp
thework = do thework = do
ldep <- otoolGraphVisit2LibDepGraph fnm ldep <- otoolGraphVisit2LibDepGraph fnm
when (opts ^. optVerbose) (liftIO $ putStrLn (show ldep)) when (opts ^. optDebug) (liftIO $ putStrLn (show ldep))
let plan = ldepGraph2Plan opts fnmApp ldep let plan = seqToList $ ldepGraph2Plan opts fnmApp ldep
when (opts ^. optVerbose) (liftIO $ forM_ (seqToList plan) (putStrLn . show)) when (opts ^. optDebug) (liftIO $ forM_ plan (putStrLn . show))
forM_ plan planCmdExec
return () return ()
-- f <- srFreshTmpName -- f <- srFreshTmpName
-- liftIO $ putStrLn f -- liftIO $ putStrLn f
Expand Down Expand Up @@ -117,23 +118,30 @@ ldepGraph2Plan opts fnmApp ldep =
[ PlanCmd_CP o n | (n,((o:_),_)) <- Map.toList filesToCopy ] [ PlanCmd_CP o n | (n,((o:_),_)) <- Map.toList filesToCopy ]
Seq.>< Seq.><
foldr (Seq.><) Seq.empty foldr (Seq.><) Seq.empty
[ Seq.fromList $ [ Seq.fromList $ PlanCmd_IntlRename n ri : mkModfRef filesToCopy n o
PlanCmd_IntlRename n o ri
: [ PlanCmd_ModfRef n u rr
| u <- maybe [] (^. libUses) $ Map.lookup o $ ldep ^. ldepGraph
, let u2 = ldepResolveSymlink ldep u
rr = Map.findWithDefault u2 u2 filesToCopyRev
]
| (n,((o:_),ri)) <- Map.toList filesToCopy | (n,((o:_),ri)) <- Map.toList filesToCopy
] ]
Seq.><
foldr (Seq.><) Seq.empty
[ Seq.fromList $ mkModfRef filesToCopy o o
| (_,((o:_),_)) <- Map.toList filesRoot
]
where where
filesToCopy = Map.fromListWith (\(l1,r1) (l2,_) -> (l1++l2,r1)) filesToCopy = mkFilesToCopyMp (Set.delete (ldep ^. ldepRoot) $ Map.keysSet $ ldep ^. ldepGraph)
[ (n, ([l'],r)) filesRoot = Map.fromList [ (o,([o],o)) | o <- [ldep ^. ldepRoot] ]
| l <- Set.toList $ Set.delete (ldep ^. ldepRoot) $ Map.keysSet $ ldep ^. ldepGraph mkFilesToCopyMp fs = Map.fromListWith (\(l1,r1) (l2,_) -> (l1++l2,r1))
, let l' = l -- ldepResolveSymlink ldep l [ (n, ([l],r))
(n,r) = fpathOfNewLib opts fnmApp l' | l <- Set.toList fs
, let (n,r) = fpathOfNewLib opts fnmApp l
]
mkFilesToCopyMpRev fMp = Map.fromList [ (o,r) | (n,(os,r)) <- Map.toList fMp, o <- os ]
mkModfRef fMp n o =
[ PlanCmd_ModfRef n u rr
| u <- maybe [] (^. libUses) $ Map.lookup o $ ldep ^. ldepGraph
, let u2 = ldepResolveSymlink ldep u
rr = Map.findWithDefault u2 u2 fMpRev
] ]
filesToCopyRev = Map.fromList [ (o,r) | (n,(os,r)) <- Map.toList filesToCopy, o <- os ] where fMpRev = mkFilesToCopyMpRev fMp


------------------------------------------------------------------------- -------------------------------------------------------------------------
-- File name manipulation -- File name manipulation
Expand Down
8 changes: 8 additions & 0 deletions src/Opts.hs
Expand Up @@ -5,6 +5,7 @@ module Opts


, optImmediateCommands , optImmediateCommands
, optVerbose , optVerbose
, optDebug
, optProgName , optProgName
, optExcludePrefixes , optExcludePrefixes
, optIncludeExtensions , optIncludeExtensions
Expand All @@ -21,6 +22,9 @@ module Opts
-- Imports -- Imports
------------------------------------------------------------------------- -------------------------------------------------------------------------


import Prelude hiding ((.))
import Control.Category

import Data.Lens.Common import Data.Lens.Common
import Data.Lens.Template import Data.Lens.Template
import Data.Typeable import Data.Typeable
Expand All @@ -43,6 +47,7 @@ data ImmediateCommand
data Opts data Opts
= Opts = Opts
{ _optVerbose :: Bool -- ^ be verbose { _optVerbose :: Bool -- ^ be verbose
, _optDebug :: Bool -- ^ dump debug info
, _optImmediateCommands :: [ImmediateCommand] -- ^ e.g. help , _optImmediateCommands :: [ImmediateCommand] -- ^ e.g. help
, _optProgName :: String -- ^ the name of this program , _optProgName :: String -- ^ the name of this program
, _optExcludePrefixes :: [FilePath] -- ^ prefixes of locations which may not be copied , _optExcludePrefixes :: [FilePath] -- ^ prefixes of locations which may not be copied
Expand All @@ -60,6 +65,7 @@ makeLens ''Opts
defaultOpts defaultOpts
= Opts = Opts
{ _optVerbose = False { _optVerbose = False
, _optDebug = False
, _optImmediateCommands = [] , _optImmediateCommands = []
, _optProgName = "??" , _optProgName = "??"
, _optExcludePrefixes = [ "/usr/lib" , _optExcludePrefixes = [ "/usr/lib"
Expand All @@ -81,5 +87,7 @@ cmdLineOpts
"output this help" "output this help"
, Option "v" ["verbose"] (NoArg $ optVerbose ^= True) , Option "v" ["verbose"] (NoArg $ optVerbose ^= True)
"be verbose" "be verbose"
, Option "d" ["debug"] (NoArg $ (optVerbose ^= True) . (optDebug ^= True))
"dump debug info"
] ]


34 changes: 19 additions & 15 deletions src/Plan.hs
Expand Up @@ -31,7 +31,7 @@ import Data.Typeable
-- import System.Environment -- import System.Environment
-- import System.IO -- import System.IO
-- import System.Exit -- import System.Exit
-- import System.FilePath import System.FilePath
-- import System.Directory -- import System.Directory
-- import System.Cmd -- import System.Cmd
-- import System.Process -- import System.Process
Expand All @@ -46,19 +46,18 @@ import Cmds
------------------------------------------------------------------------- -------------------------------------------------------------------------


data PlanCmd data PlanCmd
= PlanCmd_CP -- ^ Copy file = PlanCmd_CP -- ^ Copy file
{ _pcFrom :: FilePath { _pcFrom :: FilePath
, _pcTo :: FilePath , _pcTo :: FilePath
} }
| PlanCmd_ModfRef -- ^ Modify ref in file | PlanCmd_ModfRef -- ^ Modify ref in file
{ _pcInFile :: FilePath { _pcInFile :: FilePath
, _pcFrom :: FilePath , _pcFrom :: FilePath
, _pcTo :: FilePath , _pcTo :: FilePath
} }
| PlanCmd_IntlRename -- ^ Modify internal name in file | PlanCmd_IntlRename -- ^ Modify internal name in file
{ _pcInFile :: FilePath { _pcInFile :: FilePath
, _pcFrom :: FilePath , _pcTo :: FilePath
, _pcTo :: FilePath
} }
deriving (Show,Typeable) deriving (Show,Typeable)


Expand All @@ -72,9 +71,14 @@ type Plan = Seq PlanCmd


planCmdExec :: PlanCmd -> StRun () planCmdExec :: PlanCmd -> StRun ()
planCmdExec pcmd = case pcmd of planCmdExec pcmd = case pcmd of
PlanCmd_CP fFr fTo -> do cmdCP "-f" fFr fTo PlanCmd_CP fFr fTo -> do
cmdChmod "+w" fTo cmdMkdir "-p" $ takeDirectory fTo
_ -> return () cmdCP "-f" fFr fTo
cmdChmod "+w" fTo
PlanCmd_ModfRef fIn fFr fTo -> do
cmdInstallNameToolChange fIn fFr fTo
PlanCmd_IntlRename fIn fTo -> do
cmdInstallNameToolId fIn fTo


------------------------------------------------------------------------- -------------------------------------------------------------------------
-- Seq extension -- Seq extension
Expand Down

0 comments on commit c4e5943

Please sign in to comment.