From bc0cd2243343c093127c3b893cb2d9b72a33830d Mon Sep 17 00:00:00 2001
From: Julian Ospald <hasufell@posteo.de>
Date: Sat, 25 Apr 2020 12:06:41 +0200
Subject: [PATCH] First cross try

---
 app/ghcup-gen/Validate.hs     |  18 ++-
 app/ghcup/Main.hs             | 133 +++++++++++--------
 ghcup.cabal                   |   6 +-
 lib/GHCup.hs                  | 211 +++++++++++++++++++----------
 lib/GHCup/Errors.hs           |   5 +-
 lib/GHCup/Types.hs            |  23 +++-
 lib/GHCup/Types/JSON.hs       |  18 +--
 lib/GHCup/Types/Optics.hs     |   2 +
 lib/GHCup/Utils.hs            | 241 ++++++++++++++++++++--------------
 lib/GHCup/Utils/Dirs.hs       |  25 +++-
 lib/GHCup/Utils/File.hs       |  30 +++++
 lib/GHCup/Utils/MegaParsec.hs |  87 ++++++++++++
 lib/GHCup/Utils/Prelude.hs    |   6 +
 13 files changed, 556 insertions(+), 249 deletions(-)
 create mode 100644 lib/GHCup/Utils/MegaParsec.hs

diff --git a/app/ghcup-gen/Validate.hs b/app/ghcup-gen/Validate.hs
index 53ef3674..c1621490 100644
--- a/app/ghcup-gen/Validate.hs
+++ b/app/ghcup-gen/Validate.hs
@@ -27,9 +27,12 @@ import           Haskus.Utils.Variant.Excepts
 import           Optics
 import           System.Exit
 import           System.IO
+import           Text.ParserCombinators.ReadP
 
 import qualified Data.ByteString               as B
 import qualified Data.Map.Strict               as M
+import qualified Data.Text                     as T
+import qualified Data.Version                  as V
 
 
 data ValidationError = InternalError String
@@ -61,7 +64,7 @@ validate dls = do
         forM_ (M.toList $ _viArch vi) $ \(arch, pspecs) -> do
           checkHasRequiredPlatforms t v arch (M.keys pspecs)
 
-    checkGHCisSemver
+    checkGHCVerIsValid
     forM_ (M.toList dls) $ \(t, _) -> checkMandatoryTags t
     _ <- checkGHCHasBaseVersion
 
@@ -111,13 +114,14 @@ validate dls = do
     isUniqueTag (Base       _) = False
     isUniqueTag (UnknownTag _) = False
 
-  checkGHCisSemver = do
+  checkGHCVerIsValid = do
     let ghcVers = toListOf (ix GHC % to M.keys % folded) dls
