mirror of
https://github.com/github/semantic.git
synced 2024-11-28 01:47:01 +03:00
Add export lists to modules missing them.
This commit is contained in:
parent
fb93abff18
commit
bdd75e6e7c
@ -83,7 +83,6 @@ library
|
||||
, Data.Language
|
||||
, Data.Map.Monoidal
|
||||
, Data.Mergeable
|
||||
, Data.Options
|
||||
, Data.Patch
|
||||
, Data.Project
|
||||
, Data.Range
|
||||
@ -251,7 +250,7 @@ library
|
||||
if flag(release)
|
||||
ghc-options: -Wall -Werror -Wcompat -Wincomplete-record-updates -Wincomplete-uni-patterns -Wredundant-constraints -fno-warn-name-shadowing -O1 -j
|
||||
else
|
||||
ghc-options: -Wall -Wcompat -Wincomplete-record-updates -Wincomplete-uni-patterns -Wredundant-constraints -fno-warn-name-shadowing -O0 -j
|
||||
ghc-options: -Wall -Werror -Wmissing-export-lists -Wcompat -Wincomplete-record-updates -Wincomplete-uni-patterns -Wredundant-constraints -fno-warn-name-shadowing -O0 -j
|
||||
ghc-prof-options: -fprof-auto
|
||||
|
||||
executable semantic
|
||||
|
@ -1,4 +1,8 @@
|
||||
module Control.Abstract.Hole where
|
||||
module Control.Abstract.Hole
|
||||
( AbstractHole (..)
|
||||
, Hole (..)
|
||||
, toMaybe
|
||||
) where
|
||||
|
||||
class AbstractHole a where
|
||||
hole :: a
|
||||
|
@ -1,4 +1,11 @@
|
||||
module Control.Abstract.Primitive where
|
||||
module Control.Abstract.Primitive
|
||||
( define
|
||||
, defineClass
|
||||
, defineNamespace
|
||||
, builtInPrint
|
||||
, builtInExport
|
||||
, lambda
|
||||
) where
|
||||
|
||||
import Control.Abstract.Context
|
||||
import Control.Abstract.Environment
|
||||
|
@ -1,5 +1,10 @@
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
module Data.AST where
|
||||
module Data.AST
|
||||
( Node (..)
|
||||
, AST
|
||||
, Location
|
||||
, nodeLocation
|
||||
) where
|
||||
|
||||
import Data.Range
|
||||
import Data.Record
|
||||
|
@ -1,5 +1,11 @@
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies #-}
|
||||
module Data.Abstract.Address where
|
||||
module Data.Abstract.Address
|
||||
( Precise (..)
|
||||
, Located (..)
|
||||
, Latest (..)
|
||||
, All (..)
|
||||
, Monovariant (..)
|
||||
) where
|
||||
|
||||
import Data.Abstract.Module (ModuleInfo)
|
||||
import Data.Abstract.Name
|
||||
|
@ -1,5 +1,13 @@
|
||||
{-# LANGUAGE ConstraintKinds, GeneralizedNewtypeDeriving, TypeFamilies #-}
|
||||
module Data.Abstract.Cache where
|
||||
module Data.Abstract.Cache
|
||||
( Cache
|
||||
, Cached (..)
|
||||
, Cacheable
|
||||
, cacheLookup
|
||||
, cacheSet
|
||||
, cacheInsert
|
||||
, cacheKeys
|
||||
) where
|
||||
|
||||
import Data.Abstract.Configuration
|
||||
import Data.Abstract.Heap
|
||||
|
@ -1,4 +1,4 @@
|
||||
module Data.Abstract.Configuration where
|
||||
module Data.Abstract.Configuration ( Configuration (..) ) where
|
||||
|
||||
import Data.Abstract.Environment
|
||||
import Data.Abstract.Heap
|
||||
|
@ -1,5 +1,8 @@
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving, UndecidableInstances #-}
|
||||
module Data.Abstract.Declarations where
|
||||
module Data.Abstract.Declarations
|
||||
( Declarations (..)
|
||||
, Declarations1 (..)
|
||||
) where
|
||||
|
||||
import Data.Abstract.Name
|
||||
import Data.Sum
|
||||
|
@ -1,5 +1,8 @@
|
||||
{-# LANGUAGE DefaultSignatures, GeneralizedNewtypeDeriving, UndecidableInstances #-}
|
||||
module Data.Abstract.FreeVariables where
|
||||
module Data.Abstract.FreeVariables
|
||||
( FreeVariables (..)
|
||||
, FreeVariables1 (..)
|
||||
) where
|
||||
|
||||
import Data.Abstract.Name
|
||||
import Data.Sum
|
||||
|
@ -1,5 +1,13 @@
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
module Data.Abstract.Heap where
|
||||
module Data.Abstract.Heap
|
||||
( Heap
|
||||
, heapLookup
|
||||
, heapLookupAll
|
||||
, heapInsert
|
||||
, heapInit
|
||||
, heapSize
|
||||
, heapRestrict
|
||||
) where
|
||||
|
||||
import Data.Abstract.Live
|
||||
import qualified Data.Map.Monoidal as Monoidal
|
||||
|
@ -1,5 +1,15 @@
|
||||
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, TypeFamilies, TypeOperators #-}
|
||||
module Data.Abstract.Live where
|
||||
module Data.Abstract.Live
|
||||
( Live (..)
|
||||
, fromAddresses
|
||||
, liveSingleton
|
||||
, liveInsert
|
||||
, liveDelete
|
||||
, liveDifference
|
||||
, liveMember
|
||||
, liveSplit
|
||||
, liveMap
|
||||
) where
|
||||
|
||||
import Data.Set as Set
|
||||
import Prologue
|
||||
|
@ -1,4 +1,9 @@
|
||||
module Data.Abstract.Package where
|
||||
module Data.Abstract.Package
|
||||
( Package (..)
|
||||
, PackageInfo (..)
|
||||
, PackageName
|
||||
, Data.Abstract.Package.fromModules
|
||||
) where
|
||||
|
||||
import Data.Abstract.Module
|
||||
import Data.Abstract.ModuleTable as ModuleTable
|
||||
|
@ -1,4 +1,8 @@
|
||||
module Data.Abstract.Path where
|
||||
module Data.Abstract.Path
|
||||
( dropRelativePrefix
|
||||
, joinPaths
|
||||
, stripQuotes
|
||||
) where
|
||||
|
||||
import Prologue
|
||||
import qualified Data.Text as T
|
||||
|
@ -1,5 +1,8 @@
|
||||
{-# LANGUAGE GADTs #-}
|
||||
module Data.Abstract.Ref where
|
||||
module Data.Abstract.Ref
|
||||
( ValueRef (..)
|
||||
, Ref (..)
|
||||
) where
|
||||
|
||||
import Data.Abstract.Name
|
||||
|
||||
|
@ -1,5 +1,5 @@
|
||||
{-# LANGUAGE GADTs, UndecidableInstances #-}
|
||||
module Data.Abstract.Value.Abstract where
|
||||
module Data.Abstract.Value.Abstract ( Abstract (..) ) where
|
||||
|
||||
import Control.Abstract
|
||||
import Data.Abstract.Environment as Env
|
||||
|
@ -1,5 +1,12 @@
|
||||
{-# LANGUAGE GADTs, RankNTypes, TypeOperators, UndecidableInstances, LambdaCase #-}
|
||||
module Data.Abstract.Value.Concrete where
|
||||
module Data.Abstract.Value.Concrete
|
||||
( Value (..)
|
||||
, ValueError (..)
|
||||
, ClosureBody (..)
|
||||
, runValueError
|
||||
, runValueErrorWith
|
||||
, throwValueError
|
||||
) where
|
||||
|
||||
import Control.Abstract
|
||||
import Data.Abstract.Environment (Environment, Bindings)
|
||||
|
@ -6,14 +6,14 @@ module Data.Graph.Vertex
|
||||
, vertexToType
|
||||
) where
|
||||
|
||||
import Prologue hiding (packageName)
|
||||
import Prologue
|
||||
|
||||
import Data.Aeson
|
||||
import qualified Data.Text as T
|
||||
|
||||
import Data.Abstract.Module (ModuleInfo (..))
|
||||
import Data.Abstract.Name
|
||||
import Data.Abstract.Package (PackageInfo (..))
|
||||
import Data.Abstract.Package hiding (Package (Package))
|
||||
|
||||
-- | A vertex of some specific type.
|
||||
data Vertex
|
||||
@ -23,7 +23,7 @@ data Vertex
|
||||
deriving (Eq, Ord, Show, Generic, Hashable)
|
||||
|
||||
packageVertex :: PackageInfo -> Vertex
|
||||
packageVertex = Package . formatName . packageName
|
||||
packageVertex = Package . formatName . Data.Abstract.Package.packageName
|
||||
|
||||
moduleVertex :: ModuleInfo -> Vertex
|
||||
moduleVertex = Module . T.pack . modulePath
|
||||
|
@ -1,5 +1,12 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, LambdaCase #-}
|
||||
module Data.Language where
|
||||
module Data.Language
|
||||
( Language (..)
|
||||
, ensureLanguage
|
||||
, extensionsForLanguage
|
||||
, knownLanguage
|
||||
, languageForFilePath
|
||||
, languageForType
|
||||
) where
|
||||
|
||||
import Data.Aeson
|
||||
import Data.Char (toUpper)
|
||||
|
@ -1,5 +1,5 @@
|
||||
{-# LANGUAGE DefaultSignatures, TypeOperators, UndecidableInstances #-}
|
||||
module Data.Mergeable where
|
||||
module Data.Mergeable ( Mergeable (..) ) where
|
||||
|
||||
import Control.Applicative
|
||||
import Data.Functor.Identity
|
||||
|
@ -1 +0,0 @@
|
||||
module Data.Options where
|
@ -1,5 +1,10 @@
|
||||
{-# LANGUAGE ConstraintKinds, DataKinds, GADTs, KindSignatures, MultiParamTypeClasses, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||
module Data.Record where
|
||||
module Data.Record
|
||||
( Record (..)
|
||||
, HasField (..)
|
||||
, rhead
|
||||
, rtail
|
||||
) where
|
||||
|
||||
import Data.Aeson
|
||||
import Data.JSON.Fields
|
||||
|
@ -1,4 +1,7 @@
|
||||
module Data.SplitDiff where
|
||||
module Data.SplitDiff
|
||||
( SplitPatch (..)
|
||||
, getRange
|
||||
) where
|
||||
|
||||
import Control.Monad.Free
|
||||
import Data.Range
|
||||
@ -20,6 +23,3 @@ getRange diff = getField $ case diff of
|
||||
|
||||
-- | A diff with only one side’s annotations.
|
||||
type SplitDiff syntax ann = Free (TermF syntax ann) (SplitPatch (Term syntax ann))
|
||||
|
||||
unSplit :: Functor syntax => SplitDiff syntax ann -> Term syntax ann
|
||||
unSplit = iter Term . fmap splitTerm
|
||||
|
@ -1,5 +1,5 @@
|
||||
{-# LANGUAGE AllowAmbiguousTypes, DeriveAnyClass, GADTs, TypeOperators, MultiParamTypeClasses, UndecidableInstances, ScopedTypeVariables, KindSignatures, RankNTypes, ConstraintKinds, GeneralizedNewtypeDeriving, DerivingStrategies #-}
|
||||
{-# OPTIONS_GHC -Wno-redundant-constraints -fno-warn-orphans #-} -- For HasCallStack
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists -Wno-redundant-constraints -fno-warn-orphans #-} -- For HasCallStack
|
||||
module Data.Syntax where
|
||||
|
||||
import Data.Abstract.Evaluatable
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE DeriveAnyClass, MultiParamTypeClasses #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Data.Syntax.Comment where
|
||||
|
||||
import Data.Abstract.Evaluatable
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE DeriveAnyClass, MultiParamTypeClasses, ScopedTypeVariables, UndecidableInstances #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Data.Syntax.Declaration where
|
||||
|
||||
import qualified Data.Abstract.Environment as Env
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE DeriveAnyClass, MultiParamTypeClasses, ScopedTypeVariables, UndecidableInstances #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Data.Syntax.Directive where
|
||||
|
||||
import Data.Abstract.Evaluatable
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE DeriveAnyClass, MultiParamTypeClasses, ScopedTypeVariables, UndecidableInstances, DuplicateRecordFields #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Data.Syntax.Expression where
|
||||
|
||||
import Data.Abstract.Evaluatable hiding (Member)
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE DeriveAnyClass, ViewPatterns, ScopedTypeVariables, DuplicateRecordFields #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Data.Syntax.Literal where
|
||||
|
||||
import Data.Abstract.Evaluatable
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE DeriveAnyClass, ScopedTypeVariables, UndecidableInstances, ViewPatterns, DuplicateRecordFields #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Data.Syntax.Statement where
|
||||
|
||||
import Data.Abstract.Evaluatable
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE DataKinds, DeriveAnyClass, DeriveGeneric, MultiParamTypeClasses, UndecidableInstances #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Data.Syntax.Type where
|
||||
|
||||
import Data.Abstract.Evaluatable
|
||||
|
@ -1,5 +1,18 @@
|
||||
{-# LANGUAGE DefaultSignatures, GADTs, TypeOperators, UndecidableInstances #-}
|
||||
module Diffing.Algorithm where
|
||||
module Diffing.Algorithm
|
||||
( AlgorithmF (..)
|
||||
, Algorithm
|
||||
, Diffable (..)
|
||||
, Equivalence (..)
|
||||
, diff
|
||||
, diffThese
|
||||
, diffMaybe
|
||||
, linearly
|
||||
, byReplacing
|
||||
, comparableTerms
|
||||
, equivalentTerms
|
||||
, algorithmForTerms
|
||||
) where
|
||||
|
||||
import Control.Monad.Free.Freer
|
||||
import Data.Diff
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.Go.Grammar where
|
||||
|
||||
import Language.Haskell.TH
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.Go.Syntax where
|
||||
|
||||
import Data.Abstract.Evaluatable
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.Go.Type where
|
||||
|
||||
import Prologue
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.Haskell.Grammar where
|
||||
|
||||
import Language.Haskell.TH
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.Haskell.Syntax where
|
||||
|
||||
import Data.Abstract.Evaluatable
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.JSON.Grammar where
|
||||
|
||||
import Language.Haskell.TH
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.Java.Grammar where
|
||||
|
||||
import Language.Haskell.TH
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.Java.Syntax where
|
||||
|
||||
import Data.Abstract.Evaluatable
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.Markdown.Syntax where
|
||||
|
||||
import Prologue hiding (Text)
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.PHP.Grammar where
|
||||
|
||||
import Language.Haskell.TH
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.PHP.Syntax where
|
||||
|
||||
import Data.Abstract.Evaluatable
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.Python.Grammar where
|
||||
|
||||
import Language.Haskell.TH
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.Python.Syntax where
|
||||
|
||||
import Data.Abstract.Environment as Env
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.Ruby.Grammar where
|
||||
|
||||
import Language.Haskell.TH
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields, TupleSections #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.Ruby.Syntax where
|
||||
|
||||
import Control.Monad (unless)
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.TypeScript.Grammar where
|
||||
|
||||
import Language.Haskell.TH
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.TypeScript.Syntax where
|
||||
|
||||
import qualified Data.Abstract.Environment as Env
|
||||
|
@ -1,5 +1,11 @@
|
||||
{-# LANGUAGE GADTs, RankNTypes #-}
|
||||
module Semantic.AST where
|
||||
module Semantic.AST
|
||||
( SomeAST (..)
|
||||
, withSomeAST
|
||||
, astParseBlob
|
||||
, ASTFormat (..)
|
||||
, runASTParse
|
||||
) where
|
||||
|
||||
import Data.AST
|
||||
import Data.Blob
|
||||
|
@ -1,6 +1,17 @@
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
|
||||
module Semantic.Config where
|
||||
module Semantic.Config
|
||||
( Config (..)
|
||||
, defaultConfig
|
||||
, Options (..)
|
||||
, defaultOptions
|
||||
, debugOptions
|
||||
, lookupStatsAddr
|
||||
, withHaystackFromConfig
|
||||
, withLoggerFromConfig
|
||||
, withStatterFromConfig
|
||||
, withTelemetry
|
||||
) where
|
||||
|
||||
import Network.BSD
|
||||
import Network.HTTP.Client.TLS
|
||||
|
@ -1,5 +1,11 @@
|
||||
{-# LANGUAGE ConstraintKinds, GADTs, RankNTypes, ScopedTypeVariables #-}
|
||||
module Semantic.Diff where
|
||||
module Semantic.Diff
|
||||
( runDiff
|
||||
, runRubyDiff
|
||||
, runTypeScriptDiff
|
||||
, runJSONDiff
|
||||
, diffBlobTOCPairs
|
||||
) where
|
||||
|
||||
import Analysis.ConstructorName (ConstructorName)
|
||||
import Analysis.Declaration (HasDeclaration, declarationAlgebra)
|
||||
|
@ -1,4 +1,7 @@
|
||||
module Semantic.Env where
|
||||
module Semantic.Env
|
||||
( envLookupInt
|
||||
, envLookupString
|
||||
) where
|
||||
|
||||
import Control.Monad.IO.Class
|
||||
import Prologue
|
||||
|
@ -35,7 +35,7 @@ import qualified Data.Abstract.ModuleTable as ModuleTable
|
||||
import Data.Abstract.Package as Package
|
||||
import Data.Abstract.Value.Abstract
|
||||
import Data.Abstract.Value.Type
|
||||
import Data.Abstract.Value.Concrete (Value, ValueError (..), runValueErrorWith)
|
||||
import Data.Abstract.Value.Concrete (Value,ValueError (..), runValueErrorWith)
|
||||
import Data.Graph
|
||||
import Data.Project
|
||||
import Data.Record
|
||||
|
@ -1,5 +1,10 @@
|
||||
{-# LANGUAGE GADTs, RankNTypes #-}
|
||||
module Semantic.Parse where
|
||||
module Semantic.Parse
|
||||
( runParse
|
||||
, runRubyParse
|
||||
, runTypeScriptParse
|
||||
, runJSONParse
|
||||
) where
|
||||
|
||||
import Analysis.ConstructorName (ConstructorName)
|
||||
import Analysis.Declaration (HasDeclaration, declarationAlgebra)
|
||||
|
@ -1,5 +1,10 @@
|
||||
{-# LANGUAGE ConstraintKinds, GADTs, KindSignatures, ScopedTypeVariables, TypeOperators, UndecidableInstances #-}
|
||||
module Semantic.Resolution where
|
||||
module Semantic.Resolution
|
||||
( Resolution (..)
|
||||
, nodeJSResolutionMap
|
||||
, resolutionMap
|
||||
, runResolution
|
||||
) where
|
||||
|
||||
import Control.Monad.Effect
|
||||
import Data.Aeson
|
||||
|
@ -1,4 +1,10 @@
|
||||
module Semantic.Telemetry.Haystack where
|
||||
module Semantic.Telemetry.Haystack
|
||||
( HaystackClient (..)
|
||||
, ErrorReport (..)
|
||||
, ErrorLogger
|
||||
, haystackClient
|
||||
, reportError
|
||||
) where
|
||||
|
||||
import Control.Exception
|
||||
import Crypto.Hash
|
||||
|
@ -1,4 +1,12 @@
|
||||
module Semantic.Telemetry.Log where
|
||||
module Semantic.Telemetry.Log
|
||||
( Level (..)
|
||||
, LogOptions (..)
|
||||
, Message (..)
|
||||
, LogFormatter
|
||||
, logfmtFormatter
|
||||
, terminalFormatter
|
||||
, writeLogMessage
|
||||
) where
|
||||
|
||||
import Control.Monad.IO.Class
|
||||
import Data.Error (withSGRCode)
|
||||
|
@ -1,5 +1,5 @@
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies, TypeOperators #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-signatures #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-signatures -Wno-missing-export-lists #-}
|
||||
module Semantic.Util where
|
||||
|
||||
import Prelude hiding (readFile)
|
||||
|
@ -1,6 +1,9 @@
|
||||
{-# OPTIONS_GHC -fforce-recomp #-} -- So that gitHash is correct.
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
module Semantic.Version where
|
||||
module Semantic.Version
|
||||
( buildSHA
|
||||
, buildVersion
|
||||
) where
|
||||
|
||||
import Data.Version (showVersion)
|
||||
import Development.GitRev
|
||||
|
Loading…
Reference in New Issue
Block a user