Skip to content

Commit

Permalink
Turn the damlc module hierarchy into something a bit more sane (digit…
Browse files Browse the repository at this point in the history
…al-asset#2061)

This should hopefully be the last large reshuffling PR. I’ll write a
description of the new layout in the readme in a separate PR.
  • Loading branch information
cocreature authored Jul 9, 2019
1 parent 5567a55 commit 13253d8
Show file tree
Hide file tree
Showing 46 changed files with 115 additions and 112 deletions.
2 changes: 1 addition & 1 deletion .hlint.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -97,7 +97,7 @@
# - {name: Control.Arrow, within: []} # Certain modules are banned entirely
#
- functions:
- {name: unsafePerformIO, within: [DA.Daml.GHC.Compiler.UtilGHC]}
- {name: unsafePerformIO, within: [DA.Daml.LFConversion.UtilGHC]}
- {name: unsafeInterleaveIO, within: []}
- {name: unsafeDupablePerformIO, within: []}
- {name: setCurrentDirectory, within: [DAML.Assistant.Tests, Main]}
Expand Down
2 changes: 1 addition & 1 deletion BAZEL.md
Original file line number Diff line number Diff line change
Expand Up @@ -538,7 +538,7 @@ One specific library in the `daml-foundations` stack is
da_haskell_library(
name = "daml-ghc-compiler",
srcs = glob([
"src/DA/Daml/GHC/Compiler/**/*.hs",
"src/**/*.hs",
]),
src_strip_prefix = "src",
deps = [
Expand Down
2 changes: 1 addition & 1 deletion compiler/daml-extension/src/extension.ts
Original file line number Diff line number Diff line change
Expand Up @@ -180,7 +180,7 @@ let keepAliveInterval = 60000; // Send KA every 60s.
// NOTE(JM): If you change this, make sure to also change the server-side timeouts to get
// detailed errors rather than cause a restart.
// Legacy DAML timeout for language server is defined in
// DA.Service.Daml.LanguageServer.
// DA.Daml.LanguageServer.
let keepAliveTimeout = 120000;

function startKeepAliveWatchdog() {
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@

{-# LANGUAGE OverloadedStrings #-}

module DA.Service.Daml.Compiler.Impl.Dar
module DA.Daml.Compiler.Dar
( buildDar
, FromDalf(..)
) where
Expand All @@ -30,7 +30,7 @@ import Development.IDE.Core.RuleTypes.Daml
import Development.IDE.Core.API
import Development.IDE.Types.Location
import qualified Development.IDE.Types.Logger as IdeLogger
import DA.Daml.GHC.Compiler.Options.Types
import DA.Daml.Options.Types
import qualified DA.Daml.LF.Ast as LF
import DA.Daml.LF.Proto3.Archive (encodeArchiveLazy)

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@
{-# LANGUAGE DisambiguateRecordFields #-}

-- | Compiles, generates and creates scenarios for DAML-LF
module DA.Service.Daml.Compiler.Impl.Scenario (
module DA.Daml.Compiler.Scenario (
SS.Handle
, EnableScenarioService(..)
, withScenarioService
Expand All @@ -15,7 +15,7 @@ module DA.Service.Daml.Compiler.Impl.Scenario (
, SS.defaultScenarioServiceConfig
) where

import DA.Daml.GHC.Compiler.Options.Types
import DA.Daml.Options.Types
import qualified DA.Daml.LF.ScenarioServiceClient as SS
import qualified DA.Service.Logger as Logger
import Control.Monad.IO.Class (liftIO)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -4,15 +4,15 @@

{-# LANGUAGE OverloadedStrings #-}

module DA.Service.Daml.Compiler.Impl.Upgrade
module DA.Daml.Compiler.Upgrade
( generateUpgradeModule
, generateGenInstancesModule
, generateSrcFromLf
) where

import "ghc-lib-parser" BasicTypes
import Control.Lens (toListOf)
import DA.Daml.GHC.Compiler.Generics
import DA.Daml.Preprocessor.Generics
import qualified DA.Daml.LF.Ast.Base as LF
import DA.Daml.LF.Ast.Optics
import qualified DA.Daml.LF.Ast.Util as LF
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,9 +3,9 @@

{-# LANGUAGE OverloadedStrings #-}

module DA.Daml.GHC.Damldoc.Annotate(applyAnnotations) where
module DA.Daml.Doc.Annotate(applyAnnotations) where

import DA.Daml.GHC.Damldoc.Types
import DA.Daml.Doc.Types
import qualified Data.Text as T
import Data.List.Extra

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,16 +3,16 @@

{-# LANGUAGE OverloadedStrings #-}

module DA.Daml.GHC.Damldoc.Driver(
module DA.Daml.Doc.Driver(
damlDocDriver,
InputFormat(..), DocFormat(..)
, DocOption(..)
) where

import DA.Daml.GHC.Damldoc.Types
import DA.Daml.GHC.Damldoc.Render
import DA.Daml.GHC.Damldoc.HaddockParse
import DA.Daml.GHC.Damldoc.Transform
import DA.Daml.Doc.Types
import DA.Daml.Doc.Render
import DA.Daml.Doc.HaddockParse
import DA.Daml.Doc.Transform
import Development.IDE.Types.Location
import Development.IDE.Types.Diagnostics
import Development.IDE.Types.Options
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,9 +3,9 @@

{-# LANGUAGE OverloadedStrings #-}

module DA.Daml.GHC.Damldoc.HaddockParse(mkDocs) where
module DA.Daml.Doc.HaddockParse(mkDocs) where

import DA.Daml.GHC.Damldoc.Types as DDoc
import DA.Daml.Doc.Types as DDoc
import Development.IDE.Types.Options (IdeOptions(..))
import Development.IDE.Core.FileStore
import qualified Development.IDE.Core.Service as Service
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@

{-# LANGUAGE OverloadedStrings #-}

module DA.Daml.GHC.Damldoc.Render
module DA.Daml.Doc.Render
( DocFormat(..)
, renderSimpleRst
, renderSimpleMD
Expand All @@ -12,10 +12,10 @@ module DA.Daml.GHC.Damldoc.Render
, jsonConf
) where

import DA.Daml.GHC.Damldoc.Render.Rst
import DA.Daml.GHC.Damldoc.Render.Markdown
import DA.Daml.GHC.Damldoc.Render.Hoogle
import DA.Daml.GHC.Damldoc.Types
import DA.Daml.Doc.Render.Rst
import DA.Daml.Doc.Render.Markdown
import DA.Daml.Doc.Render.Hoogle
import DA.Daml.Doc.Types

import qualified CMarkGFM as GFM
import qualified Data.Aeson.Encode.Pretty as AP
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@
-- satisfy the regex /[a-z0-9]+(-[a-z0-9]+)*/). It's also nice for them to be readable.
-- So we generate a human readable tag, and append a hash to guarantee uniqueness.

module DA.Daml.GHC.Damldoc.Render.Anchor
module DA.Daml.Doc.Render.Anchor
( Anchor
, moduleAnchor
, classAnchor
Expand All @@ -19,7 +19,7 @@ module DA.Daml.GHC.Damldoc.Render.Anchor
, functionAnchor
) where

import DA.Daml.GHC.Damldoc.Types
import DA.Daml.Doc.Types
import Data.Hashable
import qualified Data.Text as T
import qualified Data.Char as C
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,13 +3,13 @@

{-# LANGUAGE OverloadedStrings #-}

module DA.Daml.GHC.Damldoc.Render.Hoogle
module DA.Daml.Doc.Render.Hoogle
( renderSimpleHoogle
) where

import DA.Daml.GHC.Damldoc.Types
import DA.Daml.GHC.Damldoc.Render.Anchor
import DA.Daml.GHC.Damldoc.Render.Util
import DA.Daml.Doc.Types
import DA.Daml.Doc.Render.Anchor
import DA.Daml.Doc.Render.Util

import Data.Maybe
import qualified Data.Text as T
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,12 +3,12 @@

{-# LANGUAGE OverloadedStrings #-}

module DA.Daml.GHC.Damldoc.Render.Markdown
module DA.Daml.Doc.Render.Markdown
( renderSimpleMD
) where

import DA.Daml.GHC.Damldoc.Types
import DA.Daml.GHC.Damldoc.Render.Util
import DA.Daml.Doc.Types
import DA.Daml.Doc.Render.Util

import Data.Maybe
import qualified Data.Text as T
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,13 +3,13 @@

{-# LANGUAGE OverloadedStrings #-}

module DA.Daml.GHC.Damldoc.Render.Rst
module DA.Daml.Doc.Render.Rst
( renderSimpleRst
) where

import DA.Daml.GHC.Damldoc.Types
import DA.Daml.GHC.Damldoc.Render.Util
import DA.Daml.GHC.Damldoc.Render.Anchor
import DA.Daml.Doc.Types
import DA.Daml.Doc.Render.Util
import DA.Daml.Doc.Render.Anchor

import qualified Data.Text.Prettyprint.Doc as Pretty
import Data.Text.Prettyprint.Doc (Doc, defaultLayoutOptions, layoutPretty, pretty, (<+>))
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@

{-# LANGUAGE OverloadedStrings #-}

module DA.Daml.GHC.Damldoc.Render.Util
module DA.Daml.Doc.Render.Util
( adjust
, prefix
, indent
Expand Down
Original file line number Diff line number Diff line change
@@ -1,13 +1,13 @@
-- Copyright (c) 2019 Digital Asset (Switzerland) GmbH and/or its affiliates. All rights reserved.
-- SPDX-License-Identifier: Apache-2.0

module DA.Daml.GHC.Damldoc.Transform
module DA.Daml.Doc.Transform
( DocOption(..)
, applyTransform
) where

import DA.Daml.GHC.Damldoc.Types
import DA.Daml.GHC.Damldoc.Annotate
import DA.Daml.Doc.Types
import DA.Daml.Doc.Annotate

import Data.Maybe
import Data.List.Extra
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,8 @@

{-# LANGUAGE DerivingStrategies #-}

module DA.Daml.GHC.Damldoc.Types(
module DA.Daml.GHC.Damldoc.Types
module DA.Daml.Doc.Types(
module DA.Daml.Doc.Types
) where

import Data.Aeson
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,11 +3,11 @@

{-# LANGUAGE OverloadedStrings #-}

module DA.Daml.GHC.Damldoc.Render.Tests(mkTestTree)
module DA.Daml.Doc.Render.Tests(mkTestTree)
where

import DA.Daml.GHC.Damldoc.Types
import DA.Daml.GHC.Damldoc.Render
import DA.Daml.Doc.Types
import DA.Daml.Doc.Render

import Control.Monad.Except
import qualified Data.Text as T
Expand All @@ -20,7 +20,7 @@ import Test.Tasty.HUnit

mkTestTree :: IO Tasty.TestTree
mkTestTree = do
pure $ Tasty.testGroup "DA.Daml.GHC.Damldoc.Render"
pure $ Tasty.testGroup "DA.Daml.Doc.Render"
[ Tasty.testGroup "RST Rendering" $
zipWith (renderTest Rst) cases expectRst
, Tasty.testGroup "Markdown Rendering" $
Expand Down
14 changes: 7 additions & 7 deletions compiler/damlc/daml-doc/test/DA/Daml/GHC/Damldoc/Tests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,15 +3,15 @@

{-# LANGUAGE OverloadedStrings #-}

module DA.Daml.GHC.Damldoc.Tests(mkTestTree)
module DA.Daml.Doc.Tests(mkTestTree)
where

import DA.Bazel.Runfiles
import DA.Daml.GHC.Compiler.Options
import DA.Daml.GHC.Compiler.Options.Types
import DA.Daml.GHC.Damldoc.HaddockParse
import DA.Daml.GHC.Damldoc.Render
import DA.Daml.GHC.Damldoc.Types
import DA.Daml.Options
import DA.Daml.Options.Types
import DA.Daml.Doc.HaddockParse
import DA.Daml.Doc.Render
import DA.Daml.Doc.Types
import DA.Test.Util
import Development.IDE.Types.Location

Expand Down Expand Up @@ -43,7 +43,7 @@ mkTestTree = do
let goldenSrcs = nubOrd $ map (flip replaceExtensions "daml") expectFiles
goldenTests <- mapM (fileTest . (testDir </>)) goldenSrcs

pure $ Tasty.testGroup "DA.Daml.GHC.Damldoc" $ unitTests <> concat goldenTests
pure $ Tasty.testGroup "DA.Daml.Doc" $ unitTests <> concat goldenTests

unitTests :: [Tasty.TestTree]
unitTests =
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ import Control.Monad.Extra
import Control.Monad.Trans.Maybe
import Development.IDE.Core.OfInterest
import Development.IDE.Types.Logger hiding (Priority)
import DA.Daml.GHC.Compiler.Options.Types
import DA.Daml.Options.Types
import qualified Text.PrettyPrint.Annotated.HughesPJClass as Pretty
import Development.IDE.Types.Location as Base
import Data.Aeson hiding (Options)
Expand Down Expand Up @@ -49,8 +49,8 @@ import qualified Language.Haskell.LSP.Types as LSP

import Development.IDE.Core.RuleTypes.Daml

import DA.Daml.GHC.Compiler.Convert (convertModule, sourceLocToRange)
import DA.Daml.GHC.Compiler.UtilLF
import DA.Daml.LFConversion (convertModule, sourceLocToRange)
import DA.Daml.LFConversion.UtilLF
import qualified DA.Daml.LF.Ast as LF
import qualified DA.Daml.LF.InferSerializability as Serializability
import qualified DA.Daml.LF.PrettyScenario as LF
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ import Development.IDE.Types.Location
import Development.IDE.Types.Options
import qualified Language.Haskell.LSP.Messages as LSP

import DA.Daml.GHC.Compiler.Options.Types
import DA.Daml.Options.Types
import qualified DA.Daml.LF.Ast as LF
import qualified DA.Daml.LF.ScenarioServiceClient as SS

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -41,11 +41,11 @@ module Development.IDE.Core.API.Testing
import qualified Development.IDE.Core.API as API
import qualified Development.IDE.Types.Diagnostics as D
import qualified Development.IDE.Types.Location as D
import DA.Service.Daml.Compiler.Impl.Scenario as SS
import DA.Daml.Compiler.Scenario as SS
import Development.IDE.Core.Rules.Daml
import Development.IDE.Types.Logger
import DA.Daml.GHC.Compiler.Options
import DA.Daml.GHC.Compiler.Options.Types
import DA.Daml.Options
import DA.Daml.Options.Types
import Development.IDE.Core.Service.Daml(VirtualResource(..), mkDamlEnv)
import DA.Test.Util (standardizeQuotes)
import Language.Haskell.LSP.Messages (FromServerMessage(..))
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}

module DA.Service.Daml.LanguageServer
module DA.Daml.LanguageServer
( runLanguageServer
) where

Expand All @@ -15,7 +15,7 @@ import qualified Development.IDE.LSP.LanguageServer as LS
import Control.Monad.Extra
import Data.Default

import DA.Service.Daml.LanguageServer.CodeLens
import DA.Daml.LanguageServer.CodeLens
import Development.IDE.Types.Logger

import qualified Data.Aeson as Aeson
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -4,11 +4,11 @@
{-# LANGUAGE OverloadedStrings #-}

-- | Gather code lenses like scenario execution for a DAML file.
module DA.Service.Daml.LanguageServer.CodeLens
module DA.Daml.LanguageServer.CodeLens
( setHandlersCodeLens
) where

import DA.Daml.GHC.Compiler.UtilLF (sourceLocToRange)
import DA.Daml.LFConversion.UtilLF (sourceLocToRange)
import qualified DA.Daml.LF.Ast as LF
import Language.Haskell.LSP.Types
import qualified Data.Aeson as Aeson
Expand Down
Loading

0 comments on commit 13253d8

Please sign in to comment.