[commit: ghc] master: genprimopcode: GHC.Prim is Unsafe (#9449) (3be704a)
git at git.haskell.org
git at git.haskell.org
Mon Sep 1 20:15:10 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/3be704ab373ecd84d97b832c0d4f59dd7cb9e0ea/ghc
>---------------------------------------------------------------
commit 3be704ab373ecd84d97b832c0d4f59dd7cb9e0ea
Author: Austin Seipp <austin at well-typed.com>
Date: Mon Sep 1 15:13:44 2014 -0500
genprimopcode: GHC.Prim is Unsafe (#9449)
Summary:
Make sure the documentation for `GHC.Prim` adequately
reflects the fact it is unsafe.
Also clean up some 80-column violations.
Signed-off-by: Austin Seipp <austin at well-typed.com>
Test Plan:
Build documentation, check `GHC.Prim`. It's properly marked
as `Unsafe`.
Reviewers: hvr, goldfire, ezyang
Reviewed By: ezyang
Subscribers: nomeata, simonmar, ezyang, carter
Differential Revision: https://phabricator.haskell.org/D182
GHC Trac Issues: #9449
>---------------------------------------------------------------
3be704ab373ecd84d97b832c0d4f59dd7cb9e0ea
utils/genprimopcode/Main.hs | 10 +++++++---
1 file changed, 7 insertions(+), 3 deletions(-)
diff --git a/utils/genprimopcode/Main.hs b/utils/genprimopcode/Main.hs
index bb40917..67c2131 100644
--- a/utils/genprimopcode/Main.hs
+++ b/utils/genprimopcode/Main.hs
@@ -227,7 +227,7 @@ gen_hs_source (Info defaults entries) =
++ "consumed by haddock.\n"
++ "-}\n"
++ "\n"
- ++ "-----------------------------------------------------------------------------\n"
+ ++ (replicate 77 '-' ++ "\n") -- For 80-col cleanliness
++ "-- |\n"
++ "-- Module : GHC.Prim\n"
++ "-- \n"
@@ -239,8 +239,12 @@ gen_hs_source (Info defaults entries) =
++ "-- Use GHC.Exts from the base package instead of importing this\n"
++ "-- module directly.\n"
++ "--\n"
- ++ "-----------------------------------------------------------------------------\n"
- ++ "{-# LANGUAGE MagicHash, MultiParamTypeClasses, NoImplicitPrelude, UnboxedTuples #-}\n"
+ ++ (replicate 77 '-' ++ "\n") -- For 80-col cleanliness
+ ++ "{-# LANGUAGE Unsafe #-}\n"
+ ++ "{-# LANGUAGE MagicHash #-}\n"
+ ++ "{-# LANGUAGE MultiParamTypeClasses #-}\n"
+ ++ "{-# LANGUAGE NoImplicitPrelude #-}\n"
+ ++ "{-# LANGUAGE UnboxedTuples #-}\n"
++ "module GHC.Prim (\n"
++ unlines (map ((" " ++) . hdr) entries')
++ ") where\n"
More information about the ghc-commits
mailing list