Fix build on case-insensitive filesystems (#873)
This commit is contained in:
parent
084688bb35
commit
97c3f018c4
28
GhcMod.hs
28
GhcMod.hs
@ -69,20 +69,20 @@ module GhcMod (
|
|||||||
, unloadMappedFile
|
, unloadMappedFile
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import GhcMod.Boot
|
import GhcModExe.Boot
|
||||||
import GhcMod.Browse
|
import GhcModExe.Browse
|
||||||
import GhcMod.CaseSplit
|
import GhcModExe.CaseSplit
|
||||||
import GhcMod.Check
|
import GhcModExe.Check
|
||||||
import GhcMod.Debug
|
import GhcModExe.Debug
|
||||||
import GhcMod.FillSig
|
import GhcModExe.FillSig
|
||||||
import GhcMod.Find
|
import GhcModExe.Find
|
||||||
import GhcMod.Flag
|
import GhcModExe.Flag
|
||||||
import GhcMod.Info
|
import GhcModExe.Info
|
||||||
import GhcMod.Lang
|
import GhcModExe.Lang
|
||||||
import GhcMod.Lint
|
import GhcModExe.Lint
|
||||||
import GhcMod.Modules
|
import GhcModExe.Modules
|
||||||
import GhcMod.PkgDoc
|
import GhcModExe.PkgDoc
|
||||||
import GhcMod.Test
|
import GhcModExe.Test
|
||||||
import Language.Haskell.GhcMod.Cradle
|
import Language.Haskell.GhcMod.Cradle
|
||||||
import Language.Haskell.GhcMod.FileMapping
|
import Language.Haskell.GhcMod.FileMapping
|
||||||
import Language.Haskell.GhcMod.Logging
|
import Language.Haskell.GhcMod.Logging
|
||||||
|
@ -1,12 +1,12 @@
|
|||||||
module GhcMod.Boot where
|
module GhcModExe.Boot where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
||||||
import GhcMod.Browse
|
import GhcModExe.Browse
|
||||||
import GhcMod.Flag
|
import GhcModExe.Flag
|
||||||
import GhcMod.Lang
|
import GhcModExe.Lang
|
||||||
import GhcMod.Modules
|
import GhcModExe.Modules
|
||||||
import Language.Haskell.GhcMod.Monad
|
import Language.Haskell.GhcMod.Monad
|
||||||
import Language.Haskell.GhcMod.Types (defaultBrowseOpts)
|
import Language.Haskell.GhcMod.Types (defaultBrowseOpts)
|
||||||
|
|
@ -1,5 +1,5 @@
|
|||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
module GhcMod.Browse (
|
module GhcModExe.Browse (
|
||||||
browse,
|
browse,
|
||||||
BrowseOpts(..)
|
BrowseOpts(..)
|
||||||
) where
|
) where
|
@ -1,6 +1,6 @@
|
|||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
|
|
||||||
module GhcMod.CaseSplit (
|
module GhcModExe.CaseSplit (
|
||||||
splits
|
splits
|
||||||
) where
|
) where
|
||||||
|
|
@ -1,4 +1,4 @@
|
|||||||
module GhcMod.Check (
|
module GhcModExe.Check (
|
||||||
checkSyntax
|
checkSyntax
|
||||||
, check
|
, check
|
||||||
, expandTemplate
|
, expandTemplate
|
@ -1,4 +1,4 @@
|
|||||||
module GhcMod.Debug (debugInfo, rootInfo, componentInfo) where
|
module GhcModExe.Debug (debugInfo, rootInfo, componentInfo) where
|
||||||
|
|
||||||
import Control.Arrow (first)
|
import Control.Arrow (first)
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
@ -11,7 +11,7 @@ import Data.Version
|
|||||||
import Data.List.Split
|
import Data.List.Split
|
||||||
import System.Directory
|
import System.Directory
|
||||||
|
|
||||||
import GhcMod.Internal
|
import GhcModExe.Internal
|
||||||
import Language.Haskell.GhcMod.Cradle
|
import Language.Haskell.GhcMod.Cradle
|
||||||
import Language.Haskell.GhcMod.Monad
|
import Language.Haskell.GhcMod.Monad
|
||||||
import Language.Haskell.GhcMod.Output
|
import Language.Haskell.GhcMod.Output
|
@ -1,7 +1,7 @@
|
|||||||
{-# LANGUAGE CPP, MultiParamTypeClasses, FunctionalDependencies #-}
|
{-# LANGUAGE CPP, MultiParamTypeClasses, FunctionalDependencies #-}
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
|
|
||||||
module GhcMod.FillSig (
|
module GhcModExe.FillSig (
|
||||||
sig
|
sig
|
||||||
, refine
|
, refine
|
||||||
, auto
|
, auto
|
@ -1,6 +1,6 @@
|
|||||||
{-# LANGUAGE CPP, BangPatterns, TupleSections, DeriveGeneric #-}
|
{-# LANGUAGE CPP, BangPatterns, TupleSections, DeriveGeneric #-}
|
||||||
|
|
||||||
module GhcMod.Find
|
module GhcModExe.Find
|
||||||
#ifndef SPEC
|
#ifndef SPEC
|
||||||
( Symbol
|
( Symbol
|
||||||
, SymbolDb
|
, SymbolDb
|
@ -1,4 +1,4 @@
|
|||||||
module GhcMod.Flag where
|
module GhcModExe.Flag where
|
||||||
|
|
||||||
import qualified Language.Haskell.GhcMod.Gap as Gap
|
import qualified Language.Haskell.GhcMod.Gap as Gap
|
||||||
import Language.Haskell.GhcMod.Convert
|
import Language.Haskell.GhcMod.Convert
|
@ -1,4 +1,4 @@
|
|||||||
module GhcMod.Info (
|
module GhcModExe.Info (
|
||||||
info
|
info
|
||||||
, types
|
, types
|
||||||
) where
|
) where
|
@ -1,6 +1,6 @@
|
|||||||
-- | Low level access to the ghc-mod library.
|
-- | Low level access to the ghc-mod library.
|
||||||
|
|
||||||
module GhcMod.Internal (
|
module GhcModExe.Internal (
|
||||||
-- * Types
|
-- * Types
|
||||||
GHCOption
|
GHCOption
|
||||||
, IncludeDir
|
, IncludeDir
|
@ -1,4 +1,4 @@
|
|||||||
module GhcMod.Lang where
|
module GhcModExe.Lang where
|
||||||
|
|
||||||
import DynFlags (supportedLanguagesAndExtensions)
|
import DynFlags (supportedLanguagesAndExtensions)
|
||||||
import Language.Haskell.GhcMod.Convert
|
import Language.Haskell.GhcMod.Convert
|
@ -1,4 +1,4 @@
|
|||||||
module GhcMod.Lint where
|
module GhcModExe.Lint where
|
||||||
|
|
||||||
import Exception (ghandle)
|
import Exception (ghandle)
|
||||||
import Control.Exception (SomeException(..))
|
import Control.Exception (SomeException(..))
|
@ -1,4 +1,4 @@
|
|||||||
module GhcMod.Modules (modules) where
|
module GhcModExe.Modules (modules) where
|
||||||
|
|
||||||
import Control.Arrow
|
import Control.Arrow
|
||||||
import Data.List
|
import Data.List
|
@ -1,4 +1,4 @@
|
|||||||
module GhcMod.PkgDoc (pkgDoc) where
|
module GhcModExe.PkgDoc (pkgDoc) where
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Types
|
import Language.Haskell.GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.GhcPkg
|
import Language.Haskell.GhcMod.GhcPkg
|
@ -1,4 +1,4 @@
|
|||||||
module GhcMod.Test where
|
module GhcModExe.Test where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Data.List
|
import Data.List
|
@ -115,21 +115,21 @@ Library
|
|||||||
HS-Source-Dirs: ., core
|
HS-Source-Dirs: ., core
|
||||||
Exposed-Modules:
|
Exposed-Modules:
|
||||||
GhcMod
|
GhcMod
|
||||||
GhcMod.Boot
|
GhcModExe.Boot
|
||||||
GhcMod.Browse
|
GhcModExe.Browse
|
||||||
GhcMod.CaseSplit
|
GhcModExe.CaseSplit
|
||||||
GhcMod.Check
|
GhcModExe.Check
|
||||||
GhcMod.Debug
|
GhcModExe.Debug
|
||||||
GhcMod.FillSig
|
GhcModExe.FillSig
|
||||||
GhcMod.Find
|
GhcModExe.Find
|
||||||
GhcMod.Flag
|
GhcModExe.Flag
|
||||||
GhcMod.Info
|
GhcModExe.Info
|
||||||
GhcMod.Internal
|
GhcModExe.Internal
|
||||||
GhcMod.Lang
|
GhcModExe.Lang
|
||||||
GhcMod.Lint
|
GhcModExe.Lint
|
||||||
GhcMod.Modules
|
GhcModExe.Modules
|
||||||
GhcMod.PkgDoc
|
GhcModExe.PkgDoc
|
||||||
GhcMod.Test
|
GhcModExe.Test
|
||||||
Language.Haskell.GhcMod.CabalHelper
|
Language.Haskell.GhcMod.CabalHelper
|
||||||
Language.Haskell.GhcMod.Caching
|
Language.Haskell.GhcMod.Caching
|
||||||
Language.Haskell.GhcMod.Caching.Types
|
Language.Haskell.GhcMod.Caching.Types
|
||||||
@ -212,7 +212,7 @@ Library
|
|||||||
|
|
||||||
Executable ghc-mod
|
Executable ghc-mod
|
||||||
Default-Language: Haskell2010
|
Default-Language: Haskell2010
|
||||||
Main-Is: GHCMod.hs
|
Main-Is: GHCModMain.hs
|
||||||
Other-Modules: Paths_ghc_mod
|
Other-Modules: Paths_ghc_mod
|
||||||
, GHCMod.Options
|
, GHCMod.Options
|
||||||
, GHCMod.Options.Commands
|
, GHCMod.Options.Commands
|
||||||
|
@ -17,8 +17,8 @@ import Prelude
|
|||||||
|
|
||||||
import GHCMod.Options
|
import GHCMod.Options
|
||||||
import GhcMod
|
import GhcMod
|
||||||
import GhcMod.Find
|
import GhcModExe.Find
|
||||||
import GhcMod.Internal hiding (MonadIO,liftIO)
|
import GhcModExe.Internal hiding (MonadIO,liftIO)
|
||||||
import Language.Haskell.GhcMod.Monad
|
import Language.Haskell.GhcMod.Monad
|
||||||
import Language.Haskell.GhcMod.Types
|
import Language.Haskell.GhcMod.Types
|
||||||
|
|
Loading…
Reference in New Issue
Block a user