Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 2 additions & 2 deletions Control/Monad/Primitive.hs
Original file line number Diff line number Diff line change
Expand Up @@ -350,14 +350,14 @@ unsafeInlineST = unsafeInlinePrim
touch :: PrimMonad m => a -> m ()
{-# INLINE touch #-}
touch x = unsafePrimToPrim
$ (primitive (\s -> case touch# x s of { s' -> (# s', () #) }) :: IO ())
(primitive (\s -> case touch# x s of { s' -> (# s', () #) }) :: IO ())

-- | Variant of 'touch' that keeps a value of an unlifted type
-- (e.g. @MutableByteArray#@) alive.
touchUnlifted :: forall (m :: Type -> Type) (a :: UnliftedType). PrimMonad m => a -> m ()
{-# INLINE touchUnlifted #-}
touchUnlifted x = unsafePrimToPrim
$ (primitive (\s -> case touch# x s of { s' -> (# s', () #) }) :: IO ())
(primitive (\s -> case touch# x s of { s' -> (# s', () #) }) :: IO ())

-- | Keep value @x@ alive until computation @k@ completes.
-- Warning: This primop exists for completeness, but it is difficult to use
Expand Down
2 changes: 2 additions & 0 deletions Data/Primitive/ByteArray.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,8 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE RankNTypes #-}

{-# OPTIONS_GHC -Wno-deprecations #-}

-- |
-- Module : Data.Primitive.ByteArray
-- Copyright : (c) Roman Leshchinskiy 2009-2012
Expand Down
2 changes: 1 addition & 1 deletion Data/Primitive/Internal/Operations.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
{-# LANGUAGE CPP, MagicHash, UnliftedFFITypes, UnboxedTuples #-}
{-# LANGUAGE RankNTypes, KindSignatures, ScopedTypeVariables #-}
{-# LANGUAGE RankNTypes, KindSignatures, ScopedTypeVariables #-}
{-# LANGUAGE DataKinds #-}
#if __GLASGOW_HASKELL__ < 806
{-# LANGUAGE TypeInType #-}
Expand Down
1 change: 0 additions & 1 deletion Data/Primitive/MVar.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}

Expand Down
2 changes: 2 additions & 0 deletions Data/Primitive/PrimArray.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,8 @@
{-# LANGUAGE TemplateHaskellQuotes #-}
{-# LANGUAGE RoleAnnotations #-}

{-# OPTIONS_GHC -Wno-deprecations #-}

-- |
-- Module : Data.Primitive.PrimArray
-- Copyright : (c) Roman Leshchinskiy 2009-2012
Expand Down
1 change: 0 additions & 1 deletion Data/Primitive/Ptr.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
Expand Down
4 changes: 2 additions & 2 deletions Data/Primitive/SmallArray.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,12 +3,12 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE TemplateHaskellQuotes #-}

{-# OPTIONS_GHC -Wno-deprecations #-}

-- |
-- Module : Data.Primitive.SmallArray
-- Copyright: (c) 2015 Dan Doel
Expand Down
2 changes: 1 addition & 1 deletion bench/Array/Traverse/Closure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,10 +7,10 @@
( traversePoly
) where

import Control.Applicative

Check warning on line 10 in bench/Array/Traverse/Closure.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.6)

The import of ‘Control.Applicative’ is redundant

Check warning on line 10 in bench/Array/Traverse/Closure.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.8)

The import of ‘Control.Applicative’ is redundant

Check warning on line 10 in bench/Array/Traverse/Closure.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.10)

The import of ‘Control.Applicative’ is redundant

Check warning on line 10 in bench/Array/Traverse/Closure.hs

View workflow job for this annotation

GitHub Actions / build (macOS-latest, latest)

The import of ‘Control.Applicative’ is redundant

Check warning on line 10 in bench/Array/Traverse/Closure.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, latest)

The import of ‘Control.Applicative’ is redundant
import Control.Monad.ST
import Data.Primitive.Array
import GHC.Exts (Int(..),MutableArray#)
import GHC.Exts (MutableArray#)

{-# INLINE traversePoly #-}
traversePoly
Expand Down
4 changes: 0 additions & 4 deletions bench/PrimArray/Compare.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ScopedTypeVariables #-}

module PrimArray.Compare
( benchmarkLt
Expand All @@ -11,9 +10,6 @@ module PrimArray.Compare
) where

import Data.Primitive
import Data.Word
import Control.Monad
import Control.Monad.ST (runST)
import GHC.Exts (fromList)

benchmarkLtDef :: PrimArray Int -> PrimArray Int -> Bool
Expand Down
7 changes: 0 additions & 7 deletions bench/main.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,3 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

import Test.Tasty.Bench
import Control.Monad.ST
import Data.Primitive
Expand Down
3 changes: 0 additions & 3 deletions test/Main.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE ScopedTypeVariables #-}
Expand All @@ -11,10 +10,8 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}

#if __GLASGOW_HASKELL__ >= 805
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE TypeInType #-}

Check warning on line 14 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.6)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 14 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.6)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 14 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.6)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 14 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.6)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 14 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.8)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 14 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.8)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 14 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.8)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 14 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.8)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 14 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.10)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 14 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.10)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 14 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.10)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 14 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.10)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 14 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (macOS-latest, latest)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 14 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (macOS-latest, latest)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 14 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (macOS-latest, latest)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 14 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (macOS-latest, latest)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 14 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, latest)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 14 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, latest)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 14 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, latest)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 14 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, latest)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead
#endif

import Control.Monad
Expand Down