-    forM_ ghcVers $ \v -> case semver (prettyVer v) of
-      Left _ -> do
-        lift $ $(logError) [i|GHC version #{v} is not valid semver|]
-        addError
-      Right _ -> pure ()
+    forM_ ghcVers $ \v ->
+      case [ x | (x,"") <- readP_to_S V.parseVersion (T.unpack . prettyVer $ v) ] of
+        [_] -> pure ()
+        _   -> do
+          lift $ $(logError) [i|GHC version #{v} is not valid |]
+          addError
 
   -- a tool must have at least one of each mandatory tags
   checkMandatoryTags tool = do
diff --git a/app/ghcup/Main.hs b/app/ghcup/Main.hs
index ec05a907..f591fd69 100644
--- a/app/ghcup/Main.hs
+++ b/app/ghcup/Main.hs
@@ -19,6 +19,7 @@ import           GHCup.Types
 import           GHCup.Utils
 import           GHCup.Utils.File
 import           GHCup.Utils.Logger
+import           GHCup.Utils.MegaParsec
 import           GHCup.Utils.Prelude
 import           GHCup.Version
 
@@ -37,7 +38,7 @@ import           Data.List.NonEmpty             (NonEmpty ((:|)))
 import           Data.Maybe
 import           Data.String.Interpolate
 import           Data.Text                      ( Text )
-import           Data.Versions
+import           Data.Versions           hiding ( str )
 import           Data.Void
 import           GHC.IO.Encoding
 import           Haskus.Utils.Variant.Excepts
@@ -91,11 +92,11 @@ data Command
   | ToolRequirements
   | ChangeLog ChangeLogOptions
 
-data ToolVersion = ToolVersion Version
+data ToolVersion = ToolVersion GHCTargetVersion -- target is ignored for cabal
                  | ToolTag Tag
 
 prettyToolVer :: ToolVersion -> String
-prettyToolVer (ToolVersion v') = T.unpack $ prettyVer v'
+prettyToolVer (ToolVersion v') = T.unpack $ prettyTVer v'
 prettyToolVer (ToolTag t) = show t
 
 
@@ -115,15 +116,25 @@ data ListOptions = ListOptions
   }
 
 data RmOptions = RmOptions
-  { ghcVer :: Version
+  { ghcVer :: GHCTargetVersion
   }
 
 
-data CompileCommand = CompileGHC CompileOptions
-                    | CompileCabal CompileOptions
+data CompileCommand = CompileGHC GHCCompileOptions
+                    | CompileCabal CabalCompileOptions
 
 
-data CompileOptions = CompileOptions
+data GHCCompileOptions = GHCCompileOptions
+  { targetVer    :: Version
+  , bootstrapGhc :: Either Version (Path Abs)
+  , jobs         :: Maybe Int
+  , buildConfig  :: Maybe (Path Abs)
+  , patchDir     :: Maybe (Path Abs)
+  , crossTarget  :: Maybe Text
+  , addConfArgs  :: [Text]
+  }
+
+data CabalCompileOptions = CabalCompileOptions
   { targetVer    :: Version
   , bootstrapGhc :: Either Version (Path Abs)
   , jobs         :: Maybe Int
@@ -359,7 +370,7 @@ compileP = subparser
       "ghc"
       (   CompileGHC
       <$> (info
-            (compileOpts <**> helper)
+            (ghcCompileOpts <**> helper)
             (  progDesc "Compile GHC from source"
             <> footerDoc (Just $ text compileFooter)
             )
@@ -369,7 +380,7 @@ compileP = subparser
        "cabal"
        (   CompileCabal
        <$> (info
-             (compileOpts <**> helper)
+             (cabalCompileOpts <**> helper)
              (  progDesc "Compile Cabal from source"
              <> footerDoc (Just $ text compileCabalFooter)
              )
@@ -382,9 +393,19 @@ compileP = subparser
   a self-contained "~/.ghcup/ghc/<ghcver>" directory
   and symlinks the ghc binaries to "~/.ghcup/bin/<binary>-<ghcver>".
 
+  This also allows building a cross-compiler. Consult the documentation
+  first: <https://gitlab.haskell.org/ghc/ghc/-/wikis/building/cross-compiling#configuring-the-build>
+
+ENV variables:
+  Various toolchain variables will be passed onto the ghc build system,
+  such as: CC, LD, OBJDUMP, NM, AR, RANLIB.
+
 Examples:
   ghcup compile ghc -j 4 -v 8.4.2 -b 8.2.2
-  ghcup compile ghc -j 4 -v 8.4.2 -b /usr/bin/ghc-8.2.2|]
+  # specify path to bootstrap ghc
+  ghcup compile ghc -j 4 -v 8.4.2 -b /usr/bin/ghc-8.2.2
+  # build cross compiler
+  ghcup compile ghc -j 4 -v 8.4.2 -b 8.2.2 -x armv7-unknown-linux-gnueabihf --config $(pwd)/build.mk -- --enable-unregisterised|]
   compileCabalFooter = [i|Discussion:
   Compiles and installs the specified Cabal version
   into "~/.ghcup/bin".
@@ -394,10 +415,24 @@ Examples:
   ghcup compile cabal -j 4 -v 3.2.0.0 -b /usr/bin/ghc-8.6.5|]
 
 
+ghcCompileOpts :: Parser GHCCompileOptions
+ghcCompileOpts =
+  (\CabalCompileOptions {..} crossTarget addConfArgs -> GHCCompileOptions { .. }
+    )
+    <$> cabalCompileOpts
+    <*> (optional
+          (option
+            str
+            (short 'x' <> long "cross-target" <> metavar "CROSS_TARGET" <> help
+              "Build cross-compiler for this platform"
+            )
+          )
+        )
+    <*> many (argument str (metavar "CONFIGURE_ARGS" <> help "Additional arguments to configure, prefix with '-- ' (longopts)"))
 
-compileOpts :: Parser CompileOptions
-compileOpts =
-  CompileOptions
+cabalCompileOpts :: Parser CabalCompileOptions
+cabalCompileOpts =
+  CabalCompileOptions
     <$> (option
           (eitherReader
             (bimap (const "Not a valid version") id . version . T.pack)
@@ -472,12 +507,12 @@ toolVersionArgument =
   argument (eitherReader toolVersionEither) (metavar "VERSION|TAG")
 
 
-versionArgument :: Parser Version
-versionArgument = argument (eitherReader versionEither) (metavar "VERSION")
+versionArgument :: Parser GHCTargetVersion
+versionArgument = argument (eitherReader tVersionEither) (metavar "VERSION")
 
-versionParser :: Parser Version
+versionParser :: Parser GHCTargetVersion
 versionParser = option
-  (eitherReader versionEither)
+  (eitherReader tVersionEither)
   (short 'v' <> long "version" <> metavar "VERSION" <> help "The target version"
   )
 
@@ -490,16 +525,15 @@ tagEither s' = case fmap toLower s' of
                                   Left  _ -> Left [i|Invalid PVP version for base #{ver'}|]
   other         -> Left ([i|Unknown tag #{other}|])
 
-versionEither :: String -> Either String Version
-versionEither s' =
-  -- 'version' is a bit too lax and will parse typoed tags
-                   case readMaybe ((: []) . head $ s') :: Maybe Int of
-  Just _  -> bimap (const "Not a valid version") id . version . T.pack $ s'
-  Nothing -> Left "Not a valid version"
+
+tVersionEither :: String -> Either String GHCTargetVersion
+tVersionEither =
+  bimap (const "Not a valid version") id . MP.parse ghcTargetVerP "" . T.pack
+
 
 toolVersionEither :: String -> Either String ToolVersion
 toolVersionEither s' =
-  bimap id ToolTag (tagEither s') <|> bimap id ToolVersion (versionEither s')
+  bimap id ToolTag (tagEither s') <|> bimap id ToolVersion (tVersionEither s')
 
 
 toolParser :: String -> Either String Tool
@@ -583,18 +617,7 @@ platformParser s' = case MP.parse (platformP <* MP.eof) "" (T.pack s') of
         MP.setInput rest
         pure v
 
-  choice' []       = fail "Empty list"
-  choice' [x     ] = x
-  choice' (x : xs) = MP.try x <|> choice' xs
-
-  parseUntil :: MP.Parsec Void Text Text -> MP.Parsec Void Text Text
-  parseUntil p = do
-    (MP.try (MP.lookAhead p) $> mempty)
-      <|> (do
-            c  <- T.singleton <$> MP.anySingle
-            c2 <- parseUntil p
-            pure (c `mappend` c2)
-          )
+
 
 
 toSettings :: Options -> Settings
@@ -805,7 +828,7 @@ Report bugs at <https://gitlab.haskell.org/haskell/ghcup-hs/issues>|]
             Install (InstallOptions {..}) ->
               (runInstTool $ do
                   v <- liftE $ fromVersion dls instVer GHC
-                  liftE $ installGHCBin dls v instPlatform
+                  liftE $ installGHCBin dls (_tvVersion v) instPlatform -- FIXME: ugly sharing of tool version
                 )
                 >>= \case
                       VRight _ -> do
@@ -837,7 +860,7 @@ Make sure to clean up #{tmpdir} afterwards.|])
             InstallCabal (InstallOptions {..}) ->
               (runInstTool $ do
                   v <- liftE $ fromVersion dls instVer Cabal
-                  liftE $ installCabalBin dls v instPlatform
+                  liftE $ installCabalBin dls (_tvVersion v) instPlatform -- FIXME: ugly sharing of tool version
                 )
                 >>= \case
                       VRight _ -> do
@@ -866,10 +889,10 @@ Make sure to clean up #{tmpdir} afterwards.|])
                   liftE $ setGHC v SetGHCOnly
                 )
                 >>= \case
-                      VRight v -> do
+                      VRight (GHCTargetVersion{..}) -> do
                         runLogger
                           $ $(logInfo)
-                              [i|GHC #{prettyVer v} successfully set as default version|]
+                              [i|GHC #{prettyVer _tvVersion} successfully set as default version#{maybe "" (" for cross target " <>) _tvTarget}|]
                         pure ExitSuccess
                       VLeft e -> do
                         runLogger ($(logError) [i|#{e}|])
@@ -909,13 +932,14 @@ Make sure to clean up #{tmpdir} afterwards.|])
                         runLogger ($(logError) [i|#{e}|])
                         pure $ ExitFailure 8
 
-            Compile (CompileGHC CompileOptions {..}) ->
+            Compile (CompileGHC GHCCompileOptions {..}) ->
               (runCompileGHC $ liftE $ compileGHC dls
-                                                  targetVer
+                                                  (GHCTargetVersion crossTarget targetVer)
                                                   bootstrapGhc
                                                   jobs
                                                   buildConfig
                                                   patchDir
+                                                  addConfArgs
                 )
                 >>= \case
                       VRight _ -> do
@@ -928,7 +952,8 @@ Make sure to clean up #{tmpdir} afterwards.|])
                         pure ExitSuccess
                       VLeft (V (BuildFailed tmpdir e)) -> do
                         case keepDirs of
-                          Never -> runLogger ($(logError) [i|Build failed with #{e}|])
+                          Never -> runLogger ($(logError) [i|Build failed with #{e}
+Check the logs at ~/.ghcup/logs|])
                           _ -> runLogger ($(logError) [i|Build failed with #{e}
 Check the logs at ~/.ghcup/logs and the build directory #{tmpdir} for more clues.
 Make sure to clean up #{tmpdir} afterwards.|])
@@ -937,7 +962,7 @@ Make sure to clean up #{tmpdir} afterwards.|])
                         runLogger ($(logError) [i|#{e}|])
                         pure $ ExitFailure 9
 
-            Compile (CompileCabal CompileOptions {..}) ->
+            Compile (CompileCabal CabalCompileOptions {..}) ->
               (runCompileCabal $ do
                   liftE $ compileCabal dls targetVer bootstrapGhc jobs patchDir
                 )
@@ -1008,7 +1033,7 @@ Make sure to clean up #{tmpdir} afterwards.|])
                   ver' = maybe
                     (Right Latest)
                     (\case
-                      ToolVersion tv -> Left tv
+                      ToolVersion tv -> Left (_tvVersion tv) -- FIXME: ugly sharing of ToolVersion
                       ToolTag     t  -> Right t
                     )
                     clToolVer
@@ -1045,23 +1070,23 @@ fromVersion :: Monad m
             => GHCupDownloads
             -> Maybe ToolVersion
             -> Tool
-            -> Excepts '[TagNotFound] m Version
+            -> Excepts '[TagNotFound] m GHCTargetVersion
 fromVersion av Nothing tool =
-  getRecommended av tool ?? TagNotFound Recommended tool
+  mkTVer <$> getRecommended av tool ?? TagNotFound Recommended tool
 fromVersion av (Just (ToolVersion v)) _ = do
-  case pvp $ prettyVer v of
+  case pvp $ prettyVer (_tvVersion v) of
     Left _ -> pure v
     Right (PVP (major' :|[minor'])) ->
       case getLatestGHCFor (fromIntegral major') (fromIntegral minor') av of
-        Just v' -> pure v'
+        Just v' -> pure $ GHCTargetVersion (_tvTarget v) v'
         Nothing -> pure v
     Right _ -> pure v
 fromVersion av (Just (ToolTag Latest)) tool =
-  getLatest av tool ?? TagNotFound Latest tool
+  mkTVer <$> getLatest av tool ?? TagNotFound Latest tool
 fromVersion av (Just (ToolTag Recommended)) tool =
-  getRecommended av tool ?? TagNotFound Recommended tool
+  mkTVer <$> getRecommended av tool ?? TagNotFound Recommended tool
 fromVersion av (Just (ToolTag (Base pvp''))) GHC =
-  getLatestBaseVersion av pvp'' ?? TagNotFound (Base pvp'') GHC
+  mkTVer <$> getLatestBaseVersion av pvp'' ?? TagNotFound (Base pvp'') GHC
 fromVersion _ (Just (ToolTag t')) tool =
   throwE $ TagNotFound t' tool
 
@@ -1093,7 +1118,9 @@ printListResult raw lr = do
                     | otherwise  -> (color Red "✗")
               in  (if raw then [] else [marks])
                     ++ [ fmap toLower . show $ lTool
-                       , T.unpack . prettyVer $ lVer
+                       , case lCross of
+                           Nothing -> T.unpack . prettyVer $ lVer
+                           Just c  -> T.unpack (c <> "-" <> prettyVer lVer)
                        , intercalate "," $ (fmap printTag $ sort lTag)
                        , intercalate ","
                        $  (if fromSrc then [color' Blue "compiled"] else mempty)
diff --git a/ghcup.cabal b/ghcup.cabal
index e616f6e0..d286c982 100644
--- a/ghcup.cabal
+++ b/ghcup.cabal
@@ -41,9 +41,6 @@ common ascii-string
 common async
   build-depends: async >=0.8
 
-common attoparsec
-  build-depends: attoparsec >=0.13
-
 common base
   build-depends: base >=4.12 && <5
 
@@ -230,7 +227,6 @@ library
     , aeson
     , ascii-string
     , async
-    , attoparsec
     , binary
     , bytestring
     , bz2
@@ -248,6 +244,7 @@ library
     , hpath-posix
     , language-bash
     , lzma
+    , megaparsec
     , monad-logger
     , mtl
     , optics
@@ -295,6 +292,7 @@ library
     GHCup.Utils.Dirs
     GHCup.Utils.File
     GHCup.Utils.Logger
+    GHCup.Utils.MegaParsec
     GHCup.Utils.Prelude
     GHCup.Utils.String.QQ
     GHCup.Utils.Version.QQ
diff --git a/lib/GHCup.hs b/lib/GHCup.hs
index c448932f..967dd942 100644
--- a/lib/GHCup.hs
+++ b/lib/GHCup.hs
@@ -41,6 +41,7 @@ import           Data.ByteString                ( ByteString )
 import           Data.List
 import           Data.Maybe
 import           Data.String.Interpolate
+import           Data.Text                      ( Text )
 import           Data.Versions
 import           Data.Word8
 import           GHC.IO.Exception
@@ -53,11 +54,14 @@ import           Prelude                 hiding ( abs
                                                 , writeFile
                                                 )
 import           System.IO.Error
+import           System.Posix.Env.ByteString    ( getEnvironment )
 import           System.Posix.FilePath          ( getSearchPath )
 import           System.Posix.Files.ByteString
 
 import qualified Data.ByteString               as B
+import qualified Data.ByteString.Lazy          as BL
 import qualified Data.Map.Strict               as Map
+import qualified Data.Text                     as T
 import qualified Data.Text.Encoding            as E
 
 
@@ -94,8 +98,9 @@ installGHCBin :: ( MonadFail m
                    m
                    ()
 installGHCBin bDls ver mpfReq = do
+  let tver = (mkTVer ver)
   lift $ $(logDebug) [i|Requested to install GHC with #{ver}|]
-  whenM (liftIO $ toolAlreadyInstalled GHC ver)
+  whenM (liftIO $ ghcInstalled tver)
     $ (throwE $ AlreadyInstalled GHC ver)
   Settings {..}                <- lift ask
   pfreq@(PlatformRequest {..}) <- maybe (liftE $ platformRequest) pure mpfReq
@@ -110,14 +115,14 @@ installGHCBin bDls ver mpfReq = do
   void $ liftIO $ darwinNotarization _rPlatform tmpUnpack
 
   -- prepare paths
-  ghcdir <- liftIO $ ghcupGHCDir ver
+  ghcdir <- liftIO $ ghcupGHCDir tver
 
   -- the subdir of the archive where we do the work
   let workdir = maybe tmpUnpack (tmpUnpack </>) (view dlSubdir dlinfo)
 
   liftE $ runBuildAction tmpUnpack (Just ghcdir) (installGHC' workdir ghcdir)
 
-  liftE $ postGHCInstall ver
+  liftE $ postGHCInstall tver
 
  where
   -- | Install an unpacked GHC distribution. This only deals with the GHC build system and nothing else.
@@ -161,15 +166,15 @@ installCabalBin :: ( MonadMask m
                      ()
 installCabalBin bDls ver mpfReq = do
   lift $ $(logDebug) [i|Requested to install cabal version #{ver}|]
-  Settings {..} <- lift ask
+  Settings {..}                <- lift ask
   pfreq@(PlatformRequest {..}) <- maybe (liftE $ platformRequest) pure mpfReq
 
   -- download (or use cached version)
-  dlinfo        <- lE $ getDownloadInfo Cabal ver pfreq bDls
-  dl            <- liftE $ downloadCached dlinfo Nothing
+  dlinfo                       <- lE $ getDownloadInfo Cabal ver pfreq bDls
+  dl                           <- liftE $ downloadCached dlinfo Nothing
 
   -- unpack
-  tmpUnpack     <- lift withGHCupTmpDir
+  tmpUnpack                    <- lift withGHCupTmpDir
   liftE $ unpackToDir tmpUnpack dl
   void $ liftIO $ darwinNotarization _rPlatform tmpUnpack
 
@@ -215,11 +220,11 @@ installCabalBin bDls ver mpfReq = do
 -- Additionally creates a ~/.ghcup/share -> ~/.ghcup/ghc/<ver>/share symlink
 -- for `SetGHCOnly` constructor.
 setGHC :: (MonadLogger m, MonadThrow m, MonadFail m, MonadIO m)
-       => Version
+       => GHCTargetVersion
        -> SetGHC
-       -> Excepts '[NotInstalled] m Version
+       -> Excepts '[NotInstalled] m GHCTargetVersion
 setGHC ver sghc = do
-  let verBS = verToBS ver
+  let verBS = verToBS (_tvVersion ver)
   ghcdir <- liftIO $ ghcupGHCDir ver
 
   -- symlink destination
@@ -229,7 +234,7 @@ setGHC ver sghc = do
   -- first delete the old symlinks (this fixes compatibility issues
   -- with old ghcup)
   case sghc of
-    SetGHCOnly -> liftE $ rmPlain ver
+    SetGHCOnly -> liftE $ rmPlain (_tvTarget ver)
     SetGHC_XY  -> lift $ rmMajorSymlinks ver
     SetGHC_XYZ -> lift $ rmMinorSymlinks ver
 
@@ -239,9 +244,8 @@ setGHC ver sghc = do
     targetFile <- case sghc of
       SetGHCOnly -> pure file
       SetGHC_XY  -> do
-        major' <-
-          (\(mj, mi) -> E.encodeUtf8 $ intToText mj <> "." <> intToText mi)
-            <$> getGHCMajor ver
+        major' <- (\(mj, mi) -> E.encodeUtf8 $ intToText mj <> "." <> intToText mi)
+                     <$> getMajorMinorV (_tvVersion ver)
         parseRel (toFilePath file <> B.singleton _hyphen <> major')
       SetGHC_XYZ -> parseRel (toFilePath file <> B.singleton _hyphen <> verBS)
 
@@ -252,7 +256,7 @@ setGHC ver sghc = do
     liftIO $ createSymlink fullF destL
 
   -- create symlink for share dir
-  lift $ symlinkShareDir ghcdir verBS
+  when (isNothing . _tvTarget $ ver) $ lift $ symlinkShareDir ghcdir verBS
 
   pure ver
 
@@ -292,6 +296,7 @@ data ListCriteria = ListInstalled
 data ListResult = ListResult
   { lTool      :: Tool
   , lVer       :: Version
+  , lCross     :: Maybe Text -- ^ currently only for GHC
   , lTag       :: [Tag]
   , lInstalled :: Bool
   , lSet       :: Bool -- ^ currently active version
@@ -309,7 +314,7 @@ availableToolVersions av tool = view
 
 -- | List all versions from the download info, as well as stray
 -- versions.
-listVersions :: (MonadLogger m, MonadIO m)
+listVersions :: (MonadThrow m, MonadLogger m, MonadIO m)
              => GHCupDownloads
              -> Maybe Tool
              -> Maybe ListCriteria
@@ -333,44 +338,58 @@ listVersions av lt criteria = case lt of
     pure (ghcvers <> cabalvers <> ghcupvers)
 
  where
-  strayGHCs :: (MonadLogger m, MonadIO m)
+  strayGHCs :: (MonadThrow m, MonadLogger m, MonadIO m)
             => Map.Map Version [Tag]
             -> m [ListResult]
   strayGHCs avTools = do
-    ghcdir <- liftIO $ ghcupGHCBaseDir
-    fs     <- liftIO $ liftIO $ hideErrorDef [NoSuchThing] [] $ getDirsFiles' ghcdir
-    fmap catMaybes $ forM fs $ \(toFilePath -> f) -> do
-      case version . decUTF8Safe $ f of
-        Right v' -> do
-          case Map.lookup v' avTools of
-            Just _  -> pure Nothing
-            Nothing -> do
-              lSet    <- fmap (maybe False (== v')) $ ghcSet
-              fromSrc <- liftIO $ ghcSrcInstalled v'
-              pure $ Just $ ListResult
-                { lTool      = GHC
-                , lVer       = v'
-                , lTag       = []
-                , lInstalled = True
-                , lStray     = maybe True (const False) (Map.lookup v' avTools)
-                , ..
-                }
-        Left e -> do
-          $(logWarn)
-            [i|Could not parse version of stray directory #{toFilePath ghcdir}/#{f}: #{e}|]
-          pure Nothing
-
+    ghcs <- getInstalledGHCs
+    fmap catMaybes $ forM ghcs $ \case
+      Right tver@GHCTargetVersion{ _tvTarget = Nothing, .. } -> do
+        case Map.lookup _tvVersion avTools of
+          Just _  -> pure Nothing
+          Nothing -> do
+            lSet    <- fmap (maybe False (\(GHCTargetVersion _ v ) -> v == _tvVersion)) $ ghcSet Nothing
+            fromSrc <- liftIO $ ghcSrcInstalled tver
+            pure $ Just $ ListResult
+              { lTool      = GHC
+              , lVer       = _tvVersion
+              , lCross     = Nothing
+              , lTag       = []
+              , lInstalled = True
+              , lStray     = maybe True (const False) (Map.lookup _tvVersion avTools)
+              , ..
+              }
+      Right tver@GHCTargetVersion{ .. } -> do
+        lSet    <- fmap (maybe False (\(GHCTargetVersion _ v ) -> v == _tvVersion)) $ ghcSet _tvTarget
+        fromSrc <- liftIO $ ghcSrcInstalled tver
+        pure $ Just $ ListResult
+          { lTool      = GHC
+          , lVer       = _tvVersion
+          , lCross     = _tvTarget
+          , lTag       = []
+          , lInstalled = True
+          , lStray     = True -- NOTE: cross currently cannot be installed via bindist
+          , ..
+          }
+      Left e -> do
+        $(logWarn)
+          [i|Could not parse version of stray directory #{toFilePath e}|]
+        pure Nothing
+
+  -- NOTE: this are not cross ones, because no bindists
   toListResult :: Tool -> (Version, [Tag]) -> IO ListResult
   toListResult t (v, tags) = case t of
     GHC -> do
-      lSet       <- fmap (maybe False (== v)) $ ghcSet
-      lInstalled <- ghcInstalled v
-      fromSrc    <- ghcSrcInstalled v
-      pure ListResult { lVer = v, lTag = tags, lTool = t, lStray = False, .. }
+      let tver = mkTVer v
+      lSet       <- fmap (maybe False (\(GHCTargetVersion _ v') -> v' == v)) $ ghcSet Nothing
+      lInstalled <- ghcInstalled tver
+      fromSrc    <- ghcSrcInstalled tver
+      pure ListResult { lVer = v, lCross = Nothing , lTag = tags, lTool = t, lStray = False, .. }
     Cabal -> do
       lSet <- fmap (== v) $ cabalSet
       let lInstalled = lSet
       pure ListResult { lVer    = v
+                      , lCross  = Nothing
                       , lTag    = tags
                       , lTool   = t
                       , fromSrc = False
@@ -382,6 +401,7 @@ listVersions av lt criteria = case lt of
       let lInstalled = lSet
       pure ListResult { lVer    = v
                       , lTag    = tags
+                      , lCross  = Nothing
                       , lTool   = t
                       , fromSrc = False
                       , lStray  = False
@@ -404,10 +424,10 @@ listVersions av lt criteria = case lt of
 
 -- | This function may throw and crash in various ways.
 rmGHCVer :: (MonadThrow m, MonadLogger m, MonadIO m, MonadFail m)
-         => Version
+         => GHCTargetVersion
          -> Excepts '[NotInstalled] m ()
 rmGHCVer ver = do
-  isSetGHC <- fmap (maybe False (== ver)) $ ghcSet
+  isSetGHC <- fmap (maybe False (== ver)) $ ghcSet (_tvTarget ver)
   dir      <- liftIO $ ghcupGHCDir ver
   let d' = toFilePath dir
   exists <- liftIO $ doesDirectoryExist dir
@@ -418,7 +438,7 @@ rmGHCVer ver = do
       -- this isn't atomic, order matters
       when isSetGHC $ do
         lift $ $(logInfo) [i|Removing ghc symlinks|]
-        liftE $ rmPlain ver
+        liftE $ rmPlain (_tvTarget ver)
 
       lift $ $(logInfo) [i|Removing directory recursively: #{d'}|]
       liftIO $ deleteDirRecursive dir
@@ -430,15 +450,15 @@ rmGHCVer ver = do
       -- first remove
       lift $ rmMajorSymlinks ver
       -- then fix them (e.g. with an earlier version)
-      (mj, mi) <- getGHCMajor ver
-      getGHCForMajor mj mi >>= mapM_ (\v -> liftE $ setGHC v SetGHC_XY)
+      (mj, mi) <- getMajorMinorV (_tvVersion ver)
+      getGHCForMajor mj mi (_tvTarget ver) >>= mapM_ (\v -> liftE $ setGHC v SetGHC_XY)
 
       liftIO
         $   ghcupBaseDir
         >>= hideError doesNotExistErrorType
         .   deleteFile
         .   (</> [rel|share|])
-    else throwE (NotInstalled GHC ver)
+    else throwE (NotInstalled GHC (ver ^. tvVersion % to prettyVer))
 
 
 
@@ -479,11 +499,12 @@ compileGHC :: ( MonadMask m
               , MonadFail m
               )
            => GHCupDownloads
-           -> Version                    -- ^ version to install
+           -> GHCTargetVersion           -- ^ version to install
            -> Either Version (Path Abs)  -- ^ version to bootstrap with
            -> Maybe Int                  -- ^ jobs
            -> Maybe (Path Abs)           -- ^ build config
-           -> Maybe (Path Abs)
+           -> Maybe (Path Abs)           -- ^ patch directory
+           -> [Text]                     -- ^ additional args to ./configure
            -> Excepts
                 '[ AlreadyInstalled
                  , BuildFailed
@@ -500,13 +521,15 @@ compileGHC :: ( MonadMask m
                  ]
                 m
                 ()
-compileGHC dls tver bstrap jobs mbuildConfig patchdir = do
+compileGHC dls tver bstrap jobs mbuildConfig patchdir aargs = do
   lift $ $(logDebug) [i|Requested to compile: #{tver} with #{bstrap}|]
-  whenM (liftIO $ toolAlreadyInstalled GHC tver)
-        (throwE $ AlreadyInstalled GHC tver)
+  whenM (liftIO $ ghcInstalled tver)
+        (throwE $ AlreadyInstalled GHC (tver ^. tvVersion))
 
   -- download source tarball
-  dlInfo    <- preview (ix GHC % ix tver % viSourceDL % _Just) dls ?? NoDownload
+  dlInfo <-
+    preview (ix GHC % ix (tver ^. tvVersion) % viSourceDL % _Just) dls
+      ?? NoDownload
   dl        <- liftE $ downloadCached dlInfo Nothing
 
   -- unpack
@@ -530,13 +553,20 @@ compileGHC dls tver bstrap jobs mbuildConfig patchdir = do
   pure ()
 
  where
-  defaultConf = [s|
+  defaultConf = case _tvTarget tver of
+                  Nothing -> [s|
+V=0
+BUILD_MAN = NO
+BUILD_SPHINX_HTML = NO
+BUILD_SPHINX_PDF = NO
+HADDOCK_DOCS = YES|]
+                  Just _ -> [s|
 V=0
 BUILD_MAN = NO
 BUILD_SPHINX_HTML = NO
 BUILD_SPHINX_PDF = NO
-HADDOCK_DOCS = YES
-GhcWithLlvmCodeGen = YES|]
+HADDOCK_DOCS = NO
+Stage1Only = YES|]
 
   compile :: (MonadCatch m, MonadLogger m, MonadIO m)
           => Either (Path Rel) (Path Abs)
@@ -544,6 +574,7 @@ GhcWithLlvmCodeGen = YES|]
           -> Path Abs
           -> Excepts
                '[ FileDoesNotExistError
+                , InvalidBuildConfig
                 , PatchFailed
                 , ProcessError
                 , NotFoundInPATH
@@ -552,14 +583,14 @@ GhcWithLlvmCodeGen = YES|]
                ()
   compile bghc ghcdir workdir = do
     lift $ $(logInfo) [i|configuring build|]
+    liftE $ checkBuildConfig
 
     forM_ patchdir $ \dir -> liftE $ applyPatches dir workdir
 
-    -- force ld.bfd for build (others seem to misbehave, like lld from FreeBSD)
-    newEnv <- addToCurrentEnv [("LD", "ld.bfd")]
+    cEnv <- liftIO $ getEnvironment
 
     if
-      | tver >= [vver|8.8.0|] -> do
+      | (_tvVersion tver) >= [vver|8.8.0|] -> do
         bghcPath <- case bghc of
           Right ghc' -> pure ghc'
           Left  bver -> do
@@ -568,20 +599,32 @@ GhcWithLlvmCodeGen = YES|]
         lEM $ liftIO $ execLogged
           "./configure"
           False
-          ["--prefix=" <> toFilePath ghcdir]
+          (  ["--prefix=" <> toFilePath ghcdir]
+          ++ (maybe mempty
+                    (\x -> ["--target=" <> E.encodeUtf8 x])
+                    (_tvTarget tver)
+             )
+          ++ fmap E.encodeUtf8 aargs
+          )
           [rel|ghc-conf|]
           (Just workdir)
-          (Just (("GHC", toFilePath bghcPath) : newEnv))
+          (Just (("GHC", toFilePath bghcPath) : cEnv))
       | otherwise -> do
         lEM $ liftIO $ execLogged
           "./configure"
           False
-          [ "--prefix=" <> toFilePath ghcdir
-          , "--with-ghc=" <> either toFilePath toFilePath bghc
-          ]
+          (  [ "--prefix=" <> toFilePath ghcdir
+             , "--with-ghc=" <> either toFilePath toFilePath bghc
+             ]
+          ++ (maybe mempty
+                    (\x -> ["--target=" <> E.encodeUtf8 x])
+                    (_tvTarget tver)
+             )
+          ++ fmap E.encodeUtf8 aargs
+          )
           [rel|ghc-conf|]
           (Just workdir)
-          (Just newEnv)
+          (Just cEnv)
 
     case mbuildConfig of
       Just bc -> liftIOException
@@ -604,6 +647,30 @@ GhcWithLlvmCodeGen = YES|]
 
   build_mk workdir = workdir </> [rel|mk/build.mk|]
 
+  checkBuildConfig :: (MonadCatch m, MonadIO m)
+                   => Excepts
+                        '[FileDoesNotExistError , InvalidBuildConfig]
+                        m
+                        ()
+  checkBuildConfig = do
+    c <- case mbuildConfig of
+      Just bc -> do
+        BL.toStrict <$> liftIOException doesNotExistErrorType
+                                        (FileDoesNotExistError $ toFilePath bc)
+                                        (liftIO $ readFile bc)
+      Nothing -> pure defaultConf
+    let lines' = fmap T.strip . T.lines $ decUTF8Safe c
+
+   -- for cross, we need Stage1Only
+    case _tvTarget tver of
+      Just _ -> when (not $ elem "Stage1Only = YES" lines') $ throwE
+        (InvalidBuildConfig
+          [s|Cross compiling needs to be a Stage1 build, add "Stage1Only = YES" to your config!|]
+        )
+      Nothing -> pure ()
+
+
+
 
 compileCabal :: ( MonadReader Settings m
                 , MonadResource m
@@ -763,12 +830,12 @@ upgradeGHCup dls mtarget force = do
 -- | Creates ghc-x.y.z and ghc-x.y symlinks. This is used for
 -- both installing from source and bindist.
 postGHCInstall :: (MonadLogger m, MonadThrow m, MonadFail m, MonadIO m)
-               => Version
+               => GHCTargetVersion
                -> Excepts '[NotInstalled] m ()
-postGHCInstall ver = do
+postGHCInstall ver@GHCTargetVersion{..} = do
   void $ liftE $ setGHC ver SetGHC_XYZ
 
   -- Create ghc-x.y symlinks. This may not be the current
   -- version, create it regardless.
-  (mj, mi) <- liftIO $ getGHCMajor ver
-  getGHCForMajor mj mi >>= mapM_ (\v -> liftE $ setGHC v SetGHC_XY)
+  (mj, mi) <- getMajorMinorV _tvVersion
+  getGHCForMajor mj mi _tvTarget >>= mapM_ (\v -> liftE $ setGHC v SetGHC_XY)
diff --git a/lib/GHCup/Errors.hs b/lib/GHCup/Errors.hs
index 9046c1c0..d963de80 100644
--- a/lib/GHCup/Errors.hs
+++ b/lib/GHCup/Errors.hs
@@ -64,7 +64,7 @@ data AlreadyInstalled = AlreadyInstalled Tool Version
 
 -- | The tool is not installed. Some operations rely on a tool
 -- to be installed (such as setting the current GHC version).
-data NotInstalled = NotInstalled Tool Version
+data NotInstalled = NotInstalled Tool Text
   deriving Show
 
 -- | An executable was expected to be in PATH, but was not found.
@@ -104,6 +104,9 @@ data PatchFailed = PatchFailed
 data NoToolRequirements = NoToolRequirements
   deriving Show
 
+data InvalidBuildConfig = InvalidBuildConfig Text
+  deriving Show
+
 
     -------------------------
     --[ High-level errors ]--
diff --git a/lib/GHCup/Types.hs b/lib/GHCup/Types.hs
index e5c8338e..6074b948 100644
--- a/lib/GHCup/Types.hs
+++ b/lib/GHCup/Types.hs
@@ -1,4 +1,5 @@
-{-# LANGUAGE DeriveGeneric #-}
+{-# LANGUAGE DeriveGeneric     #-}
+{-# LANGUAGE OverloadedStrings #-}
 
 module GHCup.Types where
 
@@ -182,3 +183,23 @@ data PlatformRequest = PlatformRequest
   , _rVersion  :: Maybe Versioning
   }
   deriving (Eq, Show)
+
+
+-- | A GHC identified by the target platform triple
+-- and the version.
+data GHCTargetVersion = GHCTargetVersion
+  { _tvTarget  :: Maybe Text
+  , _tvVersion :: Version
+  }
+  deriving (Ord, Eq, Show)
+
+
+mkTVer :: Version -> GHCTargetVersion
+mkTVer = GHCTargetVersion Nothing
+
+
+-- | Assembles a path of the form: <target-triple>-<version>
+prettyTVer :: GHCTargetVersion -> Text
+prettyTVer (GHCTargetVersion (Just t) v') = t <> "-" <> prettyVer v'
+prettyTVer (GHCTargetVersion Nothing  v') = prettyVer v'
+
diff --git a/lib/GHCup/Types/JSON.hs b/lib/GHCup/Types/JSON.hs
index 4607294b..b1e52d6a 100644
--- a/lib/GHCup/Types/JSON.hs
+++ b/lib/GHCup/Types/JSON.hs
@@ -42,18 +42,18 @@ deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''GHCupI
 deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''Requirements
 
 instance ToJSON Tag where
-  toJSON Latest = String "Latest"
-  toJSON Recommended = String "Recommended"
-  toJSON (Base pvp'') = String ("base-" <> prettyPVP pvp'')
-  toJSON (UnknownTag x) = String (T.pack x)
+  toJSON Latest             = String "Latest"
+  toJSON Recommended        = String "Recommended"
+  toJSON (Base       pvp'') = String ("base-" <> prettyPVP pvp'')
+  toJSON (UnknownTag x    ) = String (T.pack x)
 
 instance FromJSON Tag where
   parseJSON = withText "Tag" $ \t -> case T.unpack t of
-    "Latest" -> pure Latest
-    "Recommended" -> pure Recommended
-    ('b':'a':'s':'e':'-':ver') -> case pvp (T.pack ver') of
-                                    Right x -> pure $ Base x
-                                    Left e -> fail . show $ e
+    "Latest"                             -> pure Latest
+    "Recommended"                        -> pure Recommended
+    ('b' : 'a' : 's' : 'e' : '-' : ver') -> case pvp (T.pack ver') of
+      Right x -> pure $ Base x
+      Left  e -> fail . show $ e
     x -> pure (UnknownTag x)
 
 instance ToJSON URI where
diff --git a/lib/GHCup/Types/Optics.hs b/lib/GHCup/Types/Optics.hs
index 4dcd22f6..97951967 100644
--- a/lib/GHCup/Types/Optics.hs
+++ b/lib/GHCup/Types/Optics.hs
@@ -19,6 +19,8 @@ makeLenses ''DownloadInfo
 makeLenses ''Tag
 makeLenses ''VersionInfo
 
+makeLenses ''GHCTargetVersion
+
 makeLenses ''GHCupInfo
 
 uriSchemeL' :: Lens' (URIRef Absolute) Scheme
diff --git a/lib/GHCup/Utils.hs b/lib/GHCup/Utils.hs
index 9ebe964d..69dc6864 100644
--- a/lib/GHCup/Utils.hs
+++ b/lib/GHCup/Utils.hs
@@ -4,6 +4,7 @@
 {-# LANGUAGE OverloadedStrings     #-}
 {-# LANGUAGE QuasiQuotes           #-}
 {-# LANGUAGE TemplateHaskell       #-}
+{-# LANGUAGE ViewPatterns          #-}
 
 
 module GHCup.Utils
@@ -19,7 +20,9 @@ import           GHCup.Types.Optics
 import           GHCup.Types.JSON               ( )
 import           GHCup.Utils.Dirs
 import           GHCup.Utils.File
+import           GHCup.Utils.MegaParsec
 import           GHCup.Utils.Prelude
+import           GHCup.Utils.String.QQ
 
 import           Control.Applicative
 import           Control.Exception.Safe
@@ -29,11 +32,12 @@ import           Control.Monad.Fail             ( MonadFail )
 #endif
 import           Control.Monad.Logger
 import           Control.Monad.Reader
-import           Data.Attoparsec.ByteString
 import           Data.ByteString                ( ByteString )
+import           Data.Either
 import           Data.List
 import           Data.Maybe
 import           Data.String.Interpolate
+import           Data.Text                      ( Text )
 import           Data.Versions
 import           Data.Word8
 import           GHC.IO.Exception
@@ -51,6 +55,7 @@ import           System.Posix.FilePath          ( getSearchPath
                                                 , takeFileName
                                                 )
 import           System.Posix.Files.ByteString  ( readSymbolicLink )
+import           Text.Regex.Posix
 import           URI.ByteString
 
 import qualified Codec.Archive.Tar             as Tar
@@ -60,7 +65,7 @@ import qualified Codec.Compression.Lzma        as Lzma
 import qualified Data.ByteString               as B
 import qualified Data.Map.Strict               as Map
 import qualified Data.Text.Encoding            as E
-
+import qualified Text.Megaparsec               as MP
 
 
 
@@ -73,64 +78,69 @@ import qualified Data.Text.Encoding            as E
 
 -- | The symlink destination of a ghc tool.
 ghcLinkDestination :: ByteString -- ^ the tool, such as 'ghc', 'haddock' etc.
-                   -> Version
+                   -> GHCTargetVersion
                    -> ByteString
-ghcLinkDestination tool ver = "../ghc/" <> verToBS ver <> "/bin/" <> tool
-
-
--- | Extract the version part of the result of `ghcLinkDestination`.
-ghcLinkVersion :: MonadThrow m => ByteString -> m Version
-ghcLinkVersion = either (throwM . ParseError) pure . parseOnly parser
- where
-  parser    = string "../ghc/" *> verParser <* string "/bin/ghc"
-  verParser = many1' (notWord8 _slash) >>= \t ->
-    case
-        version (decUTF8Safe $ B.pack t)
-      of
-        Left  e -> fail $ show e
-        Right r -> pure r
+ghcLinkDestination tool ver =
+  "../ghc/" <> E.encodeUtf8 (prettyTVer ver) <> "/bin/" <> tool
 
 
 -- e.g. ghc-8.6.5
-rmMinorSymlinks :: (MonadIO m, MonadLogger m) => Version -> m ()
-rmMinorSymlinks ver = do
+rmMinorSymlinks :: (MonadIO m, MonadLogger m) => GHCTargetVersion -> m ()
+rmMinorSymlinks GHCTargetVersion {..} = do
   bindir <- liftIO $ ghcupBinDir
-  files  <- liftIO $ getDirsFiles' bindir
-  let myfiles =
-        filter (\x -> ("-" <> verToBS ver) `B.isSuffixOf` toFilePath x) files
-  forM_ myfiles $ \f -> do
+
+  files  <- liftIO $ findFiles'
+    bindir
+    (  maybe mempty (\x -> MP.chunk (x <> "-")) _tvTarget
+    *> parseUntil1 (MP.chunk $ prettyVer _tvVersion)
+    *> (MP.chunk $ prettyVer _tvVersion)
+    *> MP.eof
+    )
+
+  forM_ files $ \f -> do
     let fullF = (bindir </> f)
     $(logDebug) [i|rm -f #{toFilePath fullF}|]
     liftIO $ hideError doesNotExistErrorType $ deleteFile fullF
 
--- E.g. ghc, if this version is the set one.
--- This reads `ghcupGHCDir`.
+
+-- Removes the set ghc version for the given target, if any.
 rmPlain :: (MonadLogger m, MonadThrow m, MonadFail m, MonadIO m)
-        => Version
+  => Maybe Text -- ^ target
         -> Excepts '[NotInstalled] m ()
-rmPlain ver = do
-  files  <- liftE $ ghcToolFiles ver
-  bindir <- liftIO $ ghcupBinDir
-  forM_ files $ \f -> do
-    let fullF = (bindir </> f)
-    lift $ $(logDebug) [i|rm -f #{toFilePath fullF}|]
-    liftIO $ hideError doesNotExistErrorType $ deleteFile fullF
-  -- old ghcup
-  let hdc_file = (bindir </> [rel|haddock-ghc|])
-  lift $ $(logDebug) [i|rm -f #{toFilePath hdc_file}|]
-  liftIO $ hideError doesNotExistErrorType $ deleteFile hdc_file
+rmPlain target = do
+  mtv <- ghcSet target
+  forM_ mtv $ \tv -> do
+    files  <- liftE $ ghcToolFiles tv
+    bindir <- liftIO $ ghcupBinDir
+    forM_ files $ \f -> do
+      let fullF = (bindir </> f)
+      lift $ $(logDebug) [i|rm -f #{toFilePath fullF}|]
+      liftIO $ hideError doesNotExistErrorType $ deleteFile fullF
+    -- old ghcup
+    let hdc_file = (bindir </> [rel|haddock-ghc|])
+    lift $ $(logDebug) [i|rm -f #{toFilePath hdc_file}|]
+    liftIO $ hideError doesNotExistErrorType $ deleteFile hdc_file
+
 
 -- e.g. ghc-8.6
-rmMajorSymlinks :: (MonadLogger m, MonadIO m) => Version -> m ()
-rmMajorSymlinks ver = do
-  (mj, mi) <- liftIO $ getGHCMajor ver
-  let v' = E.encodeUtf8 $ intToText mj <> "." <> intToText mi
+rmMajorSymlinks :: (MonadThrow m, MonadLogger m, MonadIO m)
+                => GHCTargetVersion
+                -> m ()
+rmMajorSymlinks GHCTargetVersion {..} = do
+  (mj, mi) <- getMajorMinorV _tvVersion
+  let v' = intToText mj <> "." <> intToText mi
 
   bindir <- liftIO ghcupBinDir
 
-  files  <- liftIO $ getDirsFiles' bindir
-  let myfiles = filter (\x -> ("-" <> v') `B.isSuffixOf` toFilePath x) files
-  forM_ myfiles $ \f -> do
+  files  <- liftIO $ findFiles'
+    bindir
+    (  maybe mempty (\x -> MP.chunk (x <> "-")) _tvTarget
+    *> parseUntil1 (MP.chunk v')
+    *> MP.chunk v'
+    *> MP.eof
+    )
+
+  forM_ files $ \f -> do
     let fullF = (bindir </> f)
     $(logDebug) [i|rm -f #{toFilePath fullF}|]
     liftIO $ hideError doesNotExistErrorType $ deleteFile fullF
@@ -143,33 +153,60 @@ rmMajorSymlinks ver = do
     -----------------------------------
 
 
-toolAlreadyInstalled :: Tool -> Version -> IO Bool
-toolAlreadyInstalled tool ver = case tool of
-  GHC   -> ghcInstalled ver
-  Cabal -> cabalInstalled ver
-  GHCup -> pure True
-
-
-ghcInstalled :: Version -> IO Bool
+ghcInstalled :: GHCTargetVersion -> IO Bool
 ghcInstalled ver = do
   ghcdir <- ghcupGHCDir ver
   doesDirectoryExist ghcdir
 
 
-ghcSrcInstalled :: Version -> IO Bool
+ghcSrcInstalled :: GHCTargetVersion -> IO Bool
 ghcSrcInstalled ver = do
   ghcdir <- ghcupGHCDir ver
   doesFileExist (ghcdir </> ghcUpSrcBuiltFile)
 
 
-ghcSet :: (MonadIO m) => m (Maybe Version)
-ghcSet = do
-  ghcBin <- (</> [rel|ghc|]) <$> liftIO ghcupBinDir
+ghcSet :: (MonadThrow m, MonadIO m)
+       => Maybe Text   -- ^ the target of the GHC version, if any
+                       --  (e.g. armv7-unknown-linux-gnueabihf)
+       -> m (Maybe GHCTargetVersion)
+ghcSet mtarget = do
+  ghc    <- parseRel $ E.encodeUtf8 (maybe "ghc" (<> "-ghc") mtarget)
+  ghcBin <- (</> ghc) <$> liftIO ghcupBinDir
 
   -- link destination is of the form ../ghc/<ver>/bin/ghc
   liftIO $ handleIO' NoSuchThing (\_ -> pure $ Nothing) $ do
     link <- readSymbolicLink $ toFilePath ghcBin
     Just <$> ghcLinkVersion link
+ where
+  ghcLinkVersion :: MonadThrow m => ByteString -> m GHCTargetVersion
+  ghcLinkVersion bs = do
+    t <- throwEither $ E.decodeUtf8' bs
+    throwEither $ MP.parse parser "" t
+   where
+    parser =
+      MP.chunk "../ghc/"
+        *> (do
+             r    <- parseUntil1 (MP.chunk "/")
+             rest <- MP.getInput
+             MP.setInput r
+             x <- ghcTargetVerP
+             MP.setInput rest
+             pure x
+           )
+        <* MP.chunk "/bin/"
+        <* ghcTargetBinP "ghc"
+        <* MP.eof
+
+
+-- | Get all installed GHCs by reading ~/.ghcup/ghc/<dir>.
+-- If a dir cannot be parsed, returns left.
+getInstalledGHCs :: MonadIO m => m [Either (Path Rel) GHCTargetVersion]
+getInstalledGHCs = do
+  ghcdir <- liftIO $ ghcupGHCBaseDir
+  fs     <- liftIO $ hideErrorDef [NoSuchThing] [] $ getDirsFiles' ghcdir
+  forM fs $ \f -> case parseGHCupGHCDir f of
+    Right r -> pure $ Right r
+    Left  _ -> pure $ Left f
 
 
 cabalInstalled :: Version -> IO Bool
@@ -193,33 +230,36 @@ cabalSet = do
     -----------------------------------------
 
 
--- | We assume GHC is in semver format. I hope it is.
-getGHCMajor :: MonadThrow m => Version -> m (Int, Int)
-getGHCMajor ver = do
-  SemVer {..} <- throwEither (semver $ prettyVer ver)
-  pure (fromIntegral _svMajor, fromIntegral _svMinor)
+getMajorMinorV :: MonadThrow m => Version -> m (Int, Int)
+getMajorMinorV Version {..} = case _vChunks of
+  ([Digits x] : [Digits y] : _) -> pure (fromIntegral x, fromIntegral y)
+  _ -> throwM $ ParseError "Could not parse X.Y from version"
+
+
+matchMajor :: Version -> Int -> Int -> Bool
+matchMajor v' major' minor' = case getMajorMinorV v' of
+  Just (x, y) -> x == major' && y == minor'
+  Nothing     -> False
 
 
 -- | Get the latest installed full GHC version that satisfies X.Y.
 -- This reads `ghcupGHCBaseDir`.
 getGHCForMajor :: (MonadIO m, MonadThrow m)
-               => Int -- ^ major version component
-               -> Int -- ^ minor version component
-               -> m (Maybe Version)
-getGHCForMajor major' minor' = do
-  p       <- liftIO $ ghcupGHCBaseDir
-  ghcs    <- liftIO $ getDirsFiles' p
-  semvers <- forM ghcs $ \ghc ->
-    throwEither . semver =<< (throwEither . E.decodeUtf8' . toFilePath $ ghc)
-  mapM (throwEither . version)
-    . fmap prettySemVer
+               => Int        -- ^ major version component
+               -> Int        -- ^ minor version component
+               -> Maybe Text -- ^ the target triple
+               -> m (Maybe GHCTargetVersion)
+getGHCForMajor major' minor' mt = do
+  ghcs <- rights <$> getInstalledGHCs
+
+  pure
     . lastMay
-    . sort
+    . sortBy (\x y -> compare (_tvVersion x) (_tvVersion y))
     . filter
-        (\SemVer {..} ->
-          fromIntegral _svMajor == major' && fromIntegral _svMinor == minor'
+        (\GHCTargetVersion {..} ->
+          _tvTarget == mt && matchMajor _tvVersion major' minor'
         )
-    $ semvers
+    $ ghcs
 
 
 -- | Get the latest available ghc for X.Y major version.
@@ -228,14 +268,10 @@ getLatestGHCFor :: Int -- ^ major version component
                 -> GHCupDownloads
                 -> Maybe Version
 getLatestGHCFor major' minor' dls = do
-  join . fmap
-      (lastMay . filter
-        (\v -> case semver $ prettyVer v of
-                 Right SemVer{..} -> fromIntegral _svMajor == major' && fromIntegral _svMinor == minor'
-                 Left _ -> False
-        )
-      )
-    . preview (ix GHC % to Map.keys) $ dls
+  join
+    . fmap (lastMay . filter (\v -> matchMajor v major' minor'))
+    . preview (ix GHC % to Map.keys)
+    $ dls
 
 
 
@@ -282,7 +318,8 @@ unpackToDir dest av = do
 
 -- | Get the tool version that has this tag. If multiple have it,
 -- picks the greatest version.
-getTagged :: Tag -> AffineFold (Map.Map Version VersionInfo) (Version, VersionInfo)
+getTagged :: Tag
+          -> AffineFold (Map.Map Version VersionInfo) (Version, VersionInfo)
 getTagged tag =
   ( to (Map.filter (\VersionInfo {..} -> elem tag _viTags))
   % to Map.toDescList
@@ -298,7 +335,8 @@ getRecommended av tool = headOf (ix tool % getTagged Recommended % to fst) $ av
 
 -- | Gets the latest GHC with a given base version.
 getLatestBaseVersion :: GHCupDownloads -> PVP -> Maybe Version
-getLatestBaseVersion av pvpVer = headOf (ix GHC % getTagged (Base pvpVer) % to fst) av
+getLatestBaseVersion av pvpVer =
+  headOf (ix GHC % getTagged (Base pvpVer) % to fst) av
 
 
 
@@ -324,12 +362,12 @@ urlBaseName = parseRel . snd . B.breakEnd (== _slash) . urlDecode False
 
 
 -- Get tool files from '~/.ghcup/bin/ghc/<ver>/bin/*'
--- while ignoring *-<ver> symlinks.
+-- while ignoring *-<ver> symlinks and accounting for cross triple prefix.
 --
 -- Returns unversioned relative files, e.g.:
 --   ["hsc2hs","haddock","hpc","runhaskell","ghc","ghc-pkg","ghci","runghc","hp2ps"]
 ghcToolFiles :: (MonadThrow m, MonadFail m, MonadIO m)
-             => Version
+             => GHCTargetVersion
              -> Excepts '[NotInstalled] m [Path Rel]
 ghcToolFiles ver = do
   ghcdir <- liftIO $ ghcupGHCDir ver
@@ -337,18 +375,28 @@ ghcToolFiles ver = do
 
   -- fail if ghc is not installed
   whenM (fmap not $ liftIO $ doesDirectoryExist ghcdir)
-        (throwE (NotInstalled GHC ver))
+        (throwE (NotInstalled GHC (prettyTVer ver)))
 
-  files         <- liftIO $ getDirsFiles' bindir
+  files    <- liftIO $ getDirsFiles' bindir
   -- figure out the <ver> suffix, because this might not be `Version` for
   -- alpha/rc releases, but x.y.a.somedate.
+
+  -- for cross, this won't be "ghc", but e.g.
+  -- "armv7-unknown-linux-gnueabihf-ghc"
+  [ghcbin] <- liftIO $ findFiles
+    bindir
+    (makeRegexOpts compExtended
+                   execBlank
+                   ([s|^([a-zA-Z0-9_-]*[a-zA-Z0-9_]-)?ghc$|] :: ByteString)
+    )
+
   (Just symver) <-
-    (B.stripPrefix "ghc-" . takeFileName)
-      <$> (liftIO $ readSymbolicLink $ toFilePath (bindir </> [rel|ghc|]))
+    (B.stripPrefix (toFilePath ghcbin <> "-") . takeFileName)
+      <$> (liftIO $ readSymbolicLink $ toFilePath (bindir </> ghcbin))
   when (B.null symver)
        (throwIO $ userError $ "Fatal: ghc symlink target is broken")
 
-  pure $ filter (\x -> not $ symver `B.isSuffixOf` toFilePath x) files
+  pure . filter (\x -> not $ symver `B.isSuffixOf` toFilePath x) $ files
 
 
 -- | This file, when residing in ~/.ghcup/ghc/<ver>/ signals that
@@ -399,13 +447,8 @@ darwinNotarization _ _ = pure $ Right ()
 getChangeLog :: GHCupDownloads -> Tool -> Either Version Tag -> Maybe URI
 getChangeLog dls tool (Left v') =
   preview (ix tool % ix v' % viChangeLog % _Just) dls
-getChangeLog dls tool (Right tag) = preview
-  ( ix tool
-  % getTagged tag
-  % to snd
-  % viChangeLog
-  % _Just
-  ) dls
+getChangeLog dls tool (Right tag) =
+  preview (ix tool % getTagged tag % to snd % viChangeLog % _Just) dls
 
 
 -- | Execute a build action while potentially cleaning up:
diff --git a/lib/GHCup/Utils/Dirs.hs b/lib/GHCup/Utils/Dirs.hs
index c5594530..7f19b99b 100644
--- a/lib/GHCup/Utils/Dirs.hs
+++ b/lib/GHCup/Utils/Dirs.hs
@@ -1,10 +1,13 @@
 {-# LANGUAGE OverloadedStrings     #-}
 {-# LANGUAGE QuasiQuotes           #-}
+{-# LANGUAGE ViewPatterns          #-}
 
 module GHCup.Utils.Dirs where
 
 
+import           GHCup.Types
 import           GHCup.Types.JSON               ( )
+import           GHCup.Utils.MegaParsec
 import           GHCup.Utils.Prelude
 
 import           Control.Applicative
@@ -13,7 +16,6 @@ import           Control.Monad
 import           Control.Monad.Reader
 import           Control.Monad.Trans.Resource
 import           Data.Maybe
-import           Data.Versions
 import           HPath
 import           HPath.IO
 import           Optics
@@ -27,8 +29,10 @@ import           System.Posix.Env.ByteString    ( getEnv
 import           System.Posix.Temp.ByteString   ( mkdtemp )
 
 import qualified Data.ByteString.UTF8          as UTF8
+import qualified Data.Text.Encoding            as E
 import qualified System.Posix.FilePath         as FP
 import qualified System.Posix.User             as PU
+import qualified Text.Megaparsec               as MP
 
 
 
@@ -37,6 +41,7 @@ import qualified System.Posix.User             as PU
     -------------------------
 
 
+-- | ~/.ghcup by default
 ghcupBaseDir :: IO (Path Abs)
 ghcupBaseDir = do
   bdir <- getEnv "GHCUP_INSTALL_BASE_PREFIX" >>= \case
@@ -44,16 +49,30 @@ ghcupBaseDir = do
     Nothing -> liftIO getHomeDirectory
   pure (bdir </> [rel|.ghcup|])
 
+
+-- | ~/.ghcup/ghc by default.
 ghcupGHCBaseDir :: IO (Path Abs)
 ghcupGHCBaseDir = ghcupBaseDir <&> (</> [rel|ghc|])
 
-ghcupGHCDir :: Version -> IO (Path Abs)
+
+-- | Gets '~/.ghcup/ghc/<ghcupGHCDir>'.
+-- The dir may be of the form
+--   * armv7-unknown-linux-gnueabihf-8.8.3
+--   * 8.8.4
+ghcupGHCDir :: GHCTargetVersion -> IO (Path Abs)
 ghcupGHCDir ver = do
   ghcbasedir <- ghcupGHCBaseDir
-  verdir     <- parseRel (verToBS ver)
+  verdir     <- parseRel $ E.encodeUtf8 (prettyTVer ver)
   pure (ghcbasedir </> verdir)
 
 
+-- | See 'ghcupToolParser'.
+parseGHCupGHCDir :: MonadThrow m => Path Rel -> m GHCTargetVersion
+parseGHCupGHCDir (toFilePath -> f) = do
+  fp <- throwEither $ E.decodeUtf8' f
+  throwEither $ MP.parse ghcTargetVerP "" fp
+
+
 ghcupBinDir :: IO (Path Abs)
 ghcupBinDir = ghcupBaseDir <&> (</> [rel|bin|])
 
diff --git a/lib/GHCup/Utils/File.hs b/lib/GHCup/Utils/File.hs
index 6de9eb76..10ca4343 100644
--- a/lib/GHCup/Utils/File.hs
+++ b/lib/GHCup/Utils/File.hs
@@ -18,6 +18,8 @@ import           Data.Foldable
 import           Data.Functor
 import           Data.IORef
 import           Data.Maybe
+import           Data.Text                      ( Text )
+import           Data.Void
 import           GHC.Foreign                    ( peekCStringLen )
 import           GHC.IO.Encoding                ( getLocaleEncoding )
 import           GHC.IO.Exception
@@ -39,10 +41,12 @@ import "unix"    System.Posix.IO.ByteString
                                          hiding ( openFd )
 import           System.Posix.Process           ( ProcessStatus(..) )
 import           System.Posix.Types
+import           Text.Regex.Posix
 
 
 import qualified Control.Exception             as EX
 import qualified Data.Text                     as T
+import qualified Data.Text.Encoding            as E
 import qualified System.Posix.Process.ByteString
                                                as SPPB
 import           Streamly.External.Posix.DirStream
@@ -51,12 +55,14 @@ import qualified Streamly.Internal.Memory.ArrayStream
 import qualified Streamly.FileSystem.Handle    as FH
 import qualified Streamly.Internal.Data.Unfold as SU
 import qualified Streamly.Prelude              as S
+import qualified Text.Megaparsec               as MP
 import qualified Data.ByteString               as BS
 import qualified Data.ByteString.Lazy          as L
 import qualified "unix-bytestring" System.Posix.IO.ByteString
                                                as SPIB
 
 
+
 -- | Bool signals whether the regions should be cleaned.
 data StopThread = StopThread Bool
   deriving Show
@@ -379,3 +385,27 @@ searchPath paths needle = go paths
     if p == toFilePath needle
       then isExecutable (basedir </> needle)
       else pure False
+
+
+findFiles :: Path Abs -> Regex -> IO [Path Rel]
+findFiles path regex = do
+  dirStream <- openDirStream (toFilePath path)
+  f         <-
+    (fmap . fmap) snd
+    . S.toList
+    . S.filter (\(_, p) -> match regex p)
+    $ dirContentsStream dirStream
+  pure $ join $ fmap parseRel f
+
+
+findFiles' :: Path Abs -> MP.Parsec Void Text () -> IO [Path Rel]
+findFiles' path parser = do
+  dirStream <- openDirStream (toFilePath path)
+  f         <-
+    (fmap . fmap) snd
+    . S.toList
+    . S.filter (\(_, p) -> case E.decodeUtf8' p of
+                             Left _ -> False
+                             Right p' -> isJust $ MP.parseMaybe parser p')
+    $ dirContentsStream dirStream
+  pure $ join $ fmap parseRel f
diff --git a/lib/GHCup/Utils/MegaParsec.hs b/lib/GHCup/Utils/MegaParsec.hs
new file mode 100644
index 00000000..c9126fdb
--- /dev/null
+++ b/lib/GHCup/Utils/MegaParsec.hs
@@ -0,0 +1,87 @@
+{-# LANGUAGE CPP                  #-}
+{-# LANGUAGE OverloadedStrings    #-}
+
+module GHCup.Utils.MegaParsec where
+
+import           GHCup.Types
+
+import           Control.Applicative
+import           Control.Monad
+#if !MIN_VERSION_base(4,13,0)
+import           Control.Monad.Fail             ( MonadFail )
+#endif
+import           Data.Functor
+import           Data.Maybe
+import           Data.Text                      ( Text )
+import           Data.Versions
+import           Data.Void
+
+import qualified Data.Text                     as T
+import qualified Text.Megaparsec               as MP
+
+
+choice' :: (MonadFail f, MP.MonadParsec e s f) => [f a] -> f a
+choice' []       = fail "Empty list"
+choice' [x     ] = x
+choice' (x : xs) = MP.try x <|> choice' xs
+
+
+parseUntil :: MP.Parsec Void Text a -> MP.Parsec Void Text Text
+parseUntil p = do
+  (MP.try (MP.lookAhead p) $> mempty)
+    <|> (do
+          c  <- T.singleton <$> MP.anySingle
+          c2 <- parseUntil p
+          pure (c `mappend` c2)
+        )
+
+parseUntil1 :: MP.Parsec Void Text a -> MP.Parsec Void Text Text
+parseUntil1 p = do
+  i1 <- MP.getOffset
+  t <- parseUntil p
+  i2 <- MP.getOffset
+  if i1 == i2 then fail "empty parse" else pure t
+
+
+
+-- | Parses e.g.
+--   * armv7-unknown-linux-gnueabihf-ghc
+--   * armv7-unknown-linux-gnueabihf-ghci
+ghcTargetBinP :: Text -> MP.Parsec Void Text (Maybe Text, Text)
+ghcTargetBinP t =
+  (,)
+    <$> (   MP.try
+            (Just <$> (parseUntil1 (MP.chunk "-" *> MP.chunk t)) <* MP.chunk "-"
+            )
+        <|> (flip const Nothing <$> mempty)
+        )
+    <*> (MP.chunk t <* MP.eof)
+
+
+-- | Extracts target triple and version from e.g.
+--   * armv7-unknown-linux-gnueabihf-8.8.3
+--   * armv7-unknown-linux-gnueabihf-8.8.3
+ghcTargetVerP :: MP.Parsec Void Text GHCTargetVersion
+ghcTargetVerP =
+  (\x y -> GHCTargetVersion x y)
+    <$> (MP.try (Just <$> (parseUntil1 (MP.chunk "-" *> verP)) <* MP.chunk "-")
+        <|> (flip const Nothing <$> mempty)
+        )
+    <*> (version' <* MP.eof)
+ where
+  verP :: MP.Parsec Void Text Text
+  verP = do
+    v <- version'
+    let startsWithDigists =
+          and
+            . take 3
+            . join
+            . (fmap . fmap)
+                (\case
+                  (Digits _) -> True
+                  (Str    _) -> False
+                )
+            $ (_vChunks v)
+    if startsWithDigists && not (isJust (_vEpoch v))
+      then pure $ prettyVer v
+      else fail "Oh"
diff --git a/lib/GHCup/Utils/Prelude.hs b/lib/GHCup/Utils/Prelude.hs
index 0d698d15..d10b1914 100644
--- a/lib/GHCup/Utils/Prelude.hs
+++ b/lib/GHCup/Utils/Prelude.hs
@@ -218,6 +218,12 @@ throwEither a = case a of
   Right r -> pure r
 
 
+throwEither' :: (Exception a, MonadThrow m) => a -> Either x b -> m b
+throwEither' e eth = case eth of
+  Left  _ -> throwM e
+  Right r -> pure r
+
+
 verToBS :: Version -> ByteString
 verToBS = E.encodeUtf8 . prettyVer
 
-- 
GitLab