Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
1 change: 1 addition & 0 deletions .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -10,3 +10,4 @@ cabal-dev
cabal.sandbox.config
cabal.config
TAGS
*.DS_Store
12 changes: 6 additions & 6 deletions Analyse.hs → Language/Haskell/SourceGraph/Analyse.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,13 +27,13 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA

Analyse Haskell software
-}
module Analyse(analyse, sgLegend) where
module Language.Haskell.SourceGraph.Analyse(analyse, sgLegend) where

import Analyse.Module
import Analyse.Imports
import Analyse.Everything
import Analyse.Colors
import Parsing.Types
import Language.Haskell.SourceGraph.Analyse.Module
import Language.Haskell.SourceGraph.Analyse.Imports
import Language.Haskell.SourceGraph.Analyse.Everything
import Language.Haskell.SourceGraph.Analyse.Colors
import Language.Haskell.SourceGraph.Parsing.Types

import Data.Graph.Analysis hiding (Bold)
import qualified Data.Graph.Analysis.Reporting as R (DocInline(Bold))
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA

Utility functions and types for analysis.
-}
module Analyse.Colors where
module Language.Haskell.SourceGraph.Analyse.Colors where

import Data.GraphViz.Attributes

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -27,12 +27,12 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA

Analysis of the entire overall piece of software.
-}
module Analyse.Everything(analyseEverything) where
module Language.Haskell.SourceGraph.Analyse.Everything(analyseEverything,codeToGraph) where

import Parsing.Types
import Analyse.Utils
import Analyse.GraphRepr
import Analyse.Visualise
import Language.Haskell.SourceGraph.Parsing.Types
import Language.Haskell.SourceGraph.Analyse.Utils
import Language.Haskell.SourceGraph.Analyse.GraphRepr
import Language.Haskell.SourceGraph.Analyse.Visualise

import Data.Graph.Analysis

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA

Interacting with GraphData from Graphalyze.
-}
module Analyse.GraphRepr
module Language.Haskell.SourceGraph.Analyse.GraphRepr
( -- * General stuff
GData(..)
, mapData
Expand Down Expand Up @@ -62,9 +62,9 @@ module Analyse.GraphRepr
, ModGraph
) where

import Analyse.Colors
import Analyse.Utils
import Parsing.Types
import Language.Haskell.SourceGraph.Analyse.Colors
import Language.Haskell.SourceGraph.Analyse.Utils
import Language.Haskell.SourceGraph.Parsing.Types

import Data.Graph.Analysis
import Data.Graph.Inductive
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -27,12 +27,12 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA

Analysis of Haskell module importing.
-}
module Analyse.Imports (analyseImports) where
module Language.Haskell.SourceGraph.Analyse.Imports (analyseImports) where

import Parsing.Types
import Analyse.Utils
import Analyse.GraphRepr
import Analyse.Visualise
import Language.Haskell.SourceGraph.Parsing.Types
import Language.Haskell.SourceGraph.Analyse.Utils
import Language.Haskell.SourceGraph.Analyse.GraphRepr
import Language.Haskell.SourceGraph.Analyse.Visualise

import Data.Graph.Analysis

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -27,12 +27,12 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA

Analysis of Haskell modules.
-}
module Analyse.Module(analyseModules) where
module Language.Haskell.SourceGraph.Analyse.Module(analyseModules,moduleToGraph) where

import Parsing.Types
import Analyse.Utils
import Analyse.GraphRepr
import Analyse.Visualise
import Language.Haskell.SourceGraph.Parsing.Types
import Language.Haskell.SourceGraph.Analyse.Utils
import Language.Haskell.SourceGraph.Analyse.GraphRepr
import Language.Haskell.SourceGraph.Analyse.Visualise

import Data.Graph.Analysis

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA

Utility functions and types for analysis.
-}
module Analyse.Utils where
module Language.Haskell.SourceGraph.Analyse.Utils where

import Data.Graph.Analysis hiding (Bold)

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -27,12 +27,12 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA

Utility functions and types for analysis.
-}
module Analyse.Visualise where
module Language.Haskell.SourceGraph.Analyse.Visualise where

import Analyse.Colors
import Analyse.GraphRepr
import Analyse.Utils
import Parsing.Types
import Language.Haskell.SourceGraph.Analyse.Colors
import Language.Haskell.SourceGraph.Analyse.GraphRepr
import Language.Haskell.SourceGraph.Analyse.Utils
import Language.Haskell.SourceGraph.Parsing.Types

import Data.Graph.Analysis hiding (Bold)
import Data.GraphViz
Expand Down
46 changes: 35 additions & 11 deletions CabalInfo.hs → Language/Haskell/SourceGraph/CabalInfo.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,8 @@
{-# LANGUAGE CPP #-}
#if !defined(MIN_VERSION_Cabal)
# define MIN_VERSION_Cabal(a,b,c) 0
#endif

{-
Copyright (C) 2009 Ivan Lazar Miljenovic <Ivan.Miljenovic@gmail.com>

Expand Down Expand Up @@ -27,17 +32,21 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA

Used to parse and obtain information from the provided Cabal file.
-}
module CabalInfo(parseCabal) where
module Language.Haskell.SourceGraph.CabalInfo(parseCabal) where

import Distribution.Compiler (CompilerInfo)
import Distribution.ModuleName (toFilePath)
import Distribution.Package
import Distribution.PackageDescription hiding (author)
import Distribution.PackageDescription.Configuration
#if MIN_VERSION_Cabal(2,0,0)
import Distribution.PackageDescription.Parsec
#else
import Distribution.PackageDescription.Parse
#endif
import Distribution.Simple.Compiler (compilerInfo)
import Distribution.Simple.GHC (configure)
import Distribution.Simple.Program (defaultProgramConfiguration)
import Distribution.Simple.Program (defaultProgramDb)
import Distribution.System (buildPlatform)
import Distribution.Verbosity (silent)

Expand All @@ -46,12 +55,26 @@ import Control.Monad (liftM)
import Data.List (nub)
import Data.Maybe (fromJust, isJust)
import System.FilePath (dropExtension)
import Distribution.Types.ComponentRequestedSpec (defaultComponentRequestedSpec)

-- -----------------------------------------------------------------------------

emptyFlagAssignment :: FlagAssignment
#if MIN_VERSION_Cabal(2,0,0)
emptyFlagAssignment = mkFlagAssignment []
#else
emptyFlagAssignment = []
#endif

#if MIN_VERSION_Cabal(2,0,0)
readDescription = readGenericPackageDescription
#else
readDescription = readPackageDescription
#endif

ghcID :: IO CompilerInfo
ghcID = liftM (compilerInfo . getCompiler)
$ configure silent Nothing Nothing defaultProgramConfiguration
$ configure silent Nothing Nothing defaultProgramDb
where
getCompiler (comp,_mplat,_progconfig) = comp

Expand All @@ -61,19 +84,20 @@ parseCabal fp = do cID <- ghcID
where
-- Need to specify the Exception type
getDesc :: FilePath -> IO (Either SomeException GenericPackageDescription)
getDesc = try . readPackageDescription silent
getDesc = try . readDescription silent
parseDesc cID = fmap parse . compactEithers . fmap (unGeneric cID)
unGeneric cID = fmap fst
. finalizePackageDescription [] -- flags, use later
(const True) -- ignore
-- deps
buildPlatform
cID
[]
. finalizePD emptyFlagAssignment -- flags, use later
defaultComponentRequestedSpec
(const True) -- ignore
-- deps
buildPlatform
cID
[]
parse pd = (nm, exps)
where
nm = pName . pkgName $ package pd
pName (PackageName nm') = nm'
pName nm' = unPackageName nm'
exes = filter (buildable . buildInfo) $ executables pd
lib = library pd
moduleNames = map toFilePath
Expand Down
Loading