find functions went to lib.

This commit is contained in:
Kazu Yamamoto
2014-04-24 17:02:50 +09:00
parent 3059a295dc
commit 390c509144
5 changed files with 66 additions and 40 deletions

View File

@@ -0,0 +1,49 @@
{-# LANGUAGE CPP, BangPatterns #-}
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
import Language.Haskell.GhcMod.Browse (browseAll)
import Language.Haskell.GhcMod.Types (convert)
#ifndef MIN_VERSION_containers
#define MIN_VERSION_containers(x,y,z) 1
#endif
#if MIN_VERSION_containers(0,5,0)
import Control.DeepSeq (force)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as M
#else
import Data.Map (Map)
import qualified Data.Map as M
#endif
-- | Type of key for `SymMdlDb`.
type Symbol = String
-- | Database from 'Symbol' to modules.
newtype SymMdlDb = SymMdlDb (Map Symbol [ModuleString])
-- | Creating 'SymMdlDb'.
getSymMdlDb :: Ghc SymMdlDb
getSymMdlDb = do
sm <- G.getSessionDynFlags >>= browseAll
#if MIN_VERSION_containers(0,5,0)
let !sms = force $ map tieup $ groupBy ((==) `on` fst) $ sort sm
!m = force $ M.fromList sms
#else
let !sms = map tieup $ groupBy ((==) `on` fst) $ sort sm
!m = M.fromList sms
#endif
return (SymMdlDb m)
where
tieup x = (head (map fst x), map snd x)
-- | Looking up 'SymMdlDb' with 'Symbol' to find modules.
lookupSym :: Options -> Symbol -> SymMdlDb -> String
lookupSym opt sym (SymMdlDb db) = convert opt $ fromMaybe [] (M.lookup sym db)

View File

@@ -8,10 +8,16 @@ module Language.Haskell.GhcMod.Ghc (
, info
, types
, modules
-- * 'SymMdlDb'
, Symbol
, SymMdlDb
, getSymMdlDb
, lookupSym
) where
import Language.Haskell.GhcMod.Browse
import Language.Haskell.GhcMod.Check
import Language.Haskell.GhcMod.Find
import Language.Haskell.GhcMod.GHCApi
import Language.Haskell.GhcMod.Info
import Language.Haskell.GhcMod.List

View File

@@ -26,18 +26,14 @@ module Language.Haskell.GhcMod.Internal (
, setTargetFiles
, addTargetFiles
, handleErrMsg
, browseAll
-- * 'Ghc' Choice
, (||>)
, goNext
, runAnyOne
-- * 'GhcMonad' Choice
, (|||>)
-- * Misc
, convert
) where
import Language.Haskell.GhcMod.Browse
import Language.Haskell.GhcMod.CabalApi
import Language.Haskell.GhcMod.ErrMsg
import Language.Haskell.GhcMod.GHCApi