summaryrefslogtreecommitdiff
path: root/libraries/ghc-boot-th
diff options
context:
space:
mode:
authorBen Gamari <bgamari.foss@gmail.com>2016-05-16 15:21:34 +0200
committerBen Gamari <ben@smart-cactus.org>2016-05-16 16:22:05 +0200
commiteed820b672e6c3d23106cd151b1e31ce29326e32 (patch)
tree48fd270edef8f7a50ef28f876b0d5e6a47e6313c /libraries/ghc-boot-th
parentd78faa135921dfe7a6b92f908171af1a2cdce512 (diff)
downloadhaskell-eed820b672e6c3d23106cd151b1e31ce29326e32.tar.gz
Move Extension type to ghc-boot-th
This creates a new package, `ghc-boot-th`, to contain the `Extension` type, which now lives in `GHC.LanguageExtension.Type`. This ensures that the transitive dependency set of the `template-haskell` package remains minimal. The `GHC.LanguageExtensions.Type` module is also re-exported by `ghc-boot`, which provides an orphan `binary` instance as well. Test Plan: Validate Reviewers: goldfire, thomie, hvr, austin Reviewed By: thomie Subscribers: RyanGlScott, thomie, erikd, ezyang Differential Revision: https://phabricator.haskell.org/D2224
Diffstat (limited to 'libraries/ghc-boot-th')
-rw-r--r--libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs132
-rw-r--r--libraries/ghc-boot-th/GHC/Lexeme.hs32
-rw-r--r--libraries/ghc-boot-th/LICENSE31
-rw-r--r--libraries/ghc-boot-th/changelog.md5
-rw-r--r--libraries/ghc-boot-th/ghc-boot-th.cabal.in37
5 files changed, 237 insertions, 0 deletions
diff --git a/libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs b/libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs
new file mode 100644
index 0000000000..39613b0c4b
--- /dev/null
+++ b/libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs
@@ -0,0 +1,132 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : GHC.LanguageExtensions.Type
+-- Copyright : (c) The GHC Team
+--
+-- Maintainer : ghc-devs@haskell.org
+-- Portability : portable
+--
+-- A data type defining the language extensions supported by GHC.
+--
+{-# LANGUAGE DeriveGeneric #-}
+module GHC.LanguageExtensions.Type ( Extension(..) ) where
+
+import GHC.Generics
+
+-- | The language extensions known to GHC.
+--
+-- Note that there is an orphan 'Binary' instance for this type supplied by
+-- the "GHC.LanguageExtensions" module provided by @ghc-boot@. We can't provide
+-- here as this would require adding transitive dependencies to the
+-- @template-haskell@ package, which must have a minimal dependency set.
+data Extension
+-- See Note [Updating flag description in the User's Guide] in DynFlags
+ = Cpp
+ | OverlappingInstances
+ | UndecidableInstances
+ | IncoherentInstances
+ | UndecidableSuperClasses
+ | MonomorphismRestriction
+ | MonoPatBinds
+ | MonoLocalBinds
+ | RelaxedPolyRec -- Deprecated
+ | ExtendedDefaultRules -- Use GHC's extended rules for defaulting
+ | ForeignFunctionInterface
+ | UnliftedFFITypes
+ | InterruptibleFFI
+ | CApiFFI
+ | GHCForeignImportPrim
+ | JavaScriptFFI
+ | ParallelArrays -- Syntactic support for parallel arrays
+ | Arrows -- Arrow-notation syntax
+ | TemplateHaskell
+ | TemplateHaskellQuotes -- subset of TH supported by stage1, no splice
+ | QuasiQuotes
+ | ImplicitParams
+ | ImplicitPrelude
+ | ScopedTypeVariables
+ | AllowAmbiguousTypes
+ | UnboxedTuples
+ | BangPatterns
+ | TypeFamilies
+ | TypeFamilyDependencies
+ | TypeInType
+ | OverloadedStrings
+ | OverloadedLists
+ | NumDecimals
+ | DisambiguateRecordFields
+ | RecordWildCards
+ | RecordPuns
+ | ViewPatterns
+ | GADTs
+ | GADTSyntax
+ | NPlusKPatterns
+ | DoAndIfThenElse
+ | RebindableSyntax
+ | ConstraintKinds
+ | PolyKinds -- Kind polymorphism
+ | DataKinds -- Datatype promotion
+ | InstanceSigs
+ | ApplicativeDo
+
+ | StandaloneDeriving
+ | DeriveDataTypeable
+ | AutoDeriveTypeable -- Automatic derivation of Typeable
+ | DeriveFunctor
+ | DeriveTraversable
+ | DeriveFoldable
+ | DeriveGeneric -- Allow deriving Generic/1
+ | DefaultSignatures -- Allow extra signatures for defmeths
+ | DeriveAnyClass -- Allow deriving any class
+ | DeriveLift -- Allow deriving Lift
+
+ | TypeSynonymInstances
+ | FlexibleContexts
+ | FlexibleInstances
+ | ConstrainedClassMethods
+ | MultiParamTypeClasses
+ | NullaryTypeClasses
+ | FunctionalDependencies
+ | UnicodeSyntax
+ | ExistentialQuantification
+ | MagicHash
+ | EmptyDataDecls
+ | KindSignatures
+ | RoleAnnotations
+ | ParallelListComp
+ | TransformListComp
+ | MonadComprehensions
+ | GeneralizedNewtypeDeriving
+ | RecursiveDo
+ | PostfixOperators
+ | TupleSections
+ | PatternGuards
+ | LiberalTypeSynonyms
+ | RankNTypes
+ | ImpredicativeTypes
+ | TypeOperators
+ | ExplicitNamespaces
+ | PackageImports
+ | ExplicitForAll
+ | AlternativeLayoutRule
+ | AlternativeLayoutRuleTransitional
+ | DatatypeContexts
+ | NondecreasingIndentation
+ | RelaxedLayout
+ | TraditionalRecordSyntax
+ | LambdaCase
+ | MultiWayIf
+ | BinaryLiterals
+ | NegativeLiterals
+ | DuplicateRecordFields
+ | OverloadedLabels
+ | EmptyCase
+ | PatternSynonyms
+ | PartialTypeSignatures
+ | NamedWildCards
+ | StaticPointers
+ | TypeApplications
+ | Strict
+ | StrictData
+ | MonadFailDesugaring
+ deriving (Eq, Enum, Show, Generic)
diff --git a/libraries/ghc-boot-th/GHC/Lexeme.hs b/libraries/ghc-boot-th/GHC/Lexeme.hs
new file mode 100644
index 0000000000..677c9a65e6
--- /dev/null
+++ b/libraries/ghc-boot-th/GHC/Lexeme.hs
@@ -0,0 +1,32 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : GHC.Lexeme
+-- Copyright : (c) The GHC Team
+--
+-- Maintainer : ghc-devs@haskell.org
+-- Portability : portable
+--
+-- Functions to evaluate whether or not a string is a valid identifier.
+--
+module GHC.Lexeme (
+ -- * Lexical characteristics of Haskell names
+ startsVarSym, startsVarId, startsConSym, startsConId,
+ startsVarSymASCII, isVarSymChar
+ ) where
+
+import Data.Char
+
+startsVarSym, startsVarId, startsConSym, startsConId :: Char -> Bool
+startsVarSym c = startsVarSymASCII c || (ord c > 0x7f && isSymbol c) -- Infix Ids
+startsConSym c = c == ':' -- Infix data constructors
+startsVarId c = c == '_' || case generalCategory c of -- Ordinary Ids
+ LowercaseLetter -> True
+ OtherLetter -> True -- See #1103
+ _ -> False
+startsConId c = isUpper c || c == '(' -- Ordinary type constructors and data constructors
+
+startsVarSymASCII :: Char -> Bool
+startsVarSymASCII c = c `elem` "!#$%&*+./<=>?@\\^|~-"
+
+isVarSymChar :: Char -> Bool
+isVarSymChar c = c == ':' || startsVarSym c
diff --git a/libraries/ghc-boot-th/LICENSE b/libraries/ghc-boot-th/LICENSE
new file mode 100644
index 0000000000..b5059b71f6
--- /dev/null
+++ b/libraries/ghc-boot-th/LICENSE
@@ -0,0 +1,31 @@
+The Glasgow Haskell Compiler License
+
+Copyright 2002, The University Court of the University of Glasgow.
+All rights reserved.
+
+Redistribution and use in source and binary forms, with or without
+modification, are permitted provided that the following conditions are met:
+
+- Redistributions of source code must retain the above copyright notice,
+this list of conditions and the following disclaimer.
+
+- Redistributions in binary form must reproduce the above copyright notice,
+this list of conditions and the following disclaimer in the documentation
+and/or other materials provided with the distribution.
+
+- Neither name of the University nor the names of its contributors may be
+used to endorse or promote products derived from this software without
+specific prior written permission.
+
+THIS SOFTWARE IS PROVIDED BY THE UNIVERSITY COURT OF THE UNIVERSITY OF
+GLASGOW AND THE CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES,
+INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND
+FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+UNIVERSITY COURT OF THE UNIVERSITY OF GLASGOW OR THE CONTRIBUTORS BE LIABLE
+FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
+DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR
+SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
+OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH
+DAMAGE.
diff --git a/libraries/ghc-boot-th/changelog.md b/libraries/ghc-boot-th/changelog.md
new file mode 100644
index 0000000000..3ed5bbbfd2
--- /dev/null
+++ b/libraries/ghc-boot-th/changelog.md
@@ -0,0 +1,5 @@
+## 8.0.1 *May 2016*
+
+ * Bundled with GHC 8.0.1
+
+ * Initial version
diff --git a/libraries/ghc-boot-th/ghc-boot-th.cabal.in b/libraries/ghc-boot-th/ghc-boot-th.cabal.in
new file mode 100644
index 0000000000..3aebfbfc89
--- /dev/null
+++ b/libraries/ghc-boot-th/ghc-boot-th.cabal.in
@@ -0,0 +1,37 @@
+-- WARNING: ghc-boot-th.cabal is automatically generated from
+-- ghc-boot-th.cabal.in by ../../configure. Make sure you are editing
+-- ghc-boot-th.cabal.in, not ghc-boot-th.cabal.
+
+name: ghc-boot-th
+version: @ProjectVersionMunged@
+license: BSD3
+license-file: LICENSE
+category: GHC
+maintainer: ghc-devs@haskell.org
+bug-reports: https://ghc.haskell.org/trac/ghc/newticket
+synopsis: Shared functionality between GHC and the @template-haskell@
+ library
+description: This library contains various bits shared between the @ghc@ and
+ @template-haskell@ libraries.
+ .
+ This package exists to ensure that @template-haskell@ has a
+ minimal set of transitive dependencies, since it is intended to
+ be depended upon by user code.
+cabal-version: >=1.10
+build-type: Simple
+extra-source-files: changelog.md
+
+source-repository head
+ type: git
+ location: http://git.haskell.org/ghc.git
+ subdir: libraries/ghc-boot-th
+
+Library
+ default-language: Haskell2010
+ other-extensions: DeriveGeneric
+
+ exposed-modules:
+ GHC.LanguageExtensions.Type
+ GHC.Lexeme
+
+ build-depends: base >= 4.7 && < 4.10