Skip to content
Snippets Groups Projects
Forked from Glasgow Haskell Compiler / GHC
13960 commits behind the upstream repository.
  • Sebastian Graf's avatar
    8add024f
    Make GHC-in-GHCi work on Windows · 8add024f
    Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
    By not building anything in the dynamic way on Windows, where we don't
    have a working story for DLLs yet.
    
    Also the ghcid command needs to call bash on the hadrian/ghci.sh script
    explicitly as the path gets interpreted differently otherwise.
    8add024f
    History
    Make GHC-in-GHCi work on Windows
    Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
    By not building anything in the dynamic way on Windows, where we don't
    have a working story for DLLs yet.
    
    Also the ghcid command needs to call bash on the hadrian/ghci.sh script
    explicitly as the path gets interpreted differently otherwise.
Code owners
Assign users and groups as approvers for specific file changes. Learn more.
GhcInGhci.hs 1012 B
module Settings.Flavours.GhcInGhci (ghcInGhciFlavour) where

import Expression
import Flavour
import {-# SOURCE #-} Settings.Default
import Settings.Flavours.Common

-- Please update doc/flavours.md when changing this file.
ghcInGhciFlavour :: Flavour
ghcInGhciFlavour = defaultFlavour
    { name        = "ghc-in-ghci"
    , args        = defaultBuilderArgs <> ghciArgs <> defaultPackageArgs
    -- We can't build DLLs on Windows (yet). Actually we should only
    -- include the dynamic way when we have a dynamic host GHC, but just
    -- checking for Windows seems simpler for now.
    , libraryWays = pure [vanilla] <> pure [ dynamic | not windowsHost ]
    , rtsWays     = pure [vanilla, threaded] <> pure [ dynamic | not windowsHost ]
    , dynamicGhcPrograms = return False }

ghciArgs :: Args
ghciArgs = sourceArgs SourceArgs
    { hsDefault  = mconcat $
        [ pure ["-O0", "-H64m"]
        , naturalInBaseFixArgs
        ]
    , hsLibrary  = mempty
    , hsCompiler = mempty
    , hsGhc = mempty }