Various cleanups (#48)

This commit is contained in:
Judah Jacobson 2019-08-31 16:32:28 -07:00 committed by GitHub
parent 7b095be700
commit 1d350f8eaa
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
7 changed files with 54 additions and 24 deletions

View File

@ -22,11 +22,11 @@ module GHC.SourceGen
-- * Overloaded combinators
-- | Certain concepts make sense in different
-- parts of Haskell syntax. For example, 'var' may be used in
-- expressions, types, patterns, and import or export lists.
-- expressions, types, and import or export lists.
module GHC.SourceGen.Binds,
module GHC.SourceGen.Lit,
module GHC.SourceGen.Overloaded,
-- * Renders Haskell syntax into text
-- * Rendering Haskell syntax into text
module GHC.SourceGen.Pretty,
) where

View File

@ -408,20 +408,36 @@ derivingAnyclass = derivingWay (Just AnyclassStrategy)
-- > deriving (Eq, Show) via T
-- > =====
-- > derivingVia (var "T") [var "Eq", var "Show"]
-- Available with `ghc >= 8.6`.
-- Available with @ghc>=8.6@.
derivingVia :: HsType' -> [HsType'] -> HsDerivingClause'
derivingVia t = derivingWay (Just $ ViaStrategy $ sigType t)
#endif
-- | Declares multiple pattern signatures of the same type.
--
-- > pattern F, G :: T
-- > =====
-- > patSynSigs ["F", "G"] $ var "T"
patSynSigs :: [OccNameStr] -> HsType' -> HsDecl'
patSynSigs names t =
sigB $ noExt PatSynSig (map (typeRdrName . unqual) names)
$ sigType t
-- | Declares a pattern signature and its type.
--
-- > pattern F :: T
-- > =====
-- > patSynSigs "F" $ var "T"
patSynSig :: OccNameStr -> HsType' -> HsDecl'
patSynSig n = patSynSigs [n]
-- TODO: patSynBidi, patSynUni
-- | Defines a pattern signature.
--
-- > pattern F a b = G b a
-- > =====
-- > patSynBind "F" ["a", "b"] $ conP "G" [bvar "b", bvar "a"]
patSynBind :: OccNameStr -> [OccNameStr] -> Pat' -> HsDecl'
patSynBind n ns p = bindB $ noExt PatSynBind
$ withPlaceHolder (noExt PSB (valueRdrName $ unqual n))

View File

@ -7,9 +7,11 @@
-- | This module provides combinators for constructing Haskell modules,
-- including import and export statements.
module GHC.SourceGen.Module
( HsModule'
, ImportDecl'
( -- * HsModule'
HsModule'
, module'
-- * Import declarations
, ImportDecl'
, qualified'
, as'
, import'

View File

@ -10,15 +10,19 @@
-- These types are all instances of 'Data.String.IsString'. For ease of use,
-- we recommend enabling the @OverloadedStrings@ extension.
module GHC.SourceGen.Name
( RdrNameStr(..)
( -- * RdrNameStr
RdrNameStr(..)
, RawNameSpace(..)
, rdrNameStrToString
, OccNameStr(..)
, occNameStrToString
, ModuleNameStr(..)
, moduleNameStrToString
, qual
, unqual
-- * OccNameStr
, OccNameStr
, occNameStrToString
, occNameStrNamespace
-- ModuleNameStr
, ModuleNameStr(..)
, moduleNameStrToString
) where
import FastString (unpackFS)
@ -37,6 +41,9 @@ moduleNameStrToString = moduleNameString . unModuleNameStr
occNameStrToString :: OccNameStr -> String
occNameStrToString (OccNameStr _ s) = unpackFS s
occNameStrNamespace :: OccNameStr -> RawNameSpace
occNameStrNamespace (OccNameStr n _) = n
rdrNameStrToString :: RdrNameStr -> String
rdrNameStrToString (UnqualStr o) = occNameStrToString o
rdrNameStrToString (QualStr m o) =

View File

@ -23,8 +23,9 @@ import GHC.SourceGen.Syntax.Internal (builtLoc)
-- (e.g.: @\"Foo\"@ vs @\"foo\"@, respectively).
--
-- 'OccNameStr' is simililar in purpose to GHC's 'OccName'. However, unlike
-- 'OccName', 'OccNameStr' does not differentiate between the type or function/value
-- namespaces. Functions in this package that take an 'OccNameStr' as input
-- 'OccName', 'OccNameStr' does not differentiate between the namespace
-- of types and of values.
-- Functions in this package that take an 'OccNameStr' as input
-- will internally convert it to the proper namespace. (This approach
-- makes it easier to implement an 'IsString' instance without the context
-- where a name would be used.)
@ -66,8 +67,9 @@ instance IsString ModuleNameStr where
-- respectively).
--
-- 'RdrNameStr' is simililar in purpose to GHC's 'RdrName'. However, unlike
-- 'RdrName', 'RdrNameStr' does not differentiate between the type or function/value
-- namespaces. Functions in this package that take a 'RdrNameStr' as input
-- 'RdrName', 'RdrNameStr' does not differentiate between the namespace of types
-- and of values.
-- Functions in this package that take a 'RdrNameStr' as input
-- will internally convert it to the proper namespace. (This approach
-- makes it easier to implement an 'IsString' instance without the context
-- where a name would be used.)

View File

@ -123,6 +123,7 @@ notPromoted = NotPromoted
--
-- Instances:
--
-- * 'GHC.SourceGen.Overloaded.BVar'
-- * 'GHC.SourceGen.Overloaded.Var'
-- * 'GHC.SourceGen.Overloaded.Par'
-- * 'GHC.SourceGen.Overloaded.App'

View File

@ -31,14 +31,16 @@ testRdrName = testGroup "RdrName"
]
testOccName = testGroup "OccName"
[ testProperty "constructor" $ forAll genUpperName $ \n ->
fromString n === OccNameStr Constructor (fromString n)
, testProperty "value" $ forAll genLowerName $ \n ->
fromString n === OccNameStr Value (fromString n)
, testProperty "punctuation" $ forAll genOp $ \n ->
fromString n === OccNameStr Value (fromString n)
[ testProperty "toString" $ forAll genOccNameString $ \n ->
occNameStrToString (fromString n) == n
, testProperty "round-trip" $ forAll genOccName $ \o ->
fromString (occNameStrToString o) === o
, testProperty "constructor" $ forAll genUpperName $ \n ->
occNameStrNamespace (fromString n) === Constructor
, testProperty "value" $ forAll genLowerName $ \n ->
occNameStrNamespace (fromString n) === Value
, testProperty "punctuation" $ forAll genOp $ \n ->
occNameStrNamespace (fromString n) === Value
]
genUpperName, genLowerName, genOp :: Gen String
@ -53,10 +55,10 @@ genRest = elements "Ab1_'"
genPunctuation = elements ".-+"
genOccName :: Gen OccNameStr
genOccName = oneof
[ OccNameStr Constructor . fromString <$> genUpperName
, OccNameStr Value . fromString <$> oneof [genLowerName, genOp]
]
genOccName = fromString <$> genOccNameString
genOccNameString :: Gen String
genOccNameString = oneof [genUpperName, genLowerName, genOp]
genModuleName :: Gen ModuleNameStr
genModuleName = fromString . intercalate "." <$> listOf1 genUpperName