summaryrefslogtreecommitdiff
path: root/compiler/main
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/main')
-rw-r--r--compiler/main/Ar.hs4
-rw-r--r--compiler/main/CmdLineParser.hs6
-rw-r--r--compiler/main/Constants.hs2
-rw-r--r--compiler/main/DriverPipeline.hs8
-rw-r--r--compiler/main/DynFlags.hs14
-rw-r--r--compiler/main/ErrUtils.hs2
-rw-r--r--compiler/main/GHC.hs4
-rw-r--r--compiler/main/GhcMake.hs8
-rw-r--r--compiler/main/HscTypes.hs8
-rw-r--r--compiler/main/InteractiveEval.hs6
-rw-r--r--compiler/main/Packages.hs2
-rw-r--r--compiler/main/SysTools.hs4
-rw-r--r--compiler/main/SysTools/Info.hs8
-rw-r--r--compiler/main/SysTools/Process.hs2
-rw-r--r--compiler/main/TidyPgm.hs16
15 files changed, 47 insertions, 47 deletions
diff --git a/compiler/main/Ar.hs b/compiler/main/Ar.hs
index 1f1b44ed35..73292d0ae3 100644
--- a/compiler/main/Ar.hs
+++ b/compiler/main/Ar.hs
@@ -106,7 +106,7 @@ getBSDArchEntries = do
return $ C.unpack $ C.takeWhile (/= ' ') name
off2 <- liftM fromIntegral bytesRead :: Get Int
file <- getByteString (st_size - (off2 - off1))
- -- data sections are two byte aligned (see Trac #15396)
+ -- data sections are two byte aligned (see #15396)
when (odd st_size) $
void (getByteString 1)
@@ -135,7 +135,7 @@ getGNUArchEntries extInfo = do
fail ("[BSD Archive] Invalid archive header end marker for name: " ++
C.unpack name)
file <- getByteString st_size
- -- data sections are two byte aligned (see Trac #15396)
+ -- data sections are two byte aligned (see #15396)
when (odd st_size) $
void (getByteString 1)
name <- return . C.unpack $
diff --git a/compiler/main/CmdLineParser.hs b/compiler/main/CmdLineParser.hs
index cb30b6fe6c..6763aed128 100644
--- a/compiler/main/CmdLineParser.hs
+++ b/compiler/main/CmdLineParser.hs
@@ -235,12 +235,12 @@ processOneArg opt_kind rest arg args
[] -> missingArgErr dash_arg
(L _ arg1:args1) -> Right (f arg1, args1)
- -- See Trac #9776
+ -- See #9776
SepArg f -> case args of
[] -> missingArgErr dash_arg
(L _ arg1:args1) -> Right (f arg1, args1)
- -- See Trac #12625
+ -- See #12625
Prefix f | notNull rest_no_eq -> Right (f rest_no_eq, args)
| otherwise -> missingArgErr dash_arg
@@ -277,7 +277,7 @@ arg_ok (NoArg _) rest _ = null rest
arg_ok (HasArg _) _ _ = True
arg_ok (SepArg _) rest _ = null rest
arg_ok (Prefix _) _ _ = True -- Missing argument checked for in processOneArg t
- -- to improve error message (Trac #12625)
+ -- to improve error message (#12625)
arg_ok (OptIntSuffix _) _ _ = True
arg_ok (IntSuffix _) _ _ = True
arg_ok (FloatSuffix _) _ _ = True
diff --git a/compiler/main/Constants.hs b/compiler/main/Constants.hs
index 7eda130917..cf3458507b 100644
--- a/compiler/main/Constants.hs
+++ b/compiler/main/Constants.hs
@@ -26,7 +26,7 @@ mAX_SUM_SIZE :: Int
mAX_SUM_SIZE = 62
-- | Default maximum depth for both class instance search and type family
--- reduction. See also Trac #5395.
+-- reduction. See also #5395.
mAX_REDUCTION_DEPTH :: Int
mAX_REDUCTION_DEPTH = 200
diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs
index 998928709a..5866568619 100644
--- a/compiler/main/DriverPipeline.hs
+++ b/compiler/main/DriverPipeline.hs
@@ -329,7 +329,7 @@ compileEmptyStub dflags hsc_env basename location mod_name = do
-- valid) stub object file for signatures. However,
-- we make sure this object file has a unique symbol,
-- so that ranlib on OS X doesn't complain, see
- -- http://ghc.haskell.org/trac/ghc/ticket/12673
+ -- https://gitlab.haskell.org/ghc/ghc/issues/12673
-- and https://github.com/haskell/cabal/issues/2257
empty_stub <- newTempName dflags TFL_CurrentModule "c"
let src = text "int" <+> ppr (mkModule (thisPackage dflags) mod_name) <+> text "= 0;"
@@ -777,7 +777,7 @@ getOutputFilename stop_phase output basename dflags next_phase maybe_location
As _ | keep_s -> True
LlvmOpt | keep_bc -> True
HCc | keep_hc -> True
- HsPp _ | keep_hscpp -> True -- See Trac #10869
+ HsPp _ | keep_hscpp -> True -- See #10869
_other -> False
suffix = myPhaseInputExt next_phase
@@ -1958,7 +1958,7 @@ doCpp dflags raw input_fn output_fn = do
-- Include version macros for every *exposed* package.
-- Without -hide-all-packages and with a package database
-- size of 1000 packages, it takes cpp an estimated 2
- -- milliseconds to process this file. See Trac #10970
+ -- milliseconds to process this file. See #10970
-- comment 8.
return [SysTools.FileOption "-include" macro_stub]
else return []
@@ -2011,7 +2011,7 @@ getBackendDefs _ =
generatePackageVersionMacros :: [PackageConfig] -> String
generatePackageVersionMacros pkgs = concat
- -- Do not add any C-style comments. See Trac #3389.
+ -- Do not add any C-style comments. See #3389.
[ generateMacros "" pkgname version
| pkg <- pkgs
, let version = packageVersion pkg
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index b3cfa4860e..ba4cfe726a 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -324,7 +324,7 @@ import Foreign (Ptr) -- needed for 2nd stage
-- There is a change log tracking language extension additions and removals
-- on the GHC wiki: https://ghc.haskell.org/trac/ghc/wiki/LanguagePragmaHistory
--
--- See Trac #4437 and #8176.
+-- See #4437 and #8176.
-- -----------------------------------------------------------------------------
-- DynFlags
@@ -727,7 +727,7 @@ data WarnReason
-- | Used to differentiate the scope an include needs to apply to.
-- We have to split the include paths to avoid accidentally forcing recursive
--- includes since -I overrides the system search paths. See Trac #14312.
+-- includes since -I overrides the system search paths. See #14312.
data IncludeSpecs
= IncludeSpecs { includePathsQuote :: [String]
, includePathsGlobal :: [String]
@@ -3005,7 +3005,7 @@ dynamic_flags_deps = [
, make_ord_flag defFlag "pgmc"
(hasArg (\f -> alterSettings (\s -> s { sPgm_c = (f,[]),
-- Don't pass -no-pie with -pgmc
- -- (see Trac #15319)
+ -- (see #15319)
sGccSupportsNoPie = False})))
, make_ord_flag defFlag "pgms"
(HasArg (\_ -> addWarn "Object splitting was removed in GHC 8.8"))
@@ -3753,7 +3753,7 @@ dynamic_flags_deps = [
"-XDeriveGeneric for generic programming support.") ]
-- | This is where we handle unrecognised warning flags. We only issue a warning
--- if -Wunrecognised-warning-flags is set. See Trac #11429 for context.
+-- if -Wunrecognised-warning-flags is set. See #11429 for context.
unrecognisedWarning :: String -> Flag (CmdLineP DynFlags)
unrecognisedWarning prefix = defHiddenFlag prefix (Prefix action)
where
@@ -4557,7 +4557,7 @@ impliedXFlags
, (LangExt.ExistentialQuantification, turnOn, LangExt.ExplicitForAll)
, (LangExt.FlexibleInstances, turnOn, LangExt.TypeSynonymInstances)
, (LangExt.FunctionalDependencies, turnOn, LangExt.MultiParamTypeClasses)
- , (LangExt.MultiParamTypeClasses, turnOn, LangExt.ConstrainedClassMethods) -- c.f. Trac #7854
+ , (LangExt.MultiParamTypeClasses, turnOn, LangExt.ConstrainedClassMethods) -- c.f. #7854
, (LangExt.TypeFamilyDependencies, turnOn, LangExt.TypeFamilies)
, (LangExt.RebindableSyntax, turnOff, LangExt.ImplicitPrelude) -- NB: turn off!
@@ -4675,7 +4675,7 @@ optLevelFlags -- see Note [Documenting optimisation flags]
{- Note [Eta-reduction in -O0]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Trac #11562 showed an example which tripped an ASSERT in CoreToStg; a
+#11562 showed an example which tripped an ASSERT in CoreToStg; a
function was marked as MayHaveCafRefs when in fact it obviously
didn't. Reason was:
* Eta reduction wasn't happening in the simplifier, but it was
@@ -5553,7 +5553,7 @@ picCCOpts dflags = pieOpts ++ picOpts
| gopt Opt_PIC dflags || WayDyn `elem` ways dflags ->
["-fPIC", "-U__PIC__", "-D__PIC__"]
-- gcc may be configured to have PIC on by default, let's be
- -- explicit here, see Trac #15847
+ -- explicit here, see #15847
| otherwise -> ["-fno-PIC"]
pieOpts
diff --git a/compiler/main/ErrUtils.hs b/compiler/main/ErrUtils.hs
index 9ee6856275..4f19437ce9 100644
--- a/compiler/main/ErrUtils.hs
+++ b/compiler/main/ErrUtils.hs
@@ -485,7 +485,7 @@ withDumpFileHandle dflags flag action = do
-- We do not want the dump file to be affected by
-- environment variables, but instead to always use
-- UTF8. See:
- -- https://ghc.haskell.org/trac/ghc/ticket/10762
+ -- https://gitlab.haskell.org/ghc/ghc/issues/10762
hSetEncoding handle utf8
action (Just handle)
diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs
index 9e58f356f6..4e6e0f43c2 100644
--- a/compiler/main/GHC.hs
+++ b/compiler/main/GHC.hs
@@ -138,7 +138,7 @@ module GHC (
getDocs, GetDocsFailure(..),
-- ** Other
- runTcInteractive, -- Desired by some clients (Trac #8878)
+ runTcInteractive, -- Desired by some clients (#8878)
isStmt, hasImport, isImport, isDecl,
-- ** The debugger
@@ -516,7 +516,7 @@ initGhcMonad mb_top_dir
-- check should be more selective but there is currently no released
-- version where this bug is fixed.
-- See https://sourceware.org/bugzilla/show_bug.cgi?id=16177 and
--- https://ghc.haskell.org/trac/ghc/ticket/4210#comment:29
+-- https://gitlab.haskell.org/ghc/ghc/issues/4210#note_78333
checkBrokenTablesNextToCode :: MonadIO m => DynFlags -> m ()
checkBrokenTablesNextToCode dflags
= do { broken <- checkBrokenTablesNextToCode' dflags
diff --git a/compiler/main/GhcMake.hs b/compiler/main/GhcMake.hs
index a6fe5c7f72..d730fe70f1 100644
--- a/compiler/main/GhcMake.hs
+++ b/compiler/main/GhcMake.hs
@@ -160,7 +160,7 @@ depanal excluded_mods allow_dup_roots = do
-- but "A" imports some other module "C", then GHC will issue a warning
-- about module "C" not being listed in a command line.
--
--- The warning in enabled by `-Wmissing-home-modules`. See Trac #13129
+-- The warning in enabled by `-Wmissing-home-modules`. See #13129
warnMissingHomeModules :: GhcMonad m => HscEnv -> ModuleGraph -> m ()
warnMissingHomeModules hsc_env mod_graph =
when (wopt Opt_WarnMissingHomeModules dflags && not (null missing)) $
@@ -178,7 +178,7 @@ warnMissingHomeModules hsc_env mod_graph =
-- For instance, `ghc --make src-exe/Main.hs` and
-- `ghc --make -isrc-exe Main` are supposed to be equivalent.
-- Note also that we can't always infer the associated module name
- -- directly from the filename argument. See Trac #13727.
+ -- directly from the filename argument. See #13727.
is_my_target mod (TargetModule name)
= moduleName (ms_mod mod) == name
is_my_target mod (TargetFile target_file _)
@@ -868,7 +868,7 @@ parUpsweep n_jobs mHscMessage old_hpt stable_mods cleanup sccs = do
n_cpus <- getNumProcessors
-- Setting number of capabilities more than
-- CPU count usually leads to high userspace
- -- lock contention. Trac #9221
+ -- lock contention. #9221
let n_caps = min n_jobs n_cpus
unless (n_capabilities /= 1) $ setNumCapabilities n_caps
return n_capabilities
@@ -1629,7 +1629,7 @@ Potential TODOS:
-- be any object code that we can compare against, nor should there
-- be: we're *just* generating interface files. In this case, we
-- want to check if the interface file is new, in lieu of the object
--- file. See also Trac #9243.
+-- file. See also #9243.
-- Filter modules in the HPT
retainInTopLevelEnvs :: [ModuleName] -> HomePackageTable -> HomePackageTable
diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs
index 0ca7bdae45..add0ee95d2 100644
--- a/compiler/main/HscTypes.hs
+++ b/compiler/main/HscTypes.hs
@@ -703,7 +703,7 @@ hptSomeThingsBelowUs extract include_hi_boot hsc_env deps
Nothing -> pprTrace "WARNING in hptSomeThingsBelowUs" msg []
msg = vcat [text "missing module" <+> ppr mod,
text "Probable cause: out-of-date interface files"]
- -- This really shouldn't happen, but see Trac #962
+ -- This really shouldn't happen, but see #962
-- And get its dfuns
, thing <- things ]
@@ -1535,7 +1535,7 @@ e.g. Prelude> data T = A | B
Prelude> instance Eq T where ...
Prelude> instance Eq T where ... -- This one overrides
-It's exactly the same for type-family instances. See Trac #7102
+It's exactly the same for type-family instances. See #7102
-}
-- | Interactive context, recording information about the state of the
@@ -1658,7 +1658,7 @@ extendInteractiveContext :: InteractiveContext
extendInteractiveContext ictxt new_tythings new_cls_insts new_fam_insts defaults fix_env
= ictxt { ic_mod_index = ic_mod_index ictxt + 1
-- Always bump this; even instances should create
- -- a new mod_index (Trac #9426)
+ -- a new mod_index (#9426)
, ic_tythings = new_tythings ++ old_tythings
, ic_rn_gbl_env = ic_rn_gbl_env ictxt `icExtendGblRdrEnv` new_tythings
, ic_instances = ( new_cls_insts ++ old_cls_insts
@@ -1726,7 +1726,7 @@ icExtendGblRdrEnv env tythings
-- are not implicit-ids, and must appear in the TypeEnv. But they
-- will also be brought into scope by the corresponding (ATyCon
-- tc). And we want the latter, because that has the correct
- -- parent (Trac #10520)
+ -- parent (#10520)
is_sub_bndr (AnId f) = case idDetails f of
RecSelId {} -> True
ClassOpId {} -> True
diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs
index 5ff1b03a97..2c04029e88 100644
--- a/compiler/main/InteractiveEval.hs
+++ b/compiler/main/InteractiveEval.hs
@@ -249,7 +249,7 @@ Things like the coercion axiom for newtypes. These bindings all get
OccNames that users can't write, to avoid the possibility of name
clashes (in linker symbols). That gives a convenient way to suppress
them. The relevant predicate is OccName.isDerivedOccName.
-See Trac #11051 for more background and examples.
+See #11051 for more background and examples.
-}
withVirtualCWD :: GhcMonad m => m a -> m a
@@ -756,7 +756,7 @@ moduleIsInterpreted modl = withSession $ \h ->
-- Filter the instances by the ones whose tycons (or clases resp)
-- are in scope (qualified or otherwise). Otherwise we list a whole lot too many!
-- The exact choice of which ones to show, and which to hide, is a judgement call.
--- (see Trac #1581)
+-- (see #1581)
getInfo :: GhcMonad m => Bool -> Name
-> m (Maybe (TyThing,Fixity,[ClsInst],[FamInst], SDoc))
getInfo allInfo name
@@ -800,7 +800,7 @@ getRdrNamesInScope = withSession $ \hsc_env -> do
ic = hsc_IC hsc_env
gbl_rdrenv = ic_rn_gbl_env ic
gbl_names = concatMap greRdrNames $ globalRdrEnvElts gbl_rdrenv
- -- Exclude internally generated names; see e.g. Trac #11328
+ -- Exclude internally generated names; see e.g. #11328
return (filter (not . isDerivedOccName . rdrNameOcc) gbl_names)
diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs
index 44258de70c..8c81d82d78 100644
--- a/compiler/main/Packages.hs
+++ b/compiler/main/Packages.hs
@@ -1723,7 +1723,7 @@ mkUnusableModuleToPkgConfAll unusables =
-- | Add a list of key/value pairs to a nested map.
--
-- The outer map is processed with 'Data.Map.Strict' to prevent memory leaks
--- when reloading modules in GHCi (see Trac #4029). This ensures that each
+-- when reloading modules in GHCi (see #4029). This ensures that each
-- value is forced before installing into the map.
addListTo :: (Monoid a, Ord k1, Ord k2)
=> Map k1 (Map k2 a)
diff --git a/compiler/main/SysTools.hs b/compiler/main/SysTools.hs
index 543dd9ce3b..fddc4ac30f 100644
--- a/compiler/main/SysTools.hs
+++ b/compiler/main/SysTools.hs
@@ -314,7 +314,7 @@ initSysTools top_dir
{- Note [Windows stack usage]
-See: Trac #8870 (and #8834 for related info) and #12186
+See: #8870 (and #8834 for related info) and #12186
On Windows, occasionally we need to grow the stack. In order to do
this, we would normally just bump the stack pointer - but there's a
@@ -616,5 +616,5 @@ R_*_COPY relocations.
Unregisterised compiler can't evade R_*_COPY relocations easily thus we disable
-Bsymbolic linking there.
-See related Trac tickets: #4210, #15338
+See related tickets: #4210, #15338
-}
diff --git a/compiler/main/SysTools/Info.hs b/compiler/main/SysTools/Info.hs
index 420a2bf27f..2dcd39549f 100644
--- a/compiler/main/SysTools/Info.hs
+++ b/compiler/main/SysTools/Info.hs
@@ -26,7 +26,7 @@ import SysTools.Process
{- Note [Run-time linker info]
-See also: Trac #5240, Trac #6063, Trac #10110
+See also: #5240, #6063, #10110
Before 'runLink', we need to be sure to get the relevant information
about the linker we're using at runtime to see if we need any extra
@@ -127,8 +127,8 @@ getLinkerInfo' dflags = do
parseLinkerInfo stdo _stde _exitc
| any ("GNU ld" `isPrefixOf`) stdo =
-- GNU ld specifically needs to use less memory. This especially
- -- hurts on small object files. Trac #5240.
- -- Set DT_NEEDED for all shared libraries. Trac #10110.
+ -- hurts on small object files. #5240.
+ -- Set DT_NEEDED for all shared libraries. #10110.
-- TODO: Investigate if these help or hurt when using split sections.
return (GnuLD $ map Option ["-Wl,--hash-size=31",
"-Wl,--reduce-memory-overheads",
@@ -137,7 +137,7 @@ getLinkerInfo' dflags = do
"-Wl,--no-as-needed"])
| any ("GNU gold" `isPrefixOf`) stdo =
- -- GNU gold only needs --no-as-needed. Trac #10110.
+ -- GNU gold only needs --no-as-needed. #10110.
-- ELF specific flag, see Note [ELF needed shared libs]
return (GnuGold [Option "-Wl,--no-as-needed"])
diff --git a/compiler/main/SysTools/Process.hs b/compiler/main/SysTools/Process.hs
index cc8f67d139..2e0e502b63 100644
--- a/compiler/main/SysTools/Process.hs
+++ b/compiler/main/SysTools/Process.hs
@@ -117,7 +117,7 @@ runSomething dflags phase_name pgm args =
-- response files for passing them in. See:
--
-- https://gcc.gnu.org/wiki/Response_Files
--- https://ghc.haskell.org/trac/ghc/ticket/10777
+-- https://gitlab.haskell.org/ghc/ghc/issues/10777
runSomethingResponseFile
:: DynFlags -> (String->String) -> String -> String -> [Option]
-> Maybe [(String,String)] -> IO ()
diff --git a/compiler/main/TidyPgm.hs b/compiler/main/TidyPgm.hs
index e9f3f85317..6e84530193 100644
--- a/compiler/main/TidyPgm.hs
+++ b/compiler/main/TidyPgm.hs
@@ -486,7 +486,7 @@ extendTypeEnvWithPatSyns tidy_patsyns type_env
Note [Don't attempt to trim data types]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
For some time GHC tried to avoid exporting the data constructors
-of a data type if it wasn't strictly necessary to do so; see Trac #835.
+of a data type if it wasn't strictly necessary to do so; see #835.
But "strictly necessary" accumulated a longer and longer list
of exceptions, and finally I gave up the battle:
@@ -501,7 +501,7 @@ of exceptions, and finally I gave up the battle:
there are a lot of exceptions, notably when Template Haskell is
involved or, more recently, DataKinds.
- However Trac #7445 shows that even without TemplateHaskell, using
+ However #7445 shows that even without TemplateHaskell, using
the Data class and invoking Language.Haskell.TH.Quote.dataToExpQ
is enough to require us to expose the data constructors.
@@ -528,7 +528,7 @@ Then the unfolding looks like
This generates bad code unless it's first simplified a bit. That is
why CoreUnfold.mkImplicitUnfolding uses simpleOptExpr to do a bit of
optimisation first. (Only matters when the selector is used curried;
-eg map x ys.) See Trac #2070.
+eg map x ys.) See #2070.
[Oct 09: in fact, record selectors are no longer implicit Ids at all,
because we really do want to optimise them properly. They are treated
@@ -541,7 +541,7 @@ because GlobalIds are supposed to have *fixed* IdInfo, but the
simplifier and other core-to-core passes mess with IdInfo all the
time. The straw that broke the camels back was when a class selector
got the wrong arity -- ie the simplifier gave it arity 2, whereas
-importing modules were expecting it to have arity 1 (Trac #2844).
+importing modules were expecting it to have arity 1 (#2844).
It's much safer just to inject them right at the end, after tidying.
Oh: two other reasons for injecting them late:
@@ -1251,7 +1251,7 @@ tidyTopIdInfo dflags rhs_tidy_env name orig_rhs tidy_rhs idinfo show_unfold caf_
-- marked NOINLINE or something like that
-- This is important: if you expose the worker for a loop-breaker
-- then you can make the simplifier go into an infinite loop, because
- -- in effect the unfolding is exposed. See Trac #1709
+ -- in effect the unfolding is exposed. See #1709
--
-- You might think that if show_unfold is False, then the thing should
-- not be w/w'd in the first place. But a legitimate reason is this:
@@ -1371,7 +1371,7 @@ not exported, to reduce the size of interface files, at least without
-O. But that is not always possible: see the old Note [When we can't
trim types] below for exceptions.
-Then (Trac #7445) I realised that the TH problem arises for any data type
+Then (#7445) I realised that the TH problem arises for any data type
that we have deriving( Data ), because we can invoke
Language.Haskell.TH.Quote.dataToExpQ
to get a TH Exp representation of a value built from that data type.
@@ -1396,7 +1396,7 @@ now.
But there are some times we can't do that, indicated by the 'no_trim_types' flag.
-First, Template Haskell. Consider (Trac #2386) this
+First, Template Haskell. Consider (#2386) this
module M(T, makeOne) where
data T = Yay String
makeOne = [| Yay "Yep" |]
@@ -1405,7 +1405,7 @@ A module that splices in $(makeOne) will then look for a declaration of Yay,
so it'd better be there. Hence, brutally but simply, we switch off type
constructor trimming if TH is enabled in this module.
-Second, data kinds. Consider (Trac #5912)
+Second, data kinds. Consider (#5912)
{-# LANGUAGE DataKinds #-}
module M() where
data UnaryTypeC a = UnaryDataC a