Skip to content
Snippets Groups Projects
Commit 23892440 authored by Herbert Valerio Riedel's avatar Herbert Valerio Riedel :man_dancing:
Browse files

Add LANGUAGE pragmas to compiler/ source files

In some cases, the layout of the LANGUAGE/OPTIONS_GHC lines has been
reorganized, while following the convention, to

- place `{-# LANGUAGE #-}` pragmas at the top of the source file, before
  any `{-# OPTIONS_GHC #-}`-lines.

- Moreover, if the list of language extensions fit into a single
  `{-# LANGUAGE ... -#}`-line (shorter than 80 characters), keep it on one
  line. Otherwise split into `{-# LANGUAGE ... -#}`-lines for each
  individual language extension. In both cases, try to keep the
  enumeration alphabetically ordered.
  (The latter layout is preferable as it's more diff-friendly)

While at it, this also replaces obsolete `{-# OPTIONS ... #-}` pragma
occurences by `{-# OPTIONS_GHC ... #-}` pragmas.
parent e199891f
No related branches found
No related tags found
No related merge requests found
Showing
with 32 additions and 11 deletions
......@@ -5,6 +5,7 @@
\section[ConLike]{@ConLike@: Constructor-like things}
\begin{code}
{-# LANGUAGE CPP, DeriveDataTypeable #-}
module ConLike (
ConLike(..)
......
......@@ -5,7 +5,8 @@
\section[DataCon]{@DataCon@: Data Constructors}
\begin{code}
{-# OPTIONS -fno-warn-tabs #-}
{-# LANGUAGE CPP, DeriveDataTypeable #-}
{-# OPTIONS_GHC -fno-warn-tabs #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and
-- detab the module (please do the detabbing in a separate patch). See
......
......@@ -5,6 +5,7 @@
\section[Demand]{@Demand@: A decoupled implementation of a demand domain}
\begin{code}
{-# LANGUAGE CPP, FlexibleInstances, TypeSynonymInstances #-}
module Demand (
StrDmd, UseDmd(..), Count(..),
......
......@@ -5,6 +5,8 @@
\section[Id]{@Ids@: Value and constructor identifiers}
\begin{code}
{-# LANGUAGE CPP #-}
-- |
-- #name_types#
-- GHC uses several kinds of name internally:
......
......@@ -8,7 +8,7 @@
Haskell. [WDP 94/11])
\begin{code}
{-# OPTIONS -fno-warn-tabs #-}
{-# OPTIONS_GHC -fno-warn-tabs #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and
-- detab the module (please do the detabbing in a separate patch). See
......
......@@ -5,7 +5,7 @@
\section[Literal]{@Literal@: Machine literals (unboxed, of course)}
\begin{code}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE CPP, DeriveDataTypeable #-}
module Literal
(
......
......@@ -12,7 +12,8 @@ have a standard form, namely:
- primitive operations
\begin{code}
{-# OPTIONS -fno-warn-tabs #-}
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-tabs #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and
-- detab the module (please do the detabbing in a separate patch). See
......
......@@ -9,6 +9,7 @@ These are Uniquable, hence we can build Maps with Modules as
the keys.
\begin{code}
{-# LANGUAGE DeriveDataTypeable #-}
module Module
(
......
......@@ -5,6 +5,8 @@
\section[Name]{@Name@: to transmit name info from renamer to typechecker}
\begin{code}
{-# LANGUAGE DeriveDataTypeable #-}
-- |
-- #name_types#
-- GHC uses several kinds of name internally:
......
......@@ -5,7 +5,8 @@
\section[NameEnv]{@NameEnv@: name environments}
\begin{code}
{-# OPTIONS -fno-warn-tabs #-}
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-tabs #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and
-- detab the module (please do the detabbing in a separate patch). See
......
......@@ -4,7 +4,8 @@
%
\begin{code}
{-# OPTIONS -fno-warn-tabs #-}
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-tabs #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and
-- detab the module (please do the detabbing in a separate patch). See
......
......@@ -4,6 +4,8 @@
%
\begin{code}
{-# LANGUAGE DeriveDataTypeable #-}
-- |
-- #name_types#
-- GHC uses several kinds of name internally:
......@@ -20,7 +22,7 @@
--
-- * 'Var.Var': see "Var#name_types"
{-# OPTIONS -fno-warn-tabs #-}
{-# OPTIONS_GHC -fno-warn-tabs #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and
-- detab the module (please do the detabbing in a separate patch). See
......
......@@ -5,6 +5,7 @@
\section[PatSyn]{@PatSyn@: Pattern synonyms}
\begin{code}
{-# LANGUAGE CPP, DeriveDataTypeable #-}
module PatSyn (
-- * Main data types
......
......@@ -4,7 +4,7 @@
%
\begin{code}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE CPP, DeriveDataTypeable #-}
-- |
-- #name_types#
......
......@@ -3,6 +3,7 @@
%
\begin{code}
{-# LANGUAGE DeriveDataTypeable #-}
{-# OPTIONS_GHC -fno-omit-interface-pragmas #-}
-- Workaround for Trac #5252 crashes the bootstrap compiler without -O
-- When the earliest compiler we want to boostrap with is
......
......@@ -4,6 +4,8 @@
%
\begin{code}
{-# LANGUAGE UnboxedTuples #-}
module UniqSupply (
-- * Main data type
UniqSupply, -- Abstractly
......
......@@ -16,7 +16,7 @@ Some of the other hair in this code is to be able to use a
Haskell).
\begin{code}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP, BangPatterns, MagicHash #-}
module Unique (
-- * Main data types
......
......@@ -5,7 +5,8 @@
\section{@Vars@: Variables}
\begin{code}
{-# OPTIONS -fno-warn-tabs #-}
{-# LANGUAGE CPP, DeriveDataTypeable #-}
{-# OPTIONS_GHC -fno-warn-tabs #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and
-- detab the module (please do the detabbing in a separate patch). See
......
......@@ -4,7 +4,8 @@
%
\begin{code}
{-# OPTIONS -fno-warn-tabs #-}
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-tabs #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and
-- detab the module (please do the detabbing in a separate patch). See
......
{-# LANGUAGE CPP #-}
--
-- (c) The University of Glasgow 2003-2006
--
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment