Don't expose `Convert`

This commit is contained in:
Daniel Gröber 2014-05-14 18:54:56 +02:00
parent 80e2761f2f
commit 8324dd96ae
5 changed files with 8 additions and 6 deletions

View File

@ -1,6 +1,6 @@
{-# LANGUAGE FlexibleInstances #-}
module Language.Haskell.GhcMod.Convert where
module Language.Haskell.GhcMod.Convert (convert, convert') where
import Language.Haskell.GhcMod.Monad
import Language.Haskell.GhcMod.Types

View File

@ -5,10 +5,8 @@ module Language.Haskell.GhcMod.Find where
import Data.Function (on)
import Data.List (groupBy, sort)
import Data.Maybe (fromMaybe)
import GHC (Ghc)
import qualified GHC as G
import Language.Haskell.GhcMod.Browse (browseAll)
import Language.Haskell.GhcMod.GHCApi
import Language.Haskell.GhcMod.Monad
import Language.Haskell.GhcMod.Convert
import Language.Haskell.GhcMod.Types
@ -54,3 +52,6 @@ getSymMdlDb = do
-- | Looking up 'SymMdlDb' with 'Symbol' to find modules.
lookupSym :: Symbol -> SymMdlDb -> [ModuleString]
lookupSym sym (SymMdlDb db) = fromMaybe [] (M.lookup sym db)
lookupSym' :: Options -> Symbol -> SymMdlDb -> String
lookupSym' opt sym db = convert opt $ lookupSym sym db

View File

@ -14,6 +14,7 @@ module Language.Haskell.GhcMod.Ghc (
, SymMdlDb
, getSymMdlDb
, lookupSym
, lookupSym'
) where
import Language.Haskell.GhcMod.Boot

View File

@ -53,7 +53,6 @@ Library
GHC-Options: -Wall
Exposed-Modules: Language.Haskell.GhcMod
Language.Haskell.GhcMod.Ghc
Language.Haskell.GhcMod.Convert
Language.Haskell.GhcMod.Monad
Language.Haskell.GhcMod.Internal
Other-Modules: Language.Haskell.GhcMod.Boot
@ -64,6 +63,7 @@ Library
Language.Haskell.GhcMod.Cabal18
Language.Haskell.GhcMod.Check
Language.Haskell.GhcMod.Cradle
Language.Haskell.GhcMod.Convert
Language.Haskell.GhcMod.Debug
Language.Haskell.GhcMod.Doc
Language.Haskell.GhcMod.Find

View File

@ -35,7 +35,6 @@ import GHC (Ghc)
import qualified GHC as G
import Language.Haskell.GhcMod
import Language.Haskell.GhcMod.Ghc
import Language.Haskell.GhcMod.Convert (convert')
import Language.Haskell.GhcMod.Monad
import Language.Haskell.GhcMod.Internal
import Paths_ghc_mod
@ -204,7 +203,8 @@ findSym :: Set FilePath -> String -> MVar SymMdlDb
-> GhcMod (String, Bool, Set FilePath)
findSym set sym mvar = do
db <- liftIO $ readMVar mvar
ret <- convert' $ lookupSym sym db
opt <- options
let ret = lookupSym' opt sym db
return (ret, True, set)
lintStx :: Options -> Set FilePath -> FilePath