All, I did some more work and we have version 2 of the patches to make a GHC cross compiler, here - patches against GHC HEAD: http://hip-to-be-square.com/~blackh/ghc-cross/ These patches will need a lot more testing and tidying up before they're ready to push upstream. (Thanks for your email Manuel.) They also don't yet properly work with packages containing C stuff that uses configure. If you would like to give it a try, here's what you need to do: * If your cross-compile target is arm, you'll need >= llvm-3.0rc3 * Check out GHC HEAD (see GHC wiki) and apply the patches * Copy build.mk into ghc/mk/ and alien and config.sh into ghc/. Tweak to your requirements. 'alien' is a script that you must provide, to run code generated for your target platform locally. This could be by scp and ssh, or as in my case, using qemu. * ./config.sh * make and install ghc * Install a patched version of the Cabal package locally. It happens that there's a nice easy way to do that: cd ghc/libraries/Cabal/Cabal cabal install * Re-install a cabal-install to use this new Cabal. Note that the hackage version of cabal-install has an upper limit on Cabal that is too low for ghc-head's version. You can just remove this upper limit in the .cabal file. The terminal session below shows you how to use it. The CROSS_COMPILE environment variable tells Cabal what target to use. Note that it has to have a trailing -. --- iPhone: Once this is going, I'll work on getting it pushed upstream. Then I'll get onto compiling specifically for iPhone. Steve blackh@amentet:~/src/haskell$ export PATH=/usr/local/ghc-ldu/bin:$PATH blackh@amentet:~/src/haskell$ export CROSS_COMPILE=arm-ldu-linux-gnueabi- blackh@amentet:~/src/haskell$ cat reverse.hs {-# LANGUAGE DoRec #-} import Control.Monad.Fix import Control.Monad.Trans import Control.Monad main = runReverseT $ do lift $ putStrLn "start" forM_ [1..5] (lift . print) lift $ putStrLn "end" ----------------------------------------------------- newtype ReverseT m a = ReverseT { runReverseT :: m a } instance MonadFix m => Monad (ReverseT m) where return = ReverseT . return ReverseT m >>= f = ReverseT $ do rec b <- runReverseT (f a) a <- m return b instance MonadTrans ReverseT where lift = ReverseT blackh@amentet:~/src/haskell$ cabal install mtl Resolving dependencies... Configuring transformers-0.2.2.0... Building transformers-0.2.2.0... Preprocessing library transformers-0.2.2.0... [ 1 of 21] Compiling Data.Functor.Product ( Data/Functor/Product.hs, dist/build/Data/Functor/Product.o ) [ 2 of 21] Compiling Data.Functor.Constant ( Data/Functor/Constant.hs, dist/build/Data/Functor/Constant.o ) [ 3 of 21] Compiling Data.Functor.Compose ( Data/Functor/Compose.hs, dist/build/Data/Functor/Compose.o ) [ 4 of 21] Compiling Data.Functor.Identity ( Data/Functor/Identity.hs, dist/build/Data/Functor/Identity.o ) [ 5 of 21] Compiling Control.Monad.Trans.Class ( Control/Monad/Trans/Class.hs, dist/build/Control/Monad/Trans/Class.o ) [ 6 of 21] Compiling Control.Monad.IO.Class ( Control/Monad/IO/Class.hs, dist/build/Control/Monad/IO/Class.o ) [ 7 of 21] Compiling Control.Monad.Trans.Cont ( Control/Monad/Trans/Cont.hs, dist/build/Control/Monad/Trans/Cont.o ) [ 8 of 21] Compiling Control.Monad.Trans.Error ( Control/Monad/Trans/Error.hs, dist/build/Control/Monad/Trans/Error.o ) Control/Monad/Trans/Error.hs:26:8: Warning: In the use of `catch' (imported from Prelude, but defined in System.IO.Error): Deprecated: "Please use the new exceptions variant, Control.Exception.catch" [ 9 of 21] Compiling Control.Monad.Trans.Identity ( Control/Monad/Trans/Identity.hs, dist/build/Control/Monad/Trans/Identity.o ) [10 of 21] Compiling Control.Monad.Trans.List ( Control/Monad/Trans/List.hs, dist/build/Control/Monad/Trans/List.o ) [11 of 21] Compiling Control.Monad.Trans.Maybe ( Control/Monad/Trans/Maybe.hs, dist/build/Control/Monad/Trans/Maybe.o ) [12 of 21] Compiling Control.Monad.Trans.Reader ( Control/Monad/Trans/Reader.hs, dist/build/Control/Monad/Trans/Reader.o ) [13 of 21] Compiling Control.Monad.Trans.RWS.Lazy ( Control/Monad/Trans/RWS/Lazy.hs, dist/build/Control/Monad/Trans/RWS/Lazy.o ) [14 of 21] Compiling Control.Monad.Trans.RWS ( Control/Monad/Trans/RWS.hs, dist/build/Control/Monad/Trans/RWS.o ) [15 of 21] Compiling Control.Monad.Trans.RWS.Strict ( Control/Monad/Trans/RWS/Strict.hs, dist/build/Control/Monad/Trans/RWS/Strict.o ) [16 of 21] Compiling Control.Monad.Trans.State.Lazy ( Control/Monad/Trans/State/Lazy.hs, dist/build/Control/Monad/Trans/State/Lazy.o ) [17 of 21] Compiling Control.Monad.Trans.State ( Control/Monad/Trans/State.hs, dist/build/Control/Monad/Trans/State.o ) [18 of 21] Compiling Control.Monad.Trans.State.Strict ( Control/Monad/Trans/State/Strict.hs, dist/build/Control/Monad/Trans/State/Strict.o ) [19 of 21] Compiling Control.Monad.Trans.Writer.Lazy ( Control/Monad/Trans/Writer/Lazy.hs, dist/build/Control/Monad/Trans/Writer/Lazy.o ) [20 of 21] Compiling Control.Monad.Trans.Writer ( Control/Monad/Trans/Writer.hs, dist/build/Control/Monad/Trans/Writer.o ) [21 of 21] Compiling Control.Monad.Trans.Writer.Strict ( Control/Monad/Trans/Writer/Strict.hs, dist/build/Control/Monad/Trans/Writer/Strict.o ) Registering transformers-0.2.2.0... Running Haddock for transformers-0.2.2.0... cabal: Haddock's internal GHC version must match the configured GHC version. The GHC version is 7.3.20111121 but haddock is using GHC version 7.0.4 Installing library in /home/blackh/.cabal/lib/transformers-0.2.2.0/ghc-7.3.20111121 Registering transformers-0.2.2.0... Configuring mtl-2.0.1.0... Building mtl-2.0.1.0... Preprocessing library mtl-2.0.1.0... [ 1 of 21] Compiling Control.Monad.Writer.Class ( Control/Monad/Writer/Class.hs, dist/build/Control/Monad/Writer/Class.o ) [ 2 of 21] Compiling Control.Monad.State.Class ( Control/Monad/State/Class.hs, dist/build/Control/Monad/State/Class.o ) [ 3 of 21] Compiling Control.Monad.Reader.Class ( Control/Monad/Reader/Class.hs, dist/build/Control/Monad/Reader/Class.o ) [ 4 of 21] Compiling Control.Monad.RWS.Class ( Control/Monad/RWS/Class.hs, dist/build/Control/Monad/RWS/Class.o ) [ 5 of 21] Compiling Control.Monad.Identity ( Control/Monad/Identity.hs, dist/build/Control/Monad/Identity.o ) [ 6 of 21] Compiling Control.Monad.Error.Class ( Control/Monad/Error/Class.hs, dist/build/Control/Monad/Error/Class.o ) Control/Monad/Error/Class.hs:36:8: Warning: In the use of `catch' (imported from Prelude, but defined in System.IO.Error): Deprecated: "Please use the new exceptions variant, Control.Exception.catch" [ 7 of 21] Compiling Control.Monad.Cont.Class ( Control/Monad/Cont/Class.hs, dist/build/Control/Monad/Cont/Class.o ) [ 8 of 21] Compiling Control.Monad.Trans ( Control/Monad/Trans.hs, dist/build/Control/Monad/Trans.o ) [ 9 of 21] Compiling Control.Monad.Error ( Control/Monad/Error.hs, dist/build/Control/Monad/Error.o ) [10 of 21] Compiling Control.Monad.List ( Control/Monad/List.hs, dist/build/Control/Monad/List.o ) [11 of 21] Compiling Control.Monad.RWS.Lazy ( Control/Monad/RWS/Lazy.hs, dist/build/Control/Monad/RWS/Lazy.o ) [12 of 21] Compiling Control.Monad.RWS ( Control/Monad/RWS.hs, dist/build/Control/Monad/RWS.o ) [13 of 21] Compiling Control.Monad.Reader ( Control/Monad/Reader.hs, dist/build/Control/Monad/Reader.o ) [14 of 21] Compiling Control.Monad.RWS.Strict ( Control/Monad/RWS/Strict.hs, dist/build/Control/Monad/RWS/Strict.o ) [15 of 21] Compiling Control.Monad.State.Lazy ( Control/Monad/State/Lazy.hs, dist/build/Control/Monad/State/Lazy.o ) [16 of 21] Compiling Control.Monad.State ( Control/Monad/State.hs, dist/build/Control/Monad/State.o ) [17 of 21] Compiling Control.Monad.State.Strict ( Control/Monad/State/Strict.hs, dist/build/Control/Monad/State/Strict.o ) [18 of 21] Compiling Control.Monad.Writer.Lazy ( Control/Monad/Writer/Lazy.hs, dist/build/Control/Monad/Writer/Lazy.o ) [19 of 21] Compiling Control.Monad.Writer ( Control/Monad/Writer.hs, dist/build/Control/Monad/Writer.o ) [20 of 21] Compiling Control.Monad.Writer.Strict ( Control/Monad/Writer/Strict.hs, dist/build/Control/Monad/Writer/Strict.o ) [21 of 21] Compiling Control.Monad.Cont ( Control/Monad/Cont.hs, dist/build/Control/Monad/Cont.o ) Registering mtl-2.0.1.0... Running Haddock for mtl-2.0.1.0... cabal: Haddock's internal GHC version must match the configured GHC version. The GHC version is 7.3.20111121 but haddock is using GHC version 7.0.4 Installing library in /home/blackh/.cabal/lib/mtl-2.0.1.0/ghc-7.3.20111121 Registering mtl-2.0.1.0... blackh@amentet:~/src/haskell$ arm-ldu-linux-gnueabi-ghc-pkg list /usr/local/ghc-ldu/lib/ghc-7.3.20111121/package.conf.d: Cabal-1.13.3 array-0.3.0.3 base-4.4.0.0 bin-package-db-0.0.0.0 binary-0.5.0.2 bytestring-0.9.2.0 containers-0.4.2.0 deepseq-1.2.0.1 directory-1.1.0.1 extensible-exceptions-0.1.1.3 filepath-1.2.0.1 ghc-prim-0.2.0.0 hoopl-3.8.7.2 hpc-0.5.1.0 integer-gmp-0.3.0.0 old-locale-1.0.0.3 old-time-1.0.0.7 pretty-1.1.0.0 process-1.1.0.0 rts-1.0 template-haskell-2.6.0.0 time-1.4 unix-2.5.0.0 /home/blackh/.ghc/arm-linux-7.3.20111121/package.conf.d: mtl-2.0.1.0 transformers-0.2.2.0 blackh@amentet:~/src/haskell$ arm-ldu-linux-gnueabi-ghc reverse.hs [1 of 1] Compiling Main ( reverse.hs, reverse.o ) Linking reverse ... blackh@amentet:~/src/haskell$ file reverse reverse: ELF 32-bit LSB executable, ARM, version 1 (SYSV), dynamically linked (uses shared libs), for GNU/Linux 2.6.18, not stripped blackh@amentet:~/src/haskell$ ~/src/ghc/alien run ./reverse end 5 4 3 2 1 start blackh@amentet:~/src/haskell$