Skip to content

Commit

Permalink
Use default-extensions to tidy up a bit (#669)
Browse files Browse the repository at this point in the history
* Use default-extensions to tidy up a bit

* Fix ghc invocation in emulated CI jobs

* Use Haskell2010 in emulated jobs, too
# Conflicts:
#	Data/ByteString/Lazy.hs
  • Loading branch information
clyring authored and Bodigrim committed Oct 9, 2024
1 parent 69d9862 commit 49222ed
Show file tree
Hide file tree
Showing 40 changed files with 119 additions and 206 deletions.
2 changes: 1 addition & 1 deletion .github/workflows/ci.yml
Original file line number Diff line number Diff line change
Expand Up @@ -143,7 +143,7 @@ jobs:
run: |
curl -s https://hackage.haskell.org/package/data-array-byte-0.1/data-array-byte-0.1.tar.gz | tar xz
ghc --version
ghc --make -Iinclude -itests:tests/builder:data-array-byte-0.1 -o Main cbits/*.c tests/Main.hs +RTS -s
ghc --make -XHaskell2010 -XBangPatterns -XDeriveDataTypeable -XDeriveGeneric -XDeriveLift -XFlexibleContexts -XFlexibleInstances -XLambdaCase -XMagicHash -XMultiWayIf -XNamedFieldPuns -XPatternSynonyms -XRankNTypes -XScopedTypeVariables -XStandaloneDeriving -XTupleSections -XTypeApplications -XTypeOperators -XUnboxedTuples -optP-Wall -optP-Werror=undef -DPURE_HASKELL=0 -Iinclude -itests:tests/builder:data-array-byte-0.1 -o Main cbits/*.c tests/Main.hs +RTS -s
./Main +RTS -s
bounds-checking:
Expand Down
7 changes: 1 addition & 6 deletions Data/ByteString.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,6 @@
{-# OPTIONS_HADDOCK prune #-}
{-# LANGUAGE Trustworthy #-}

{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_HADDOCK prune #-}

-- |
-- Module : Data.ByteString
Expand Down
7 changes: 4 additions & 3 deletions Data/ByteString/Builder.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,8 @@
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE Trustworthy #-}
{-# OPTIONS_GHC -fno-warn-unused-imports -fno-warn-orphans #-}

{-# OPTIONS_GHC -fno-warn-orphans #-}
--instance Show Builder, instance IsString Builder

{- | Copyright : (c) 2010 Jasper Van der Jeugt
(c) 2010 - 2011 Simon Meier
License : BSD3-style (see LICENSE)
Expand Down
2 changes: 1 addition & 1 deletion Data/ByteString/Builder/Extra.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE Trustworthy #-}

-----------------------------------------------------------------------------
-- | Copyright : (c) 2010 Jasper Van der Jeugt
-- (c) 2010-2011 Simon Meier
Expand Down
3 changes: 2 additions & 1 deletion Data/ByteString/Builder/Internal.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# LANGUAGE ScopedTypeVariables, CPP, BangPatterns, RankNTypes, TupleSections #-}
{-# LANGUAGE Unsafe #-}

{-# OPTIONS_HADDOCK not-home #-}

-- | Copyright : (c) 2010 - 2011 Simon Meier
-- License : BSD3-style (see LICENSE)
--
Expand Down
11 changes: 3 additions & 8 deletions Data/ByteString/Builder/Prim.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,5 @@
{-# LANGUAGE BangPatterns, ScopedTypeVariables #-}
{-# LANGUAGE MagicHash, UnboxedTuples, PatternGuards #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# LANGUAGE Trustworthy #-}

{- | Copyright : (c) 2010-2011 Simon Meier
(c) 2010 Jasper van der Jeugt
License : BSD3-style (see LICENSE)
Expand Down Expand Up @@ -457,17 +455,14 @@ import qualified Data.ByteString as S
import qualified Data.ByteString.Internal as S
import qualified Data.ByteString.Lazy.Internal as L

import Data.Monoid
import Data.Char (chr, ord)
import Control.Monad ((<=<), unless)
import Data.Char (ord)

import Data.ByteString.Builder.Prim.Internal hiding (size, sizeBound)
import qualified Data.ByteString.Builder.Prim.Internal as I (size, sizeBound)
import qualified Data.ByteString.Builder.Prim.Internal as I
import Data.ByteString.Builder.Prim.Binary
import Data.ByteString.Builder.Prim.ASCII

import Foreign
import Foreign.C.Types
import Foreign.ForeignPtr.Unsafe (unsafeForeignPtrToPtr)
import GHC.Word (Word8 (..))
import GHC.Exts
Expand Down
1 change: 0 additions & 1 deletion Data/ByteString/Builder/Prim/ASCII.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE ScopedTypeVariables #-}
-- | Copyright : (c) 2010 Jasper Van der Jeugt
-- (c) 2010 - 2011 Simon Meier
-- License : BSD3-style (see LICENSE)
Expand Down
2 changes: 0 additions & 2 deletions Data/ByteString/Builder/Prim/Binary.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,5 @@
{-# LANGUAGE Trustworthy #-}

{-# LANGUAGE TypeApplications #-}

-- | Copyright : (c) 2010-2011 Simon Meier
-- License : BSD3-style (see LICENSE)
--
Expand Down
4 changes: 3 additions & 1 deletion Data/ByteString/Builder/Prim/Internal.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,8 @@
{-# LANGUAGE ScopedTypeVariables, CPP #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE Unsafe #-}

{-# OPTIONS_HADDOCK not-home #-}

-- |
-- Copyright : 2010-2011 Simon Meier, 2010 Jasper van der Jeugt
-- License : BSD3-style (see LICENSE)
Expand Down
2 changes: 1 addition & 1 deletion Data/ByteString/Builder/Prim/Internal/Base16.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE CPP #-}

-- |
-- Copyright : (c) 2011 Simon Meier
-- License : BSD3-style (see LICENSE)
Expand Down
4 changes: 1 addition & 3 deletions Data/ByteString/Builder/RealFloat/D2S.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,5 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE ScopedTypeVariables #-}

-- |
-- Module : Data.ByteString.Builder.RealFloat.D2S
-- Copyright : (c) Lawrence Wu 2021
Expand Down
3 changes: 1 addition & 2 deletions Data/ByteString/Builder/RealFloat/F2S.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE BangPatterns, MagicHash #-}

-- |
-- Module : Data.ByteString.Builder.RealFloat.F2S
-- Copyright : (c) Lawrence Wu 2021
Expand Down
4 changes: 2 additions & 2 deletions Data/ByteString/Builder/RealFloat/Internal.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE ScopedTypeVariables, ExplicitForAll #-}
{-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples #-}
{-# LANGUAGE CPP #-}

{-# LANGUAGE RecordWildCards #-}

-- |
-- Module : Data.ByteString.Builder.RealFloat.Internal
-- Copyright : (c) Lawrence Wu 2021
Expand Down
4 changes: 0 additions & 4 deletions Data/ByteString/Builder/RealFloat/TableGenerator.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,3 @@
{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples #-}
-- |
-- Module : Data.ByteString.Builder.RealFloat.TableGenerator
-- Copyright : (c) Lawrence Wu 2021
Expand Down
7 changes: 4 additions & 3 deletions Data/ByteString/Char8.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,9 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE MagicHash #-}
{-# OPTIONS_HADDOCK prune #-}
{-# LANGUAGE Trustworthy #-}

{-# OPTIONS_HADDOCK prune #-}
{-# OPTIONS_GHC -Wno-deprecations #-}
-- We use the deprecated Data.ByteString.{hGetLine,getLine} to
-- define the not-deprecated Char8 versions of the same functions.

-- |
-- Module : Data.ByteString.Char8
Expand Down
4 changes: 0 additions & 4 deletions Data/ByteString/Internal/Pure.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,3 @@
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE MultiWayIf #-}

-- Enable yields to make `isValidUtf8` safe to use on large inputs.
{-# OPTIONS_GHC -fno-omit-yields #-}

Expand Down
9 changes: 2 additions & 7 deletions Data/ByteString/Internal/Type.hs
Original file line number Diff line number Diff line change
@@ -1,18 +1,13 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Unsafe #-}

{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE PatternSynonyms #-}
{-# OPTIONS_HADDOCK not-home #-}

{-# LANGUAGE TemplateHaskellQuotes #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UnliftedFFITypes #-}
{-# LANGUAGE ViewPatterns #-}

{-# OPTIONS_HADDOCK not-home #-}

-- |
-- Module : Data.ByteString.Internal.Type
-- Copyright : (c) Don Stewart 2006-2008
Expand Down
4 changes: 0 additions & 4 deletions Data/ByteString/Lazy.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,10 +2,6 @@
{-# OPTIONS_HADDOCK prune #-}
{-# LANGUAGE Trustworthy #-}

{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ScopedTypeVariables #-}

-- |
-- Module : Data.ByteString.Lazy
-- Copyright : (c) Don Stewart 2006
Expand Down
3 changes: 1 addition & 2 deletions Data/ByteString/Lazy/Char8.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TypeApplications #-}

{-# OPTIONS_HADDOCK prune #-}

-- |
Expand Down
10 changes: 2 additions & 8 deletions Data/ByteString/Lazy/Internal.hs
Original file line number Diff line number Diff line change
@@ -1,16 +1,10 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveLift #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE Unsafe #-}

#ifdef HS_BYTESTRING_ASSERTIONS
{-# LANGUAGE PatternSynonyms #-}
#endif

{-# OPTIONS_HADDOCK not-home #-}

{-# LANGUAGE TypeFamilies #-}

-- |
-- Module : Data.ByteString.Lazy.Internal
-- Copyright : (c) Don Stewart 2006-2008
Expand Down
5 changes: 0 additions & 5 deletions Data/ByteString/Lazy/ReadInt.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}

-- This file is also included by "Data.ByteString.ReadInt", after defining
-- "BYTESTRING_STRICT". The two modules share much of their code, but
Expand Down
5 changes: 0 additions & 5 deletions Data/ByteString/Lazy/ReadNat.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}

-- This file is included by "Data.ByteString.ReadInt", after defining
-- "BYTESTRING_STRICT". The two modules are largely identical, except for the
Expand Down
23 changes: 5 additions & 18 deletions Data/ByteString/Short/Internal.hs
Original file line number Diff line number Diff line change
@@ -1,27 +1,14 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveLift #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UnliftedFFITypes #-}
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE ViewPatterns #-}

{-# OPTIONS_HADDOCK not-home #-}

{-# OPTIONS_GHC -fexpose-all-unfoldings #-}

{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UnliftedFFITypes #-}
{-# LANGUAGE ViewPatterns #-}

#include "bytestring-cpp-macros.h"

-- |
Expand Down
1 change: 0 additions & 1 deletion Data/ByteString/Unsafe.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE Unsafe #-}

-- |
Expand Down
11 changes: 4 additions & 7 deletions Data/ByteString/Utils/UnalignedAccess.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,7 @@
{-# LANGUAGE CPP #-}

#include "bytestring-cpp-macros.h"

-- |
-- Module : Data.ByteString.Utils.UnalignedAccess
-- Copyright : (c) Matthew Craven 2023-2024
Expand All @@ -8,13 +12,6 @@
--
-- Primitives for reading and writing at potentially-unaligned memory locations

{-# LANGUAGE CPP #-}

{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}

#include "bytestring-cpp-macros.h"

module Data.ByteString.Utils.UnalignedAccess
( unalignedWriteU16
, unalignedWriteU32
Expand Down
5 changes: 0 additions & 5 deletions bench/BenchAll.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,11 +7,6 @@
-- Portability : tested on GHC only
--

{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE MagicHash #-}

module Main (main) where

import Data.Foldable (foldMap)
Expand Down
2 changes: 0 additions & 2 deletions bench/BenchBoundsCheckFusion.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,8 +8,6 @@
--
-- Benchmark that the bounds checks fuse.

{-# LANGUAGE PackageImports, ScopedTypeVariables, BangPatterns #-}

module BenchBoundsCheckFusion (benchBoundsCheckFusion) where

import Prelude hiding (words)
Expand Down
5 changes: 2 additions & 3 deletions bench/BenchCSV.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE CPP #-}

-- |
-- Copyright : (c) 2010-2011 Simon Meier
-- License : BSD3-style (see LICENSE)
Expand All @@ -9,9 +11,6 @@
-- Running example for documentation of Data.ByteString.Builder
--

{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}

module BenchCSV (benchCSV) where

-- **************************************************************************
Expand Down
2 changes: 0 additions & 2 deletions bench/BenchIndices.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,6 @@
--
-- Benchmark elemIndex, findIndex, elemIndices, and findIndices

{-# LANGUAGE BangPatterns #-}

module BenchIndices (benchIndices) where

import Data.Foldable (foldMap)
Expand Down
10 changes: 2 additions & 8 deletions bench/BenchReadInt.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE CPP #-}

-- |
-- Copyright : (c) 2021 Viktor Dukhovni
-- License : BSD3-style (see LICENSE)
Expand All @@ -7,14 +9,6 @@
-- Benchmark readInt and variants, readWord and variants,
-- readInteger and readNatural

{-# LANGUAGE
CPP
, BangPatterns
, OverloadedStrings
, TypeApplications
, ScopedTypeVariables
#-}

module BenchReadInt (benchReadInt) where

import qualified Data.ByteString.Builder as B
Expand Down
4 changes: 0 additions & 4 deletions bench/BenchShort.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,3 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE OverloadedStrings #-}

module BenchShort (benchShort) where
Expand Down
Loading

0 comments on commit 49222ed

Please sign in to comment.