diff --git a/.github/workflows/workflow.yaml b/.github/workflows/workflow.yaml index 1331db3ce..03e0998e2 100644 --- a/.github/workflows/workflow.yaml +++ b/.github/workflows/workflow.yaml @@ -56,7 +56,7 @@ jobs: bzlmod: false # TODO: in a MODULE.bazel file we declare version specific dependencies, would need to use stack snapshot json # and stack config per GHC version - - ghc: 9.4.6 + - ghc: 9.2.8 bzlmod: true - ghc: 9.6.2 bzlmod: true @@ -149,7 +149,7 @@ jobs: exclude: # TODO: in a MODULE.bazel file we declare version specific dependencies, would need to use stack snapshot json # and stack config per GHC version - - ghc: 9.4.6 + - ghc: 9.2.8 bzlmod: true - ghc: 9.6.2 bzlmod: true diff --git a/CHANGELOG.md b/CHANGELOG.md index 0cb3cdde1..d9dbdda4f 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -3,6 +3,11 @@ All notable changes to this project will be documented in this file. The format is based on [Keep a Changelog](https://keepachangelog.com/). +## Next release + +### Changed + +* Use ghc 9.4.6 by default ## [0.19] 2024-02-5 diff --git a/constants.bzl b/constants.bzl index d3f30a806..0ced4dccf 100644 --- a/constants.bzl +++ b/constants.bzl @@ -1,2 +1,2 @@ -test_ghc_version = "9.2.8" +test_ghc_version = "9.4.6" test_asterius_version = "0.0.1" diff --git a/examples/WORKSPACE b/examples/WORKSPACE index f5b212eff..68e54689b 100644 --- a/examples/WORKSPACE +++ b/examples/WORKSPACE @@ -17,14 +17,14 @@ rules_haskell_dependencies() load("@rules_haskell//haskell:nixpkgs.bzl", "haskell_register_ghc_nixpkgs") haskell_register_ghc_nixpkgs( - attribute_path = "haskell.compiler.ghc928", + attribute_path = "haskell.compiler.ghc946", repository = "@rules_haskell//nixpkgs:default.nix", - version = "9.2.8", + version = "9.4.6", ) load("@rules_haskell//haskell:toolchain.bzl", "rules_haskell_toolchains") -rules_haskell_toolchains(version = "9.2.8") +rules_haskell_toolchains(version = "9.4.6") load("@rules_nixpkgs_cc//:cc.bzl", "nixpkgs_cc_configure") load("@rules_nixpkgs_python//:python.bzl", "nixpkgs_python_configure") diff --git a/examples/primitive/.github/workflows/ci.yml b/examples/primitive/.github/workflows/ci.yml new file mode 100644 index 000000000..378945fab --- /dev/null +++ b/examples/primitive/.github/workflows/ci.yml @@ -0,0 +1,51 @@ +name: ci +on: + push: + branches: + - master + pull_request: {} + +defaults: + run: + shell: bash + +jobs: + build: + runs-on: ${{ matrix.os }} + strategy: + fail-fast: false + matrix: + os: [ubuntu-latest] + ghc: ['8.0', '8.2', '8.4', '8.6', '8.8', '8.10', '9.0', '9.2', '9.4', '9.6'] + include: + - os: windows-latest + ghc: 'latest' + - os: macOS-latest + ghc: 'latest' + ## Already covered by '9.4' + # - os: ubuntu-latest + # ghc: 'latest' + steps: + - uses: actions/checkout@v3 + - uses: haskell/actions/setup@v2 + id: setup-haskell-cabal + with: + ghc-version: ${{ matrix.ghc }} + ghcup-release-channel: ${{ matrix.ghcup-release-channel }} + - name: Update cabal package database + run: cabal update + - uses: actions/cache@v3 + name: Cache cabal stuff + with: + path: | + ${{ steps.setup-haskell-cabal.outputs.cabal-store }} + dist-newstyle + key: ${{ runner.os }}-${{ matrix.ghc }} + - name: Build + run: cabal build all --enable-tests + - name: Test + run: cabal test all --enable-tests + - name: Bench + run: cabal bench --benchmark-option=-l + - name: Haddock + run: cabal haddock diff --git a/examples/primitive/.gitignore b/examples/primitive/.gitignore new file mode 100644 index 000000000..28d589ba3 --- /dev/null +++ b/examples/primitive/.gitignore @@ -0,0 +1,27 @@ +dist +dist-* +cabal-dev +*.o +*.hi +*.chi +*.chs.h +*.dyn_o +*.dyn_hi +.hpc +.hsenv +.cabal-sandbox/ +cabal.sandbox.config +*.prof +*.aux +*.hp +*.eventlog +.stack-work/ +cabal.project.local +cabal.project.local~ +.HTF/ +.ghc.environment.* +stack.yaml +*.swm +*.swo +*.swp +test_results/** diff --git a/examples/primitive/BUILD.bazel b/examples/primitive/BUILD.bazel index 7e2cd7f3d..d695d11a1 100644 --- a/examples/primitive/BUILD.bazel +++ b/examples/primitive/BUILD.bazel @@ -11,6 +11,10 @@ haskell_toolchain_library(name = "ghc-prim") haskell_toolchain_library(name = "rts") +haskell_toolchain_library(name = "template-haskell") + +haskell_toolchain_library(name = "deepseq") + cc_library( name = "memops", srcs = ["cbits/primitive-memops.c"], @@ -28,8 +32,10 @@ haskell_library( visibility = ["//visibility:public"], deps = [ ":base", + ":deepseq", ":ghc-prim", ":memops", + ":template-haskell", "//transformers", ], ) diff --git a/examples/primitive/Control/Monad/Primitive.hs b/examples/primitive/Control/Monad/Primitive.hs index 567c129fc..beace6d4f 100644 --- a/examples/primitive/Control/Monad/Primitive.hs +++ b/examples/primitive/Control/Monad/Primitive.hs @@ -1,6 +1,11 @@ {-# LANGUAGE CPP, MagicHash, UnboxedTuples, TypeFamilies #-} {-# LANGUAGE FlexibleContexts, FlexibleInstances, UndecidableInstances #-} {-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE DataKinds #-} +#if __GLASGOW_HASKELL__ < 806 +{-# LANGUAGE TypeInType #-} +#endif {-# OPTIONS_GHC -fno-warn-deprecations #-} -- | @@ -11,52 +16,53 @@ -- Maintainer : Roman Leshchinskiy -- Portability : non-portable -- --- Primitive state-transformer monads --- +-- Primitive state-transformer monads. module Control.Monad.Primitive ( PrimMonad(..), RealWorld, primitive_, PrimBase(..), + MonadPrim, + MonadPrimBase, liftPrim, primToPrim, primToIO, primToST, ioToPrim, stToPrim, unsafePrimToPrim, unsafePrimToIO, unsafePrimToST, unsafeIOToPrim, unsafeSTToPrim, unsafeInlinePrim, unsafeInlineIO, unsafeInlineST, - touch, evalPrim, unsafeInterleave, unsafeDupableInterleave, noDuplicate + touch, touchUnlifted, + keepAlive, keepAliveUnlifted, + evalPrim, unsafeInterleave, unsafeDupableInterleave, noDuplicate ) where -import GHC.Exts ( State#, RealWorld, noDuplicate#, touch# ) -import GHC.Base ( realWorld# ) -#if MIN_VERSION_base(4,4,0) -import GHC.Base ( seq# ) -#else -import Control.Exception (evaluate) +import Data.Kind (Type) + +import GHC.Exts ( State#, RealWorld, noDuplicate#, touch# + , unsafeCoerce#, realWorld#, seq# ) +import Data.Primitive.Internal.Operations (UnliftedType) +#if defined(HAVE_KEEPALIVE) +import Data.Primitive.Internal.Operations (keepAliveLiftedLifted#,keepAliveUnliftedLifted#) #endif -#if MIN_VERSION_base(4,2,0) import GHC.IO ( IO(..) ) -#else -import GHC.IOBase ( IO(..) ) -#endif -import GHC.Exts ( unsafeCoerce# ) import GHC.ST ( ST(..) ) -import Control.Monad.Trans.Class (lift) -#if !MIN_VERSION_base(4,8,0) -import Data.Monoid (Monoid) +#if __GLASGOW_HASKELL__ >= 802 +import qualified Control.Monad.ST.Lazy as L #endif +import Control.Monad.Trans.Class (lift) + import Control.Monad.Trans.Cont ( ContT ) import Control.Monad.Trans.Identity ( IdentityT (IdentityT) ) -import Control.Monad.Trans.List ( ListT ) import Control.Monad.Trans.Maybe ( MaybeT ) -import Control.Monad.Trans.Error ( ErrorT, Error) import Control.Monad.Trans.Reader ( ReaderT ) import Control.Monad.Trans.State ( StateT ) import Control.Monad.Trans.Writer ( WriterT ) import Control.Monad.Trans.RWS ( RWST ) -#if MIN_VERSION_transformers(0,4,0) -import Control.Monad.Trans.Except ( ExceptT ) +#if !MIN_VERSION_transformers(0,6,0) +import Control.Monad.Trans.List ( ListT ) +import Control.Monad.Trans.Error ( ErrorT, Error) #endif +import Control.Monad.Trans.Except ( ExceptT ) + #if MIN_VERSION_transformers(0,5,3) import Control.Monad.Trans.Accum ( AccumT ) import Control.Monad.Trans.Select ( SelectT ) @@ -71,12 +77,12 @@ import qualified Control.Monad.Trans.RWS.Strict as Strict ( RWST ) import qualified Control.Monad.Trans.State.Strict as Strict ( StateT ) import qualified Control.Monad.Trans.Writer.Strict as Strict ( WriterT ) --- | Class of monads which can perform primitive state-transformer actions +-- | Class of monads which can perform primitive state-transformer actions. class Monad m => PrimMonad m where - -- | State token type + -- | State token type. type PrimState m - -- | Execute a primitive operation + -- | Execute a primitive operation. primitive :: (State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a -- | Class of primitive monads for state-transformer actions. @@ -87,10 +93,10 @@ class Monad m => PrimMonad m where -- -- @since 0.6.0.0 class PrimMonad m => PrimBase m where - -- | Expose the internal structure of the monad + -- | Expose the internal structure of the monad. internal :: m a -> State# (PrimState m) -> (# State# (PrimState m), a #) --- | Execute a primitive operation with no result +-- | Execute a primitive operation with no result. primitive_ :: PrimMonad m => (State# (PrimState m) -> State# (PrimState m)) -> m () {-# INLINE primitive_ #-} @@ -102,6 +108,7 @@ instance PrimMonad IO where type PrimState IO = RealWorld primitive = IO {-# INLINE primitive #-} + instance PrimBase IO where internal (IO p) = p {-# INLINE internal #-} @@ -122,18 +129,20 @@ instance PrimBase m => PrimBase (IdentityT m) where internal (IdentityT m) = internal m {-# INLINE internal #-} +#if !MIN_VERSION_transformers(0,6,0) instance PrimMonad m => PrimMonad (ListT m) where type PrimState (ListT m) = PrimState m primitive = lift . primitive {-# INLINE primitive #-} -instance PrimMonad m => PrimMonad (MaybeT m) where - type PrimState (MaybeT m) = PrimState m +instance (Error e, PrimMonad m) => PrimMonad (ErrorT e m) where + type PrimState (ErrorT e m) = PrimState m primitive = lift . primitive {-# INLINE primitive #-} +#endif -instance (Error e, PrimMonad m) => PrimMonad (ErrorT e m) where - type PrimState (ErrorT e m) = PrimState m +instance PrimMonad m => PrimMonad (MaybeT m) where + type PrimState (MaybeT m) = PrimState m primitive = lift . primitive {-# INLINE primitive #-} @@ -171,24 +180,20 @@ instance (Monoid w, PrimMonad m) => PrimMonad (CPS.RWST r w s m) where {-# INLINE primitive #-} #endif -#if MIN_VERSION_transformers(0,4,0) instance PrimMonad m => PrimMonad (ExceptT e m) where type PrimState (ExceptT e m) = PrimState m primitive = lift . primitive {-# INLINE primitive #-} -#endif #if MIN_VERSION_transformers(0,5,3) -- | @since 0.6.3.0 instance ( Monoid w , PrimMonad m -# if !(MIN_VERSION_base(4,8,0)) - , Functor m -# endif ) => PrimMonad (AccumT w m) where type PrimState (AccumT w m) = PrimState m primitive = lift . primitive {-# INLINE primitive #-} + instance PrimMonad m => PrimMonad (SelectT r m) where type PrimState (SelectT r m) = PrimState m primitive = lift . primitive @@ -214,10 +219,40 @@ instance PrimMonad (ST s) where type PrimState (ST s) = s primitive = ST {-# INLINE primitive #-} + instance PrimBase (ST s) where internal (ST p) = p {-# INLINE internal #-} +-- see https://gitlab.haskell.org/ghc/ghc/commit/2f5cb3d44d05e581b75a47fec222577dfa7a533e +-- for why we only support an instance for ghc >= 8.2 +#if __GLASGOW_HASKELL__ >= 802 +-- @since 0.7.1.0 +instance PrimMonad (L.ST s) where + type PrimState (L.ST s) = s + primitive = L.strictToLazyST . primitive + {-# INLINE primitive #-} + +-- @since 0.7.1.0 +instance PrimBase (L.ST s) where + internal = internal . L.lazyToStrictST + {-# INLINE internal #-} +#endif + +-- | 'PrimMonad''s state token type can be annoying to handle +-- in constraints. This typeclass lets users (visually) notice +-- 'PrimState' equality constraints less, by witnessing that +-- @s ~ 'PrimState' m@. +class (PrimMonad m, s ~ PrimState m) => MonadPrim s m +instance (PrimMonad m, s ~ PrimState m) => MonadPrim s m + +-- | 'PrimBase''s state token type can be annoying to handle +-- in constraints. This typeclass lets users (visually) notice +-- 'PrimState' equality constraints less, by witnessing that +-- @s ~ 'PrimState' m@. +class (PrimBase m, MonadPrim s m) => MonadPrimBase s m +instance (PrimBase m, MonadPrim s m) => MonadPrimBase s m + -- | Lifts a 'PrimBase' into another 'PrimMonad' with the same underlying state -- token type. liftPrim @@ -288,34 +323,78 @@ unsafeIOToPrim :: PrimMonad m => IO a -> m a {-# INLINE unsafeIOToPrim #-} unsafeIOToPrim = unsafePrimToPrim +-- | See 'unsafeInlineIO'. This function is not recommended for the same +-- reasons. unsafeInlinePrim :: PrimBase m => m a -> a {-# INLINE unsafeInlinePrim #-} unsafeInlinePrim m = unsafeInlineIO (unsafePrimToIO m) +-- | Generally, do not use this function. It is the same as +-- @accursedUnutterablePerformIO@ from @bytestring@ and is well behaved under +-- narrow conditions. See the documentation of that function to get an idea +-- of when this is sound. In most cases @GHC.IO.Unsafe.unsafeDupablePerformIO@ +-- should be preferred. unsafeInlineIO :: IO a -> a {-# INLINE unsafeInlineIO #-} unsafeInlineIO m = case internal m realWorld# of (# _, r #) -> r +-- | See 'unsafeInlineIO'. This function is not recommended for the same +-- reasons. Prefer @runST@ when @s@ is free. unsafeInlineST :: ST s a -> a {-# INLINE unsafeInlineST #-} unsafeInlineST = unsafeInlinePrim +-- | Ensure that the value is considered alive by the garbage collection. +-- Warning: GHC has optimization passes that can erase @touch@ if it is +-- certain that an exception is thrown afterward. Prefer 'keepAlive'. touch :: PrimMonad m => a -> m () {-# INLINE touch #-} touch x = unsafePrimToPrim $ (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 ()) + +-- | Keep value @x@ alive until computation @k@ completes. +-- Warning: This primop exists for completeness, but it is difficult to use +-- correctly. Prefer 'keepAliveUnlifted' if the value to keep alive is simply +-- a wrapper around an unlifted type (e.g. @ByteArray@). +keepAlive :: PrimBase m + => a -- ^ Value @x@ to keep alive while computation @k@ runs. + -> m r -- ^ Computation @k@ + -> m r +#if defined(HAVE_KEEPALIVE) +{-# INLINE keepAlive #-} +keepAlive x k = + primitive $ \s0 -> keepAliveLiftedLifted# x s0 (internal k) + +#else +{-# NOINLINE keepAlive #-} +keepAlive x k = k <* touch x +#endif + +-- | Variant of 'keepAlive' in which the value kept alive is of an unlifted +-- boxed type. +keepAliveUnlifted :: forall (m :: Type -> Type) (a :: UnliftedType) (r :: Type). PrimBase m => a -> m r -> m r +#if defined(HAVE_KEEPALIVE) +{-# INLINE keepAliveUnlifted #-} +keepAliveUnlifted x k = + primitive $ \s0 -> keepAliveUnliftedLifted# x s0 (internal k) + +#else +{-# NOINLINE keepAliveUnlifted #-} +keepAliveUnlifted x k = k <* touchUnlifted x +#endif + -- | Create an action to force a value; generalizes 'Control.Exception.evaluate' -- -- @since 0.6.2.0 evalPrim :: forall a m . PrimMonad m => a -> m a -#if MIN_VERSION_base(4,4,0) evalPrim a = primitive (\s -> seq# a s) -#else --- This may or may not work so well, but there's probably nothing better to do. -{-# NOINLINE evalPrim #-} -evalPrim a = unsafePrimToPrim (evaluate a :: IO a) -#endif noDuplicate :: PrimMonad m => m () #if __GLASGOW_HASKELL__ >= 802 diff --git a/examples/primitive/Data/Primitive.hs b/examples/primitive/Data/Primitive.hs index 0db9bd831..075c1b5f7 100644 --- a/examples/primitive/Data/Primitive.hs +++ b/examples/primitive/Data/Primitive.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE MagicHash #-} -{-# OPTIONS_GHC -fno-warn-duplicate-exports #-} -- | -- Module : Data.Primitive -- Copyright : (c) Roman Leshchinskiy 2009-2012 @@ -8,19 +6,19 @@ -- Maintainer : Roman Leshchinskiy -- Portability : non-portable -- --- Reexports all primitive operations --- -module Data.Primitive ( - -- * Re-exports - module Data.Primitive.Types - ,module Data.Primitive.Array - ,module Data.Primitive.ByteArray - ,module Data.Primitive.SmallArray - ,module Data.Primitive.PrimArray - ,module Data.Primitive.MutVar +-- Reexports all primitive operations. + +module Data.Primitive + ( -- * Re-exports + module Data.Primitive.Types + , module Data.Primitive.Array + , module Data.Primitive.ByteArray + , module Data.Primitive.SmallArray + , module Data.Primitive.PrimArray + , module Data.Primitive.MutVar -- * Naming Conventions -- $namingConventions -) where + ) where import Data.Primitive.Types import Data.Primitive.Array @@ -39,21 +37,22 @@ of the variants of the array indexing function are: > indexPrimArray :: Prim a => PrimArray a -> Int -> a In a few places, where the language sounds more natural, the array type -is instead used as a prefix. For example, @Data.Primitive.SmallArray@ -exports @smallArrayFromList@, which would sound unnatural if it used +is instead used as a prefix. For example, "Data.Primitive.SmallArray" +exports 'smallArrayFromList', which would sound unnatural if it used @SmallArray@ as a suffix instead. -This library provides several functions traversing, building, and filtering +This library provides several functions for traversing, building, and filtering arrays. These functions are suffixed with an additional character to -indicate their the nature of their effectfulness: +indicate the nature of their effectfulness: * No suffix: A non-effectful pass over the array. -* @-A@ suffix: An effectful pass over the array, where the effect is 'Applicative'. -* @-P@ suffix: An effectful pass over the array, where the effect is 'PrimMonad'. +* @A@ suffix: An effectful pass over the array, where the effect is 'Applicative'. +* @P@ suffix: An effectful pass over the array, where the effect is 'Control.Monad.Primitive.PrimMonad'. Additionally, an apostrophe can be used to indicate strictness in the elements. -The variants with an apostrophe are used in @Data.Primitive.Array@ but not -in @Data.Primitive.PrimArray@ since the array type it provides is always strict in the element. +The variants with an apostrophe are used in "Data.Primitive.Array" but not +in "Data.Primitive.PrimArray" since the array type it provides is always strict in the element anyway. + For example, there are three variants of the function that filters elements from a primitive array. @@ -61,17 +60,17 @@ from a primitive array. > filterPrimArrayA :: (Prim a, Applicative f) => (a -> f Bool) -> PrimArray a -> f (PrimArray a) > filterPrimArrayP :: (Prim a, PrimMonad m) => (a -> m Bool) -> PrimArray a -> m (PrimArray a) -As long as the effectful context is a monad that is sufficiently affine -the behaviors of the 'Applicative' and 'PrimMonad' variants produce the same results -and differ only in their strictness. Monads that are sufficiently affine -include: +As long as the effectful context is a monad that is sufficiently affine, +the behaviors of the 'Applicative' and 'Control.Monad.Primitive.PrimMonad' +variants produce the same results and differ only in their strictness. +Monads that are sufficiently affine include: * 'IO' and 'ST' * Any combination of 'MaybeT', 'ExceptT', 'StateT' and 'Writer' on top of another sufficiently affine monad. -* Any Monad which does not include backtracking or other mechanism where an effect can -happen more than once is an Affine Monad in the sense we care about. ContT, LogicT, ListT are all -examples of search/control monads which are NOT affine: they can run a sub computation more than once. +* Any Monad which does not include backtracking or other mechanisms where an effect can + happen more than once is an affine Monad in the sense we care about. @ContT@, @LogicT@, @ListT@ are all + examples of search/control monads which are NOT affine: they can run a sub computation more than once. There is one situation where the names deviate from effectful suffix convention described above. Throughout the haskell ecosystem, the 'Applicative' variant of diff --git a/examples/primitive/Data/Primitive/Array.hs b/examples/primitive/Data/Primitive/Array.hs index a70720fb6..c527c603e 100644 --- a/examples/primitive/Data/Primitive/Array.hs +++ b/examples/primitive/Data/Primitive/Array.hs @@ -1,6 +1,7 @@ {-# LANGUAGE CPP, MagicHash, UnboxedTuples, DeriveDataTypeable, BangPatterns #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TemplateHaskellQuotes #-} -- | -- Module : Data.Primitive.Array @@ -11,64 +12,47 @@ -- Portability : non-portable -- -- Primitive arrays of boxed values. --- module Data.Primitive.Array ( Array(..), MutableArray(..), newArray, readArray, writeArray, indexArray, indexArrayM, indexArray##, - freezeArray, thawArray, runArray, + freezeArray, thawArray, runArray, createArray, unsafeFreezeArray, unsafeThawArray, sameMutableArray, copyArray, copyMutableArray, cloneArray, cloneMutableArray, sizeofArray, sizeofMutableArray, - fromListN, fromList, + emptyArray, + arrayFromListN, arrayFromList, mapArray', traverseArrayP ) where +import Control.DeepSeq import Control.Monad.Primitive +import Data.Primitive.Internal.Read (Tag(..),lexTag) -import GHC.Base ( Int(..) ) -import GHC.Exts -#if (MIN_VERSION_base(4,7,0)) - hiding (toList) -#endif +import GHC.Exts hiding (toList) import qualified GHC.Exts as Exts -#if (MIN_VERSION_base(4,7,0)) -import GHC.Exts (fromListN, fromList) -#endif import Data.Typeable ( Typeable ) import Data.Data - (Data(..), DataType, mkDataType, Constr, mkConstr, Fixity(..), constrIndex) -import Data.Primitive.Internal.Compat ( isTrue#, mkNoRepType ) + (Data(..), DataType, mkDataType, mkNoRepType, Constr, mkConstr, Fixity(..), constrIndex) -import Control.Monad.ST(ST,runST) +import Control.Monad.ST (ST, runST) import Control.Applicative -import Control.Monad (MonadPlus(..), when) +import Control.Monad (MonadPlus(..), when, liftM2) import qualified Control.Monad.Fail as Fail import Control.Monad.Fix -#if MIN_VERSION_base(4,4,0) +import qualified Data.Foldable as Foldable import Control.Monad.Zip -#endif import Data.Foldable (Foldable(..), toList) -#if !(MIN_VERSION_base(4,8,0)) -import Data.Traversable (Traversable(..)) -import Data.Monoid -#endif -#if MIN_VERSION_base(4,9,0) import qualified GHC.ST as GHCST import qualified Data.Foldable as F import Data.Semigroup -#endif -#if MIN_VERSION_base(4,8,0) import Data.Functor.Identity -#endif -#if MIN_VERSION_base(4,10,0) -import GHC.Exts (runRW#) -#elif MIN_VERSION_base(4,9,0) +#if !MIN_VERSION_base(4,10,0) import GHC.Base (runRW#) #endif @@ -77,31 +61,71 @@ import Text.ParserCombinators.ReadPrec (ReadPrec) import qualified Text.ParserCombinators.ReadPrec as RdPrc import Text.ParserCombinators.ReadP -#if MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,4,0) -import Data.Functor.Classes (Eq1(..),Ord1(..),Show1(..),Read1(..)) -#endif -import Control.Monad (liftM2) +import Data.Functor.Classes (Eq1(..), Ord1(..), Show1(..), Read1(..)) +import Language.Haskell.TH.Syntax (Lift (..)) --- | Boxed arrays +-- | Boxed arrays. data Array a = Array { array# :: Array# a } deriving ( Typeable ) +instance Lift a => Lift (Array a) where +#if MIN_VERSION_template_haskell(2,16,0) + liftTyped ary = case lst of + [] -> [|| Array (emptyArray# (##)) ||] + [x] -> [|| pure $! x ||] + x : xs -> [|| unsafeArrayFromListN' len x xs ||] +#else + lift ary = case lst of + [] -> [| Array (emptyArray# (##)) |] + [x] -> [| pure $! x |] + x : xs -> [| unsafeArrayFromListN' len x xs |] +#endif + where + len = length ary + lst = toList ary + +-- | Strictly create an array from a nonempty list (represented as +-- a first element and a list of the rest) of a known length. If the length +-- of the list does not match the given length, this makes demons fly +-- out of your nose. We use it in the 'Lift' instance. If you edit the +-- splice and break it, you get to keep both pieces. +unsafeArrayFromListN' :: Int -> a -> [a] -> Array a +unsafeArrayFromListN' n y ys = + createArray n y $ \ma -> + let go !_ix [] = return () + go !ix (!x : xs) = do + writeArray ma ix x + go (ix+1) xs + in go 1 ys + +#if MIN_VERSION_deepseq(1,4,3) +instance NFData1 Array where + liftRnf r = Foldable.foldl' (\_ -> r) () +#endif + +instance NFData a => NFData (Array a) where + rnf = Foldable.foldl' (\_ -> rnf) () + -- | Mutable boxed arrays associated with a primitive state token. data MutableArray s a = MutableArray { marray# :: MutableArray# s a } deriving ( Typeable ) +-- | The number of elements in an immutable array. sizeofArray :: Array a -> Int sizeofArray a = I# (sizeofArray# (array# a)) {-# INLINE sizeofArray #-} +-- | The number of elements in a mutable array. sizeofMutableArray :: MutableArray s a -> Int sizeofMutableArray a = I# (sizeofMutableArray# (marray# a)) {-# INLINE sizeofMutableArray #-} -- | Create a new mutable array of the specified size and initialise all -- elements with the given value. +-- +-- /Note:/ this function does not check if the input is non-negative. newArray :: PrimMonad m => Int -> a -> m (MutableArray (PrimState m) a) {-# INLINE newArray #-} newArray (I# n#) x = primitive @@ -111,16 +135,22 @@ newArray (I# n#) x = primitive in (# s'# , ma #)) -- | Read a value from the array at the given index. +-- +-- /Note:/ this function does not do bounds checking. readArray :: PrimMonad m => MutableArray (PrimState m) a -> Int -> m a {-# INLINE readArray #-} readArray arr (I# i#) = primitive (readArray# (marray# arr) i#) -- | Write a value to the array at the given index. +-- +-- /Note:/ this function does not do bounds checking. writeArray :: PrimMonad m => MutableArray (PrimState m) a -> Int -> a -> m () {-# INLINE writeArray #-} writeArray arr (I# i#) x = primitive_ (writeArray# (marray# arr) i# x) -- | Read a value from the immutable array at the given index. +-- +-- /Note:/ this function does not do bounds checking. indexArray :: Array a -> Int -> a {-# INLINE indexArray #-} indexArray arr (I# i#) = case indexArray# (array# arr) i# of (# x #) -> x @@ -128,11 +158,13 @@ indexArray arr (I# i#) = case indexArray# (array# arr) i# of (# x #) -> x -- | Read a value from the immutable array at the given index, returning -- the result in an unboxed unary tuple. This is currently used to implement -- folds. +-- +-- /Note:/ this function does not do bounds checking. indexArray## :: Array a -> Int -> (# a #) indexArray## arr (I# i) = indexArray# (array# arr) i {-# INLINE indexArray## #-} --- | Monadically read a value from the immutable array at the given index. +-- | Read a value from the immutable array at the given index using an applicative. -- This allows us to be strict in the array while remaining lazy in the read -- element which is very useful for collective operations. Suppose we want to -- copy an array. We could do something like this: @@ -141,7 +173,7 @@ indexArray## arr (I# i) = indexArray# (array# arr) i -- > writeArray marr i (indexArray arr i) ... -- > ... -- --- But since primitive arrays are lazy, the calls to 'indexArray' will not be +-- But since the arrays are lazy, the calls to 'indexArray' will not be -- evaluated. Rather, @marr@ will be filled with thunks each of which would -- retain a reference to @arr@. This is definitely not what we want! -- @@ -155,15 +187,19 @@ indexArray## arr (I# i) = indexArray# (array# arr) i -- Now, indexing is executed immediately although the returned element is -- still not evaluated. -- -indexArrayM :: Monad m => Array a -> Int -> m a +-- /Note:/ this function does not do bounds checking. +indexArrayM :: Applicative m => Array a -> Int -> m a {-# INLINE indexArrayM #-} indexArrayM arr (I# i#) - = case indexArray# (array# arr) i# of (# x #) -> return x + = case indexArray# (array# arr) i# of (# x #) -> pure x -- | Create an immutable copy of a slice of an array. -- -- This operation makes a copy of the specified section, so it is safe to -- continue using the mutable array afterward. +-- +-- /Note:/ The provided array should contain the full subrange +-- specified by the two Ints, but this is not checked. freezeArray :: PrimMonad m => MutableArray (PrimState m) a -- ^ source @@ -189,6 +225,9 @@ unsafeFreezeArray arr -- -- This operation makes a copy of the specified slice, so it is safe to use the -- immutable array afterward. +-- +-- /Note:/ The provided array should contain the full subrange +-- specified by the two Ints, but this is not checked. thawArray :: PrimMonad m => Array a -- ^ source @@ -217,6 +256,8 @@ sameMutableArray arr brr = isTrue# (sameMutableArray# (marray# arr) (marray# brr)) -- | Copy a slice of an immutable array to a mutable array. +-- +-- /Note:/ this function does not do bounds or overlap checking. copyArray :: PrimMonad m => MutableArray (PrimState m) a -- ^ destination array -> Int -- ^ offset into destination array @@ -225,26 +266,12 @@ copyArray :: PrimMonad m -> Int -- ^ number of elements to copy -> m () {-# INLINE copyArray #-} -#if __GLASGOW_HASKELL__ > 706 --- NOTE: copyArray# and copyMutableArray# are slightly broken in GHC 7.6.* and earlier copyArray (MutableArray dst#) (I# doff#) (Array src#) (I# soff#) (I# len#) = primitive_ (copyArray# src# soff# dst# doff# len#) -#else -copyArray !dst !doff !src !soff !len = go 0 - where - go i | i < len = do - x <- indexArrayM src (soff+i) - writeArray dst (doff+i) x - go (i+1) - | otherwise = return () -#endif --- | Copy a slice of a mutable array to another array. The two arrays must --- not be the same when using this library with GHC versions 7.6 and older. --- In GHC 7.8 and newer, overlapping arrays will behave correctly. +-- | Copy a slice of a mutable array to another array. The two arrays may overlap. -- --- Note: The order of arguments is different from that of 'copyMutableArray#'. The primop --- has the source first while this wrapper has the destination first. +-- /Note:/ this function does not do bounds or overlap checking. copyMutableArray :: PrimMonad m => MutableArray (PrimState m) a -- ^ destination array -> Int -- ^ offset into destination array @@ -253,23 +280,14 @@ copyMutableArray :: PrimMonad m -> Int -- ^ number of elements to copy -> m () {-# INLINE copyMutableArray #-} -#if __GLASGOW_HASKELL__ > 706 --- NOTE: copyArray# and copyMutableArray# are slightly broken in GHC 7.6.* and earlier copyMutableArray (MutableArray dst#) (I# doff#) (MutableArray src#) (I# soff#) (I# len#) = primitive_ (copyMutableArray# src# soff# dst# doff# len#) -#else -copyMutableArray !dst !doff !src !soff !len = go 0 - where - go i | i < len = do - x <- readArray src (soff+i) - writeArray dst (doff+i) x - go (i+1) - | otherwise = return () -#endif --- | Return a newly allocated Array with the specified subrange of the --- provided Array. The provided Array should contain the full subrange +-- | Return a newly allocated 'Array' with the specified subrange of the +-- provided 'Array'. +-- +-- /Note:/ The provided array should contain the full subrange -- specified by the two Ints, but this is not checked. cloneArray :: Array a -- ^ source array -> Int -- ^ offset into destination array @@ -279,9 +297,12 @@ cloneArray :: Array a -- ^ source array cloneArray (Array arr#) (I# off#) (I# len#) = case cloneArray# arr# off# len# of arr'# -> Array arr'# --- | Return a newly allocated MutableArray. with the specified subrange of --- the provided MutableArray. The provided MutableArray should contain the +-- | Return a newly allocated 'MutableArray'. with the specified subrange of +-- the provided 'MutableArray'. The provided 'MutableArray' should contain the -- full subrange specified by the two Ints, but this is not checked. +-- +-- /Note:/ The provided array should contain the full subrange +-- specified by the two Ints, but this is not checked. cloneMutableArray :: PrimMonad m => MutableArray (PrimState m) a -- ^ source array -> Int -- ^ offset into destination array @@ -292,48 +313,15 @@ cloneMutableArray (MutableArray arr#) (I# off#) (I# len#) = primitive (\s# -> case cloneMutableArray# arr# off# len# s# of (# s'#, arr'# #) -> (# s'#, MutableArray arr'# #)) +-- | The empty 'Array'. emptyArray :: Array a emptyArray = runST $ newArray 0 (die "emptyArray" "impossible") >>= unsafeFreezeArray {-# NOINLINE emptyArray #-} -#if !MIN_VERSION_base(4,9,0) -createArray - :: Int - -> a - -> (forall s. MutableArray s a -> ST s ()) - -> Array a -createArray 0 _ _ = emptyArray -createArray n x f = runArray $ do - mary <- newArray n x - f mary - pure mary - -runArray - :: (forall s. ST s (MutableArray s a)) - -> Array a -runArray m = runST $ m >>= unsafeFreezeArray - -#else /* Below, runRW# is available. */ - --- This low-level business is designed to work with GHC's worker-wrapper --- transformation. A lot of the time, we don't actually need an Array --- constructor. By putting it on the outside, and being careful about --- how we special-case the empty array, we can make GHC smarter about this. --- The only downside is that separately created 0-length arrays won't share --- their Array constructors, although they'll share their underlying --- Array#s. -createArray - :: Int - -> a - -> (forall s. MutableArray s a -> ST s ()) - -> Array a -createArray 0 _ _ = Array (emptyArray# (# #)) -createArray n x f = runArray $ do - mary <- newArray n x - f mary - pure mary - +-- | Execute the monadic action and freeze the resulting array. +-- +-- > runArray m = runST $ m >>= unsafeFreezeArray runArray :: (forall s. ST s (MutableArray s a)) -> Array a @@ -352,7 +340,33 @@ unST (GHCST.ST f) = f emptyArray# :: (# #) -> Array# a emptyArray# _ = case emptyArray of Array ar -> ar {-# NOINLINE emptyArray# #-} -#endif + +-- | Create an array of the given size with a default value, +-- apply the monadic function and freeze the result. If the +-- size is 0, return 'emptyArray' (rather than a new copy thereof). +-- +-- > createArray 0 _ _ = emptyArray +-- > createArray n x f = runArray $ do +-- > mary <- newArray n x +-- > f mary +-- > pure mary +createArray + :: Int + -> a + -> (forall s. MutableArray s a -> ST s ()) + -> Array a +-- This low-level business is designed to work with GHC's worker-wrapper +-- transformation. A lot of the time, we don't actually need an Array +-- constructor. By putting it on the outside, and being careful about +-- how we special-case the empty array, we can make GHC smarter about this. +-- The only downside is that separately created 0-length arrays won't share +-- their Array constructors, although they'll share their underlying +-- Array#s. +createArray 0 _ _ = Array (emptyArray# (# #)) +createArray n x f = runArray $ do + mary <- newArray n x + f mary + pure mary die :: String -> String -> a @@ -363,20 +377,14 @@ arrayLiftEq p a1 a2 = sizeofArray a1 == sizeofArray a2 && loop (sizeofArray a1 - where loop i | i < 0 = True | (# x1 #) <- indexArray## a1 i , (# x2 #) <- indexArray## a2 i - , otherwise = p x1 x2 && loop (i-1) + , otherwise = p x1 x2 && loop (i - 1) instance Eq a => Eq (Array a) where a1 == a2 = arrayLiftEq (==) a1 a2 -#if MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,4,0) -- | @since 0.6.4.0 instance Eq1 Array where -#if MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,5,0) liftEq = arrayLiftEq -#else - eq1 = arrayLiftEq (==) -#endif -#endif instance Eq (MutableArray s a) where ma1 == ma2 = isTrue# (sameMutableArray# (marray# ma1) (marray# ma2)) @@ -389,22 +397,16 @@ arrayLiftCompare elemCompare a1 a2 = loop 0 | i < mn , (# x1 #) <- indexArray## a1 i , (# x2 #) <- indexArray## a2 i - = elemCompare x1 x2 `mappend` loop (i+1) + = elemCompare x1 x2 `mappend` loop (i + 1) | otherwise = compare (sizeofArray a1) (sizeofArray a2) -- | Lexicographic ordering. Subject to change between major versions. instance Ord a => Ord (Array a) where compare a1 a2 = arrayLiftCompare compare a1 a2 -#if MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,4,0) -- | @since 0.6.4.0 instance Ord1 Array where -#if MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,5,0) liftCompare = arrayLiftCompare -#else - compare1 = arrayLiftCompare compare -#endif -#endif instance Foldable Array where -- Note: we perform the array lookups eagerly so we won't @@ -416,7 +418,7 @@ instance Foldable Array where go i | i == sz = z | (# x #) <- indexArray## ary i - = f x (go (i+1)) + = f x (go (i + 1)) in go 0 {-# INLINE foldr #-} foldl f = \z !ary -> @@ -424,7 +426,7 @@ instance Foldable Array where go i | i < 0 = z | (# x #) <- indexArray## ary i - = f (go (i-1)) x + = f (go (i - 1)) x in go (sizeofArray ary - 1) {-# INLINE foldl #-} foldr1 f = \ !ary -> @@ -433,7 +435,7 @@ instance Foldable Array where go i = case indexArray## ary i of (# x #) | i == sz -> x - | otherwise -> f x (go (i+1)) + | otherwise -> f x (go (i + 1)) in if sz < 0 then die "foldr1" "empty array" else go 0 @@ -449,13 +451,12 @@ instance Foldable Array where then die "foldl1" "empty array" else go sz {-# INLINE foldl1 #-} -#if MIN_VERSION_base(4,6,0) foldr' f = \z !ary -> let go i !acc | i == -1 = acc | (# x #) <- indexArray## ary i - = go (i-1) (f x acc) + = go (i - 1) (f x acc) in go (sizeofArray ary - 1) z {-# INLINE foldr' #-} foldl' f = \z !ary -> @@ -464,11 +465,9 @@ instance Foldable Array where go i !acc | i == sz = acc | (# x #) <- indexArray## ary i - = go (i+1) (f acc x) + = go (i + 1) (f acc x) in go 0 z {-# INLINE foldl' #-} -#endif -#if MIN_VERSION_base(4,8,0) null a = sizeofArray a == 0 {-# INLINE null #-} length = sizeofArray @@ -481,7 +480,7 @@ instance Foldable Array where go i !e | i == sz = e | (# x #) <- indexArray## ary i - = go (i+1) (max e x) + = go (i + 1) (max e x) {-# INLINE maximum #-} minimum ary | sz == 0 = die "minimum" "empty array" | (# frst #) <- indexArray## ary 0 @@ -490,15 +489,14 @@ instance Foldable Array where go i !e | i == sz = e | (# x #) <- indexArray## ary i - = go (i+1) (min e x) + = go (i + 1) (min e x) {-# INLINE minimum #-} sum = foldl' (+) 0 {-# INLINE sum #-} product = foldl' (*) 1 {-# INLINE product #-} -#endif -newtype STA a = STA {_runSTA :: forall s. MutableArray# s a -> ST s (Array a)} +newtype STA a = STA { _runSTA :: forall s. MutableArray# s a -> ST s (Array a) } runSTA :: Int -> STA a -> Array a runSTA !sz = \ (STA m) -> runST $ newArray_ sz >>= \ ar -> m (marray# ar) @@ -530,8 +528,8 @@ traverseArray f = \ !ary -> writeArray (MutableArray mary) i b >> m mary) (f x) (go (i + 1)) in if len == 0 - then pure emptyArray - else runSTA len <$> go 0 + then pure emptyArray + else runSTA len <$> go 0 {-# INLINE [1] traverseArray #-} {-# RULES @@ -539,19 +537,15 @@ traverseArray f = \ !ary -> traverseArrayP f "traverse/IO" forall (f :: a -> IO b). traverseArray f = traverseArrayP f - #-} -#if MIN_VERSION_base(4,8,0) -{-# RULES "traverse/Id" forall (f :: a -> Identity b). traverseArray f = (coerce :: (Array a -> Array (Identity b)) -> Array a -> Identity (Array b)) (fmap f) #-} -#endif -- | This is the fastest, most straightforward way to traverse -- an array, but it only works correctly with a sufficiently -- "affine" 'PrimMonad' instance. In particular, it must only produce --- *one* result array. 'Control.Monad.Trans.List.ListT'-transformed +-- /one/ result array. 'Control.Monad.Trans.List.ListT'-transformed -- monads, for example, will not work right at all. traverseArrayP :: PrimMonad m @@ -586,10 +580,12 @@ mapArray' f a = -- We use indexArrayM here so that we will perform the -- indexing eagerly even if f is lazy. let !y = f x - writeArray mb i y >> go (i+1) + writeArray mb i y >> go (i + 1) in go 0 {-# INLINE mapArray' #-} +-- | Create an array from a list of a known length. If the length +-- of the list does not match the given length, this throws an exception. arrayFromListN :: Int -> [a] -> Array a arrayFromListN n l = createArray n (die "fromListN" "uninitialized element") $ \sma -> @@ -603,22 +599,15 @@ arrayFromListN n l = else die "fromListN" "list length greater than specified size" in go 0 l +-- | Create an array from a list. arrayFromList :: [a] -> Array a arrayFromList l = arrayFromListN (length l) l -#if MIN_VERSION_base(4,7,0) instance Exts.IsList (Array a) where type Item (Array a) = a fromListN = arrayFromListN fromList = arrayFromList toList = toList -#else -fromListN :: Int -> [a] -> Array a -fromListN = arrayFromListN - -fromList :: [a] -> Array a -fromList = arrayFromList -#endif instance Functor Array where fmap f a = @@ -627,47 +616,48 @@ instance Functor Array where = return () | otherwise = do x <- indexArrayM a i - writeArray mb i (f x) >> go (i+1) + writeArray mb i (f x) >> go (i + 1) in go 0 -#if MIN_VERSION_base(4,8,0) e <$ a = createArray (sizeofArray a) e (\ !_ -> pure ()) -#endif instance Applicative Array where pure x = runArray $ newArray 1 x - ab <*> a = createArray (szab*sza) (die "<*>" "impossible") $ \mb -> + + ab <*> a = createArray (szab * sza) (die "<*>" "impossible") $ \mb -> let go1 i = when (i < szab) $ do f <- indexArrayM ab i - go2 (i*sza) f 0 - go1 (i+1) + go2 (i * sza) f 0 + go1 (i + 1) go2 off f j = when (j < sza) $ do x <- indexArrayM a j writeArray mb (off + j) (f x) go2 off f (j + 1) in go1 0 - where szab = sizeofArray ab ; sza = sizeofArray a - a *> b = createArray (sza*szb) (die "*>" "impossible") $ \mb -> - let go i | i < sza = copyArray mb (i * szb) b 0 szb + where szab = sizeofArray ab; sza = sizeofArray a + + a *> b = createArray (sza * szb) (die "*>" "impossible") $ \mb -> + let go i | i < sza = copyArray mb (i * szb) b 0 szb *> go (i + 1) | otherwise = return () - in go 0 - where sza = sizeofArray a ; szb = sizeofArray b - a <* b = createArray (sza*szb) (die "<*" "impossible") $ \ma -> - let fill off i e | i < szb = writeArray ma (off+i) e >> fill off (i+1) e + in go 0 + where sza = sizeofArray a; szb = sizeofArray b + + a <* b = createArray (sza * szb) (die "<*" "impossible") $ \ma -> + let fill off i e | i < szb = writeArray ma (off + i) e >> fill off (i + 1) e | otherwise = return () go i | i < sza = do x <- indexArrayM a i - fill (i*szb) 0 x >> go (i+1) + fill (i * szb) 0 x >> go (i + 1) | otherwise = return () - in go 0 - where sza = sizeofArray a ; szb = sizeofArray b + in go 0 + where sza = sizeofArray a; szb = sizeofArray b instance Alternative Array where empty = emptyArray a1 <|> a2 = createArray (sza1 + sza2) (die "<|>" "impossible") $ \ma -> copyArray ma 0 a1 0 sza1 >> copyArray ma sza1 a2 0 sza2 - where sza1 = sizeofArray a1 ; sza2 = sizeofArray a2 + where sza1 = sizeofArray a1; sza2 = sizeofArray a2 some a | sizeofArray a == 0 = emptyArray | otherwise = die "some" "infinite arrays are not well defined" many a | sizeofArray a == 0 = pure [] @@ -682,26 +672,26 @@ instance Monad Array where return = pure (>>) = (*>) - ary >>= f = collect 0 EmptyStack (la-1) + ary >>= f = collect 0 EmptyStack (la - 1) where - la = sizeofArray ary - collect sz stk i - | i < 0 = createArray sz (die ">>=" "impossible") $ fill 0 stk - | (# x #) <- indexArray## ary i - , let sb = f x - lsb = sizeofArray sb - -- If we don't perform this check, we could end up allocating - -- a stack full of empty arrays if someone is filtering most - -- things out. So we refrain from pushing empty arrays. - = if lsb == 0 - then collect sz stk (i - 1) - else collect (sz + lsb) (PushArray sb stk) (i-1) - - fill _ EmptyStack _ = return () - fill off (PushArray sb sbs) smb - | let lsb = sizeofArray sb - = copyArray smb off sb 0 (lsb) - *> fill (off + lsb) sbs smb + la = sizeofArray ary + collect sz stk i + | i < 0 = createArray sz (die ">>=" "impossible") $ fill 0 stk + | (# x #) <- indexArray## ary i + , let sb = f x + lsb = sizeofArray sb + -- If we don't perform this check, we could end up allocating + -- a stack full of empty arrays if someone is filtering most + -- things out. So we refrain from pushing empty arrays. + = if lsb == 0 + then collect sz stk (i - 1) + else collect (sz + lsb) (PushArray sb stk) (i - 1) + + fill _ EmptyStack _ = return () + fill off (PushArray sb sbs) smb + | let lsb = sizeofArray sb + = copyArray smb off sb 0 lsb + *> fill (off + lsb) sbs smb #if !(MIN_VERSION_base(4,13,0)) fail = Fail.fail @@ -721,13 +711,12 @@ zipW s f aa ab = createArray mn (die s "impossible") $ \mc -> x <- indexArrayM aa i y <- indexArrayM ab i writeArray mc i (f x y) - go (i+1) + go (i + 1) | otherwise = return () in go 0 where mn = sizeofArray aa `min` sizeofArray ab {-# INLINE zipW #-} -#if MIN_VERSION_base(4,4,0) instance MonadZip Array where mzip aa ab = zipW "mzip" (,) aa ab mzipWith f aa ab = zipW "mzipWith" f aa ab @@ -739,11 +728,10 @@ instance MonadZip Array where (a, b) <- indexArrayM aab i writeArray ma i a writeArray mb i b - go (i+1) + go (i + 1) go _ = return () go 0 (,) <$> unsafeFreezeArray ma <*> unsafeFreezeArray mb -#endif instance MonadFix Array where mfix f = createArray (sizeofArray (f err)) @@ -755,17 +743,24 @@ instance MonadFix Array where sz = sizeofArray (f err) err = error "mfix for Data.Primitive.Array applied to strict function." -#if MIN_VERSION_base(4,9,0) -- | @since 0.6.3.0 instance Semigroup (Array a) where (<>) = (<|>) sconcat = mconcat . F.toList -#endif + stimes n arr = case compare n 0 of + LT -> die "stimes" "negative multiplier" + EQ -> empty + GT -> createArray (n' * sizeofArray arr) (die "stimes" "impossible") $ \ma -> + let go i = when (i < n') $ do + copyArray ma (i * sizeofArray arr) arr 0 (sizeofArray arr) + go (i + 1) + in go 0 + where n' = fromIntegral n :: Int instance Monoid (Array a) where mempty = empty #if !(MIN_VERSION_base(4,11,0)) - mappend = (<|>) + mappend = (<>) #endif mconcat l = createArray sz (die "mconcat" "impossible") $ \ma -> let go !_ [ ] = return () @@ -775,9 +770,8 @@ instance Monoid (Array a) where where sz = sum . fmap sizeofArray $ l arrayLiftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Array a -> ShowS -arrayLiftShowsPrec elemShowsPrec elemListShowsPrec p a = showParen (p > 10) $ - showString "fromListN " . shows (sizeofArray a) . showString " " - . listLiftShowsPrec elemShowsPrec elemListShowsPrec 11 (toList a) +arrayLiftShowsPrec elemShowsPrec elemListShowsPrec _ a = + listLiftShowsPrec elemShowsPrec elemListShowsPrec 11 (toList a) -- this need to be included for older ghcs listLiftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> [a] -> ShowS @@ -786,73 +780,43 @@ listLiftShowsPrec _ sl _ = sl instance Show a => Show (Array a) where showsPrec p a = arrayLiftShowsPrec showsPrec showList p a -#if MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,4,0) -- | @since 0.6.4.0 instance Show1 Array where -#if MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,5,0) liftShowsPrec = arrayLiftShowsPrec -#else - showsPrec1 = arrayLiftShowsPrec showsPrec showList -#endif -#endif instance Read a => Read (Array a) where readPrec = arrayLiftReadPrec readPrec readListPrec -#if MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,4,0) -- | @since 0.6.4.0 instance Read1 Array where #if MIN_VERSION_base(4,10,0) liftReadPrec = arrayLiftReadPrec -#elif MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,5,0) - liftReadsPrec = arrayLiftReadsPrec #else - readsPrec1 = arrayLiftReadsPrec readsPrec readList -#endif + -- This is just the default implementation of liftReadsPrec, but + -- it is not present in older versions of base. + liftReadsPrec rp rl = RdPrc.readPrec_to_S $ + arrayLiftReadPrec (RdPrc.readS_to_Prec rp) (RdPrc.readS_to_Prec (const rl)) #endif +-- Note [Forgiving Array Read Instance] -- We're really forgiving here. We accept -- "[1,2,3]", "fromList [1,2,3]", and "fromListN 3 [1,2,3]". -- We consider fromListN with an invalid length to be an -- error, rather than a parse failure, because doing otherwise -- seems weird and likely to make debugging difficult. arrayLiftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Array a) -arrayLiftReadPrec _ read_list = parens $ prec app_prec $ RdPrc.lift skipSpaces >> - ((fromList <$> read_list) RdPrc.+++ - do - tag <- RdPrc.lift lexTag - case tag of - FromListTag -> fromList <$> read_list - FromListNTag -> liftM2 fromListN readPrec read_list) - where - app_prec = 10 - -data Tag = FromListTag | FromListNTag - --- Why don't we just use lexP? The general problem with lexP is that --- it doesn't always fail as fast as we might like. It will --- happily read to the end of an absurdly long lexeme (e.g., a 200MB string --- literal) before returning, at which point we'll immediately discard --- the result because it's not an identifier. Doing the job ourselves, we --- can see very quickly when we've run into a problem. We should also get --- a slight efficiency boost by going through the string just once. -lexTag :: ReadP Tag -lexTag = do - _ <- string "fromList" - s <- look - case s of - 'N':c:_ - | '0' <= c && c <= '9' - -> fail "" -- We have fromListN3 or similar - | otherwise -> FromListNTag <$ get -- Skip the 'N' - _ -> return FromListTag - -#if !MIN_VERSION_base(4,10,0) -arrayLiftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Array a) -arrayLiftReadsPrec reads_prec list_reads_prec = RdPrc.readPrec_to_S $ - arrayLiftReadPrec (RdPrc.readS_to_Prec reads_prec) (RdPrc.readS_to_Prec (const list_reads_prec)) -#endif - +arrayLiftReadPrec _ read_list = + ( RdPrc.lift skipSpaces >> fmap fromList read_list ) + RdPrc.+++ + ( parens $ prec app_prec $ do + RdPrc.lift skipSpaces + tag <- RdPrc.lift lexTag + case tag of + FromListTag -> fromList <$> read_list + FromListNTag -> liftM2 fromListN readPrec read_list + ) + where + app_prec = 10 arrayDataType :: DataType arrayDataType = mkDataType "Data.Primitive.Array.Array" [fromListConstr] diff --git a/examples/primitive/Data/Primitive/ByteArray.hs b/examples/primitive/Data/Primitive/ByteArray.hs index e99abe419..03d81a942 100644 --- a/examples/primitive/Data/Primitive/ByteArray.hs +++ b/examples/primitive/Data/Primitive/ByteArray.hs @@ -1,6 +1,8 @@ -{-# LANGUAGE BangPatterns, CPP, MagicHash, UnboxedTuples, UnliftedFFITypes, DeriveDataTypeable #-} +{-# LANGUAGE BangPatterns, CPP, MagicHash, UnboxedTuples, UnliftedFFITypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE RankNTypes #-} -- | -- Module : Data.Primitive.ByteArray @@ -10,8 +12,11 @@ -- Maintainer : Roman Leshchinskiy -- Portability : non-portable -- --- Primitive operations on ByteArrays --- +-- Primitive operations on byte arrays. Most functions in this module include +-- an element type in their type signature and interpret the unit for offsets +-- and lengths as that element. A few functions (e.g. 'copyByteArray', +-- 'freezeByteArray') do not include an element type. Such functions +-- interpret offsets and lengths as units of 8-bit words. module Data.Primitive.ByteArray ( -- * Types @@ -20,26 +25,36 @@ module Data.Primitive.ByteArray ( -- * Allocation newByteArray, newPinnedByteArray, newAlignedPinnedByteArray, resizeMutableByteArray, + shrinkMutableByteArray, -- * Element access readByteArray, writeByteArray, indexByteArray, + -- * Char Element Access + -- $charElementAccess + readCharArray, writeCharArray, indexCharArray, -- * Constructing + emptyByteArray, byteArrayFromList, byteArrayFromListN, -- * Folding foldrByteArray, + -- * Comparing + compareByteArrays, + -- * Freezing and thawing + freezeByteArray, thawByteArray, runByteArray, unsafeFreezeByteArray, unsafeThawByteArray, -- * Block operations copyByteArray, copyMutableByteArray, -#if __GLASGOW_HASKELL__ >= 708 + copyByteArrayToPtr, copyMutableByteArrayToPtr, copyByteArrayToAddr, copyMutableByteArrayToAddr, -#endif + copyPtrToMutableByteArray, moveByteArray, setByteArray, fillByteArray, + cloneByteArray, cloneMutableByteArray, -- * Information sizeofByteArray, @@ -47,57 +62,41 @@ module Data.Primitive.ByteArray ( #if __GLASGOW_HASKELL__ >= 802 isByteArrayPinned, isMutableByteArrayPinned, #endif - byteArrayContents, mutableByteArrayContents + byteArrayContents, + withByteArrayContents, + mutableByteArrayContents, + withMutableByteArrayContents ) where import Control.Monad.Primitive import Control.Monad.ST import Data.Primitive.Types +import Data.Proxy -import Foreign.C.Types -import Data.Word ( Word8 ) -import GHC.Base ( Int(..) ) -#if __GLASGOW_HASKELL__ >= 708 -import qualified GHC.Exts as Exts ( IsList(..) ) -#endif -import GHC.Exts -#if __GLASGOW_HASKELL__ >= 706 - hiding (setByteArray#) -#endif - -import Data.Typeable ( Typeable ) -import Data.Data ( Data(..) ) -import Data.Primitive.Internal.Compat ( isTrue#, mkNoRepType ) -import Numeric - -#if MIN_VERSION_base(4,9,0) -import qualified Data.Semigroup as SG -import qualified Data.Foldable as F -#endif - -#if !(MIN_VERSION_base(4,8,0)) -import Data.Monoid (Monoid(..)) +#if MIN_VERSION_base(4,10,0) +import qualified GHC.ST as GHCST #endif +import Foreign.C.Types +import Data.Word ( Word8 ) #if __GLASGOW_HASKELL__ >= 802 -import GHC.Exts as Exts (isByteArrayPinned#,isMutableByteArrayPinned#) +import qualified GHC.Exts as Exts #endif +import GHC.Exts hiding (setByteArray#) -#if __GLASGOW_HASKELL__ >= 804 -import GHC.Exts (compareByteArrays#) -#else +#if __GLASGOW_HASKELL__ < 804 import System.IO.Unsafe (unsafeDupablePerformIO) #endif --- | Byte arrays -data ByteArray = ByteArray ByteArray# deriving ( Typeable ) +import Data.Array.Byte (ByteArray(..), MutableByteArray(..)) --- | Mutable byte arrays associated with a primitive state token -data MutableByteArray s = MutableByteArray (MutableByteArray# s) - deriving( Typeable ) +import Data.Primitive.Internal.Operations (mutableByteArrayContentsShim) -- | Create a new mutable byte array of the specified size in bytes. +-- The underlying memory is left uninitialized. +-- +-- /Note:/ this function does not check if the input is non-negative. newByteArray :: PrimMonad m => Int -> m (MutableByteArray (PrimState m)) {-# INLINE newByteArray #-} newByteArray (I# n#) @@ -105,7 +104,9 @@ newByteArray (I# n#) (# s'#, arr# #) -> (# s'#, MutableByteArray arr# #)) -- | Create a /pinned/ byte array of the specified size in bytes. The garbage --- collector is guaranteed not to move it. +-- collector is guaranteed not to move it. The underlying memory is left uninitialized. +-- +-- /Note:/ this function does not check if the input is non-negative. newPinnedByteArray :: PrimMonad m => Int -> m (MutableByteArray (PrimState m)) {-# INLINE newPinnedByteArray #-} newPinnedByteArray (I# n#) @@ -114,6 +115,9 @@ newPinnedByteArray (I# n#) -- | Create a /pinned/ byte array of the specified size in bytes and with the -- given alignment. The garbage collector is guaranteed not to move it. +-- The underlying memory is left uninitialized. +-- +-- /Note:/ this function does not check if the input is non-negative. newAlignedPinnedByteArray :: PrimMonad m => Int -- ^ size @@ -125,19 +129,48 @@ newAlignedPinnedByteArray (I# n#) (I# k#) (# s'#, arr# #) -> (# s'#, MutableByteArray arr# #)) -- | Yield a pointer to the array's data. This operation is only safe on --- /pinned/ byte arrays allocated by 'newPinnedByteArray' or --- 'newAlignedPinnedByteArray'. +-- /pinned/ byte arrays. Byte arrays allocated by 'newPinnedByteArray' and +-- 'newAlignedPinnedByteArray' are guaranteed to be pinned. Byte arrays +-- allocated by 'newByteArray' may or may not be pinned (use +-- 'isByteArrayPinned' to figure out). +-- +-- Prefer 'withByteArrayContents', which ensures that the array is not +-- garbage collected while the pointer is being used. byteArrayContents :: ByteArray -> Ptr Word8 {-# INLINE byteArrayContents #-} byteArrayContents (ByteArray arr#) = Ptr (byteArrayContents# arr#) +-- | A composition of 'byteArrayContents' and 'keepAliveUnlifted'. +-- The callback function must not return the pointer. The argument byte +-- array must be /pinned/. See 'byteArrayContents' for an explanation +-- of which byte arrays are pinned. +-- +-- Note: This could be implemented with 'keepAlive' instead of +-- 'keepAliveUnlifted', but 'keepAlive' here would cause GHC to materialize +-- the wrapper data constructor on the heap. +withByteArrayContents :: PrimBase m => ByteArray -> (Ptr Word8 -> m a) -> m a +{-# INLINE withByteArrayContents #-} +withByteArrayContents (ByteArray arr#) f = + keepAliveUnlifted arr# (f (Ptr (byteArrayContents# arr#))) + -- | Yield a pointer to the array's data. This operation is only safe on --- /pinned/ byte arrays allocated by 'newPinnedByteArray' or --- 'newAlignedPinnedByteArray'. +-- /pinned/ byte arrays. See 'byteArrayContents' for an explanation +-- of which byte arrays are pinned. +-- +-- Prefer 'withByteArrayContents', which ensures that the array is not +-- garbage collected while the pointer is being used. mutableByteArrayContents :: MutableByteArray s -> Ptr Word8 {-# INLINE mutableByteArrayContents #-} -mutableByteArrayContents (MutableByteArray arr#) - = Ptr (byteArrayContents# (unsafeCoerce# arr#)) +mutableByteArrayContents (MutableByteArray arr#) = Ptr (mutableByteArrayContentsShim arr#) + +-- | A composition of 'mutableByteArrayContents' and 'keepAliveUnlifted'. +-- The callback function must not return the pointer. The argument byte +-- array must be /pinned/. See 'byteArrayContents' for an explanation +-- of which byte arrays are pinned. +withMutableByteArrayContents :: PrimBase m => MutableByteArray (PrimState m) -> (Ptr Word8 -> m a) -> m a +{-# INLINE withMutableByteArrayContents #-} +withMutableByteArrayContents (MutableByteArray arr#) f = + keepAliveUnlifted arr# (f (Ptr (mutableByteArrayContentsShim arr#))) -- | Check if the two arrays refer to the same memory block. sameMutableByteArray :: MutableByteArray s -> MutableByteArray s -> Bool @@ -161,16 +194,9 @@ resizeMutableByteArray :: PrimMonad m => MutableByteArray (PrimState m) -> Int -> m (MutableByteArray (PrimState m)) {-# INLINE resizeMutableByteArray #-} -#if __GLASGOW_HASKELL__ >= 710 resizeMutableByteArray (MutableByteArray arr#) (I# n#) = primitive (\s# -> case resizeMutableByteArray# arr# n# s# of (# s'#, arr'# #) -> (# s'#, MutableByteArray arr'# #)) -#else -resizeMutableByteArray arr n - = do arr' <- newByteArray n - copyMutableByteArray arr' 0 arr 0 (min (sizeofMutableByteArray arr) n) - return arr' -#endif -- | Get the size of a byte array in bytes. Unlike 'sizeofMutableByteArray', -- this function ensures sequencing in the presence of resizing. @@ -186,6 +212,48 @@ getSizeofMutableByteArray arr = return (sizeofMutableByteArray arr) #endif +-- | Create an immutable copy of a slice of a byte array. The offset and +-- length are given in bytes. +-- +-- This operation makes a copy of the specified section, so it is safe to +-- continue using the mutable array afterward. +-- +-- /Note:/ The provided array should contain the full subrange +-- specified by the two Ints, but this is not checked. +freezeByteArray + :: PrimMonad m + => MutableByteArray (PrimState m) -- ^ source + -> Int -- ^ offset in bytes + -> Int -- ^ length in bytes + -> m ByteArray +{-# INLINE freezeByteArray #-} +freezeByteArray !src !off !len = do + dst <- newByteArray len + copyMutableByteArray dst 0 src off len + unsafeFreezeByteArray dst + +-- | Create a mutable byte array from a slice of an immutable byte array. +-- The offset and length are given in bytes. +-- +-- This operation makes a copy of the specified slice, so it is safe to +-- use the immutable array afterward. +-- +-- /Note:/ The provided array should contain the full subrange +-- specified by the two Ints, but this is not checked. +-- +-- @since 0.7.2.0 +thawByteArray + :: PrimMonad m + => ByteArray -- ^ source + -> Int -- ^ offset in bytes + -> Int -- ^ length in bytes + -> m (MutableByteArray (PrimState m)) +{-# INLINE thawByteArray #-} +thawByteArray !src !off !len = do + dst <- newByteArray len + copyByteArray dst 0 src off len + return dst + -- | Convert a mutable byte array to an immutable one without copying. The -- array should not be modified after the conversion. unsafeFreezeByteArray @@ -208,30 +276,48 @@ sizeofByteArray :: ByteArray -> Int {-# INLINE sizeofByteArray #-} sizeofByteArray (ByteArray arr#) = I# (sizeofByteArray# arr#) --- | Size of the mutable byte array in bytes. This function\'s behavior +-- | Size of the mutable byte array in bytes. +-- +-- This function is deprecated and will be removed. Its behavior -- is undefined if 'resizeMutableByteArray' is ever called on the mutable --- byte array given as the argument. Consequently, use of this function --- is discouraged. Prefer 'getSizeofMutableByteArray', which ensures correct --- sequencing in the presence of resizing. +-- byte array given as the argument. Prefer 'getSizeofMutableByteArray', +-- which ensures correct sequencing in the presence of resizing. sizeofMutableByteArray :: MutableByteArray s -> Int {-# INLINE sizeofMutableByteArray #-} +{-# DEPRECATED sizeofMutableByteArray "use getSizeofMutableByteArray instead" #-} sizeofMutableByteArray (MutableByteArray arr#) = I# (sizeofMutableByteArray# arr#) +-- | Shrink a mutable byte array. The new size is given in bytes. +-- It must be smaller than the old size. The array will be resized in place. +-- +-- @since 0.7.1.0 +shrinkMutableByteArray :: PrimMonad m + => MutableByteArray (PrimState m) + -> Int -- ^ new size + -> m () +{-# INLINE shrinkMutableByteArray #-} +shrinkMutableByteArray (MutableByteArray arr#) (I# n#) + = primitive_ (shrinkMutableByteArray# arr# n#) + #if __GLASGOW_HASKELL__ >= 802 -- | Check whether or not the byte array is pinned. Pinned byte arrays cannot --- be moved by the garbage collector. It is safe to use 'byteArrayContents' --- on such byte arrays. This function is only available when compiling with --- GHC 8.2 or newer. +-- be moved by the garbage collector. It is safe to use 'byteArrayContents' on +-- such byte arrays. +-- +-- Caution: This function is only available when compiling with GHC 8.2 or +-- newer. -- --- @since 0.6.4.0 +-- @since 0.6.4.0 isByteArrayPinned :: ByteArray -> Bool {-# INLINE isByteArrayPinned #-} isByteArrayPinned (ByteArray arr#) = isTrue# (Exts.isByteArrayPinned# arr#) --- | Check whether or not the mutable byte array is pinned. This function is --- only available when compiling with GHC 8.2 or newer. +-- | Check whether or not the mutable byte array is pinned. +-- +-- Caution: This function is only available when compiling with GHC 8.2 or +-- newer. -- --- @since 0.6.4.0 +-- @since 0.6.4.0 isMutableByteArrayPinned :: MutableByteArray s -> Bool {-# INLINE isMutableByteArrayPinned #-} isMutableByteArrayPinned (MutableByteArray marr#) = isTrue# (Exts.isMutableByteArrayPinned# marr#) @@ -239,12 +325,16 @@ isMutableByteArrayPinned (MutableByteArray marr#) = isTrue# (Exts.isMutableByteA -- | Read a primitive value from the byte array. The offset is given in -- elements of type @a@ rather than in bytes. +-- +-- /Note:/ this function does not do bounds checking. indexByteArray :: Prim a => ByteArray -> Int -> a {-# INLINE indexByteArray #-} indexByteArray (ByteArray arr#) (I# i#) = indexByteArray# arr# i# -- | Read a primitive value from the byte array. The offset is given in -- elements of type @a@ rather than in bytes. +-- +-- /Note:/ this function does not do bounds checking. readByteArray :: (Prim a, PrimMonad m) => MutableByteArray (PrimState m) -> Int -> m a {-# INLINE readByteArray #-} @@ -253,6 +343,8 @@ readByteArray (MutableByteArray arr#) (I# i#) -- | Write a primitive value to the byte array. The offset is given in -- elements of type @a@ rather than in bytes. +-- +-- /Note:/ this function does not do bounds checking. writeByteArray :: (Prim a, PrimMonad m) => MutableByteArray (PrimState m) -> Int -> a -> m () {-# INLINE writeByteArray #-} @@ -265,16 +357,21 @@ foldrByteArray :: forall a b. (Prim a) => (a -> b -> b) -> b -> ByteArray -> b foldrByteArray f z arr = go 0 where go i - | i < maxI = f (indexByteArray arr i) (go (i+1)) + | i < maxI = f (indexByteArray arr i) (go (i + 1)) | otherwise = z - maxI = sizeofByteArray arr `quot` sizeOf (undefined :: a) + maxI = sizeofByteArray arr `quot` sizeOfType @a +-- | Create a 'ByteArray' from a list. +-- +-- @byteArrayFromList xs = `byteArrayFromListN` (length xs) xs@ byteArrayFromList :: Prim a => [a] -> ByteArray byteArrayFromList xs = byteArrayFromListN (length xs) xs -byteArrayFromListN :: Prim a => Int -> [a] -> ByteArray +-- | Create a 'ByteArray' from a list of a known length. If the length +-- of the list does not match the given length, this throws an exception. +byteArrayFromListN :: forall a. Prim a => Int -> [a] -> ByteArray byteArrayFromListN n ys = runST $ do - marr <- newByteArray (n * sizeOf (head ys)) + marr <- newByteArray (n * sizeOfType @a) let go !ix [] = if ix == n then return () else die "byteArrayFromListN" "list length less than specified size" @@ -290,40 +387,103 @@ unI# :: Int -> Int# unI# (I# n#) = n# -- | Copy a slice of an immutable byte array to a mutable byte array. +-- +-- /Note:/ this function does not do bounds or overlap checking. copyByteArray - :: PrimMonad m => MutableByteArray (PrimState m) - -- ^ destination array - -> Int -- ^ offset into destination array - -> ByteArray -- ^ source array - -> Int -- ^ offset into source array - -> Int -- ^ number of bytes to copy - -> m () + :: PrimMonad m + => MutableByteArray (PrimState m) -- ^ destination array + -> Int -- ^ offset into destination array + -> ByteArray -- ^ source array + -> Int -- ^ offset into source array + -> Int -- ^ number of bytes to copy + -> m () {-# INLINE copyByteArray #-} copyByteArray (MutableByteArray dst#) doff (ByteArray src#) soff sz = primitive_ (copyByteArray# src# (unI# soff) dst# (unI# doff) (unI# sz)) -- | Copy a slice of a mutable byte array into another array. The two slices -- may not overlap. +-- +-- /Note:/ this function does not do bounds or overlap checking. copyMutableByteArray - :: PrimMonad m => MutableByteArray (PrimState m) - -- ^ destination array - -> Int -- ^ offset into destination array - -> MutableByteArray (PrimState m) - -- ^ source array - -> Int -- ^ offset into source array - -> Int -- ^ number of bytes to copy - -> m () + :: PrimMonad m + => MutableByteArray (PrimState m) -- ^ destination array + -> Int -- ^ offset into destination array + -> MutableByteArray (PrimState m) -- ^ source array + -> Int -- ^ offset into source array + -> Int -- ^ number of bytes to copy + -> m () {-# INLINE copyMutableByteArray #-} copyMutableByteArray (MutableByteArray dst#) doff (MutableByteArray src#) soff sz = primitive_ (copyMutableByteArray# src# (unI# soff) dst# (unI# doff) (unI# sz)) -#if __GLASGOW_HASKELL__ >= 708 +-- | Copy a slice of a byte array to an unmanaged pointer address. These must not +-- overlap. The offset and length are given in elements, not in bytes. +-- +-- /Note:/ this function does not do bounds or overlap checking. +-- +-- @since 0.7.1.0 +copyByteArrayToPtr + :: forall m a. (PrimMonad m, Prim a) + => Ptr a -- ^ destination + -> ByteArray -- ^ source array + -> Int -- ^ offset into source array, interpreted as elements of type @a@ + -> Int -- ^ number of elements to copy + -> m () +{-# INLINE copyByteArrayToPtr #-} +copyByteArrayToPtr (Ptr dst#) (ByteArray src#) soff sz + = primitive_ (copyByteArrayToAddr# src# (unI# soff *# siz#) dst# (unI# sz *# siz#)) + where + siz# = sizeOfType# (Proxy :: Proxy a) + +-- | Copy from an unmanaged pointer address to a byte array. These must not +-- overlap. The offset and length are given in elements, not in bytes. +-- +-- /Note:/ this function does not do bounds or overlap checking. +copyPtrToMutableByteArray :: forall m a. (PrimMonad m, Prim a) + => MutableByteArray (PrimState m) -- ^ destination array + -> Int -- ^ destination offset given in elements of type @a@ + -> Ptr a -- ^ source pointer + -> Int -- ^ number of elements + -> m () +{-# INLINE copyPtrToMutableByteArray #-} +copyPtrToMutableByteArray (MutableByteArray ba#) (I# doff#) (Ptr addr#) (I# n#) = + primitive_ (copyAddrToByteArray# addr# ba# (doff# *# siz#) (n# *# siz#)) + where + siz# = sizeOfType# (Proxy :: Proxy a) + + +-- | Copy a slice of a mutable byte array to an unmanaged pointer address. +-- These must not overlap. The offset and length are given in elements, not +-- in bytes. +-- +-- /Note:/ this function does not do bounds or overlap checking. +-- +-- @since 0.7.1.0 +copyMutableByteArrayToPtr + :: forall m a. (PrimMonad m, Prim a) + => Ptr a -- ^ destination + -> MutableByteArray (PrimState m) -- ^ source array + -> Int -- ^ offset into source array, interpreted as elements of type @a@ + -> Int -- ^ number of elements to copy + -> m () +{-# INLINE copyMutableByteArrayToPtr #-} +copyMutableByteArrayToPtr (Ptr dst#) (MutableByteArray src#) soff sz + = primitive_ (copyMutableByteArrayToAddr# src# (unI# soff *# siz#) dst# (unI# sz *# siz#)) + where + siz# = sizeOfType# (Proxy :: Proxy a) + +------ +--- These latter two should be DEPRECATED +----- + -- | Copy a slice of a byte array to an unmanaged address. These must not --- overlap. This function is only available when compiling with GHC 7.8 --- or newer. +-- overlap. -- --- @since 0.6.4.0 +-- Note: This function is just 'copyByteArrayToPtr' where @a@ is 'Word8'. +-- +-- @since 0.6.4.0 copyByteArrayToAddr :: PrimMonad m => Ptr Word8 -- ^ destination @@ -336,10 +496,11 @@ copyByteArrayToAddr (Ptr dst#) (ByteArray src#) soff sz = primitive_ (copyByteArrayToAddr# src# (unI# soff) dst# (unI# sz)) -- | Copy a slice of a mutable byte array to an unmanaged address. These must --- not overlap. This function is only available when compiling with GHC 7.8 --- or newer. +-- not overlap. +-- +-- Note: This function is just 'copyMutableByteArrayToPtr' where @a@ is 'Word8'. -- --- @since 0.6.4.0 +-- @since 0.6.4.0 copyMutableByteArrayToAddr :: PrimMonad m => Ptr Word8 -- ^ destination @@ -350,19 +511,17 @@ copyMutableByteArrayToAddr {-# INLINE copyMutableByteArrayToAddr #-} copyMutableByteArrayToAddr (Ptr dst#) (MutableByteArray src#) soff sz = primitive_ (copyMutableByteArrayToAddr# src# (unI# soff) dst# (unI# sz)) -#endif -- | Copy a slice of a mutable byte array into another, potentially -- overlapping array. moveByteArray - :: PrimMonad m => MutableByteArray (PrimState m) - -- ^ destination array - -> Int -- ^ offset into destination array - -> MutableByteArray (PrimState m) - -- ^ source array - -> Int -- ^ offset into source array - -> Int -- ^ number of bytes to copy - -> m () + :: PrimMonad m + => MutableByteArray (PrimState m) -- ^ destination array + -> Int -- ^ offset into destination array + -> MutableByteArray (PrimState m) -- ^ source array + -> Int -- ^ offset into source array + -> Int -- ^ number of bytes to copy + -> m () {-# INLINE moveByteArray #-} moveByteArray (MutableByteArray dst#) doff (MutableByteArray src#) soff sz @@ -372,179 +531,154 @@ moveByteArray (MutableByteArray dst#) doff -- | Fill a slice of a mutable byte array with a value. The offset and length -- are given in elements of type @a@ rather than in bytes. +-- +-- /Note:/ this function does not do bounds checking. setByteArray - :: (Prim a, PrimMonad m) => MutableByteArray (PrimState m) -- ^ array to fill - -> Int -- ^ offset into array - -> Int -- ^ number of values to fill - -> a -- ^ value to fill with - -> m () + :: (Prim a, PrimMonad m) + => MutableByteArray (PrimState m) -- ^ array to fill + -> Int -- ^ offset into array + -> Int -- ^ number of values to fill + -> a -- ^ value to fill with + -> m () {-# INLINE setByteArray #-} setByteArray (MutableByteArray dst#) (I# doff#) (I# sz#) x = primitive_ (setByteArray# dst# doff# sz# x) -- | Fill a slice of a mutable byte array with a byte. +-- +-- /Note:/ this function does not do bounds checking. fillByteArray - :: PrimMonad m => MutableByteArray (PrimState m) - -- ^ array to fill - -> Int -- ^ offset into array - -> Int -- ^ number of bytes to fill - -> Word8 -- ^ byte to fill with - -> m () + :: PrimMonad m + => MutableByteArray (PrimState m) -- ^ array to fill + -> Int -- ^ offset into array + -> Int -- ^ number of bytes to fill + -> Word8 -- ^ byte to fill with + -> m () {-# INLINE fillByteArray #-} fillByteArray = setByteArray foreign import ccall unsafe "primitive-memops.h hsprimitive_memmove" - memmove_mba :: MutableByteArray# s -> CInt - -> MutableByteArray# s -> CInt + memmove_mba :: MutableByteArray# s -> CPtrdiff + -> MutableByteArray# s -> CPtrdiff -> CSize -> IO () -instance Data ByteArray where - toConstr _ = error "toConstr" - gunfold _ _ = error "gunfold" - dataTypeOf _ = mkNoRepType "Data.Primitive.ByteArray.ByteArray" - -instance Typeable s => Data (MutableByteArray s) where - toConstr _ = error "toConstr" - gunfold _ _ = error "gunfold" - dataTypeOf _ = mkNoRepType "Data.Primitive.ByteArray.MutableByteArray" - --- | @since 0.6.3.0 -instance Show ByteArray where - showsPrec _ ba = - showString "[" . go 0 - where - go i - | i < sizeofByteArray ba = comma . showString "0x" . showHex (indexByteArray ba i :: Word8) . go (i+1) - | otherwise = showChar ']' - where - comma | i == 0 = id - | otherwise = showString ", " - - -compareByteArrays :: ByteArray -> ByteArray -> Int -> Ordering +-- | Lexicographic comparison of equal-length slices into two byte arrays. +-- This wraps the @compareByteArrays#@ primop, which wraps @memcmp@. +compareByteArrays + :: ByteArray -- ^ array A + -> Int -- ^ offset A, given in bytes + -> ByteArray -- ^ array B + -> Int -- ^ offset B, given in bytes + -> Int -- ^ length of the slice, given in bytes + -> Ordering {-# INLINE compareByteArrays #-} #if __GLASGOW_HASKELL__ >= 804 -compareByteArrays (ByteArray ba1#) (ByteArray ba2#) (I# n#) = - compare (I# (compareByteArrays# ba1# 0# ba2# 0# n#)) 0 +compareByteArrays (ByteArray ba1#) (I# off1#) (ByteArray ba2#) (I# off2#) (I# n#) + = compare (I# (compareByteArrays# ba1# off1# ba2# off2# n#)) 0 #else -- Emulate GHC 8.4's 'GHC.Prim.compareByteArrays#' -compareByteArrays (ByteArray ba1#) (ByteArray ba2#) (I# n#) - = compare (fromCInt (unsafeDupablePerformIO (memcmp_ba ba1# ba2# n))) 0 +compareByteArrays (ByteArray ba1#) (I# off1#) (ByteArray ba2#) (I# off2#) (I# n#) + = compare (fromCInt (unsafeDupablePerformIO (memcmp_ba_offs ba1# off1# ba2# off2# n))) 0 where n = fromIntegral (I# n#) :: CSize fromCInt = fromIntegral :: CInt -> Int -foreign import ccall unsafe "primitive-memops.h hsprimitive_memcmp" - memcmp_ba :: ByteArray# -> ByteArray# -> CSize -> IO CInt +foreign import ccall unsafe "primitive-memops.h hsprimitive_memcmp_offset" + memcmp_ba_offs :: ByteArray# -> Int# -> ByteArray# -> Int# -> CSize -> IO CInt #endif - -sameByteArray :: ByteArray# -> ByteArray# -> Bool -sameByteArray ba1 ba2 = - case reallyUnsafePtrEquality# (unsafeCoerce# ba1 :: ()) (unsafeCoerce# ba2 :: ()) of -#if __GLASGOW_HASKELL__ >= 708 - r -> isTrue# r -#else - 1# -> True - 0# -> False -#endif - --- | @since 0.6.3.0 -instance Eq ByteArray where - ba1@(ByteArray ba1#) == ba2@(ByteArray ba2#) - | sameByteArray ba1# ba2# = True - | n1 /= n2 = False - | otherwise = compareByteArrays ba1 ba2 n1 == EQ - where - n1 = sizeofByteArray ba1 - n2 = sizeofByteArray ba2 - --- | Non-lexicographic ordering. This compares the lengths of --- the byte arrays first and uses a lexicographic ordering if --- the lengths are equal. Subject to change between major versions. --- --- @since 0.6.3.0 -instance Ord ByteArray where - ba1@(ByteArray ba1#) `compare` ba2@(ByteArray ba2#) - | sameByteArray ba1# ba2# = EQ - | n1 /= n2 = n1 `compare` n2 - | otherwise = compareByteArrays ba1 ba2 n1 - where - n1 = sizeofByteArray ba1 - n2 = sizeofByteArray ba2 --- Note: On GHC 8.4, the primop compareByteArrays# performs a check for pointer --- equality as a shortcut, so the check here is actually redundant. However, it --- is included here because it is likely better to check for pointer equality --- before checking for length equality. Getting the length requires deferencing --- the pointers, which could cause accesses to memory that is not in the cache. --- By contrast, a pointer equality check is always extremely cheap. - -appendByteArray :: ByteArray -> ByteArray -> ByteArray -appendByteArray a b = runST $ do - marr <- newByteArray (sizeofByteArray a + sizeofByteArray b) - copyByteArray marr 0 a 0 (sizeofByteArray a) - copyByteArray marr (sizeofByteArray a) b 0 (sizeofByteArray b) - unsafeFreezeByteArray marr - -concatByteArray :: [ByteArray] -> ByteArray -concatByteArray arrs = runST $ do - let len = calcLength arrs 0 - marr <- newByteArray len - pasteByteArrays marr 0 arrs - unsafeFreezeByteArray marr - -pasteByteArrays :: MutableByteArray s -> Int -> [ByteArray] -> ST s () -pasteByteArrays !_ !_ [] = return () -pasteByteArrays !marr !ix (x : xs) = do - copyByteArray marr ix x 0 (sizeofByteArray x) - pasteByteArrays marr (ix + sizeofByteArray x) xs - -calcLength :: [ByteArray] -> Int -> Int -calcLength [] !n = n -calcLength (x : xs) !n = calcLength xs (sizeofByteArray x + n) - +-- | The empty 'ByteArray'. emptyByteArray :: ByteArray +{-# NOINLINE emptyByteArray #-} emptyByteArray = runST (newByteArray 0 >>= unsafeFreezeByteArray) -replicateByteArray :: Int -> ByteArray -> ByteArray -replicateByteArray n arr = runST $ do - marr <- newByteArray (n * sizeofByteArray arr) - let go i = if i < n - then do - copyByteArray marr (i * sizeofByteArray arr) arr 0 (sizeofByteArray arr) - go (i + 1) - else return () - go 0 - unsafeFreezeByteArray marr - -#if MIN_VERSION_base(4,9,0) -instance SG.Semigroup ByteArray where - (<>) = appendByteArray - sconcat = mconcat . F.toList - stimes i arr - | itgr < 1 = emptyByteArray - | itgr <= (fromIntegral (maxBound :: Int)) = replicateByteArray (fromIntegral itgr) arr - | otherwise = error "Data.Primitive.ByteArray#stimes: cannot allocate the requested amount of memory" - where itgr = toInteger i :: Integer -#endif - -instance Monoid ByteArray where - mempty = emptyByteArray -#if !(MIN_VERSION_base(4,11,0)) - mappend = appendByteArray -#endif - mconcat = concatByteArray +die :: String -> String -> a +die fun problem = error $ "Data.Primitive.ByteArray." ++ fun ++ ": " ++ problem -#if __GLASGOW_HASKELL__ >= 708 --- | @since 0.6.3.0 -instance Exts.IsList ByteArray where - type Item ByteArray = Word8 +-- | Return a newly allocated array with the specified subrange of the +-- provided array. The provided array should contain the full subrange +-- specified by the two Ints, but this is not checked. +cloneByteArray + :: ByteArray -- ^ source array + -> Int -- ^ offset into destination array + -> Int -- ^ number of bytes to copy + -> ByteArray +{-# INLINE cloneByteArray #-} +cloneByteArray src off n = runByteArray $ do + dst <- newByteArray n + copyByteArray dst 0 src off n + return dst + +-- | Return a newly allocated mutable array with the specified subrange of +-- the provided mutable array. The provided mutable array should contain the +-- full subrange specified by the two Ints, but this is not checked. +cloneMutableByteArray :: PrimMonad m + => MutableByteArray (PrimState m) -- ^ source array + -> Int -- ^ offset into destination array + -> Int -- ^ number of bytes to copy + -> m (MutableByteArray (PrimState m)) +{-# INLINE cloneMutableByteArray #-} +cloneMutableByteArray src off n = do + dst <- newByteArray n + copyMutableByteArray dst 0 src off n + return dst - toList = foldrByteArray (:) [] - fromList xs = byteArrayFromListN (length xs) xs - fromListN = byteArrayFromListN +-- | Execute the monadic action and freeze the resulting array. +-- +-- > runByteArray m = runST $ m >>= unsafeFreezeByteArray +runByteArray + :: (forall s. ST s (MutableByteArray s)) + -> ByteArray +#if MIN_VERSION_base(4,10,0) /* In new GHCs, runRW# is available. */ +runByteArray m = ByteArray (runByteArray# m) + +runByteArray# + :: (forall s. ST s (MutableByteArray s)) + -> ByteArray# +runByteArray# m = case runRW# $ \s -> + case unST m s of { (# s', MutableByteArray mary# #) -> + unsafeFreezeByteArray# mary# s'} of (# _, ary# #) -> ary# + +unST :: ST s a -> State# s -> (# State# s, a #) +unST (GHCST.ST f) = f +#else /* In older GHCs, runRW# is not available. */ +runByteArray m = runST $ m >>= unsafeFreezeByteArray #endif -die :: String -> String -> a -die fun problem = error $ "Data.Primitive.ByteArray." ++ fun ++ ": " ++ problem +{- $charElementAccess +GHC provides two sets of element accessors for 'Char'. One set faithfully +represents 'Char' as 32-bit words using UTF-32. The other set represents +'Char' as 8-bit words using Latin-1 (ISO-8859-1), and the write operation +has undefined behavior for codepoints outside of the ASCII and Latin-1 +blocks. The 'Prim' instance for 'Char' uses the UTF-32 set of operators. +-} +-- | Read an 8-bit element from the byte array, interpreting it as a +-- Latin-1-encoded character. The offset is given in bytes. +-- +-- /Note:/ this function does not do bounds checking. +readCharArray :: PrimMonad m => MutableByteArray (PrimState m) -> Int -> m Char +{-# INLINE readCharArray #-} +readCharArray (MutableByteArray arr#) (I# i#) = primitive + (\s0 -> case readCharArray# arr# i# s0 of + (# s1, c #) -> (# s1, C# c #) + ) + +-- | Write a character to the byte array, encoding it with Latin-1 as +-- a single byte. Behavior is undefined for codepoints outside of the +-- ASCII and Latin-1 blocks. The offset is given in bytes. +-- +-- /Note:/ this function does not do bounds checking. +writeCharArray + :: PrimMonad m => MutableByteArray (PrimState m) -> Int -> Char -> m () +{-# INLINE writeCharArray #-} +writeCharArray (MutableByteArray arr#) (I# i#) (C# c) + = primitive_ (writeCharArray# arr# i# c) + +-- | Read an 8-bit element from the byte array, interpreting it as a +-- Latin-1-encoded character. The offset is given in bytes. +-- +-- /Note:/ this function does not do bounds checking. +indexCharArray :: ByteArray -> Int -> Char +{-# INLINE indexCharArray #-} +indexCharArray (ByteArray arr#) (I# i#) = C# (indexCharArray# arr# i#) diff --git a/examples/primitive/Data/Primitive/Internal/Compat.hs b/examples/primitive/Data/Primitive/Internal/Compat.hs deleted file mode 100644 index f6b8016ad..000000000 --- a/examples/primitive/Data/Primitive/Internal/Compat.hs +++ /dev/null @@ -1,38 +0,0 @@ -{-# LANGUAGE CPP, MagicHash #-} - --- | --- Module : Data.Primitive.Internal.Compat --- Copyright : (c) Roman Leshchinskiy 2011-2012 --- License : BSD-style --- --- Maintainer : Roman Leshchinskiy --- Portability : non-portable --- --- Compatibility functions --- - -module Data.Primitive.Internal.Compat ( - isTrue# - , mkNoRepType - ) where - -#if MIN_VERSION_base(4,2,0) -import Data.Data (mkNoRepType) -#else -import Data.Data (mkNorepType) -#endif - -#if MIN_VERSION_base(4,7,0) -import GHC.Exts (isTrue#) -#endif - - - -#if !MIN_VERSION_base(4,2,0) -mkNoRepType = mkNorepType -#endif - -#if !MIN_VERSION_base(4,7,0) -isTrue# :: Bool -> Bool -isTrue# b = b -#endif diff --git a/examples/primitive/Data/Primitive/Internal/Operations.hs b/examples/primitive/Data/Primitive/Internal/Operations.hs index 20a7cd99c..626e9cc47 100644 --- a/examples/primitive/Data/Primitive/Internal/Operations.hs +++ b/examples/primitive/Data/Primitive/Internal/Operations.hs @@ -1,4 +1,9 @@ -{-# LANGUAGE MagicHash, UnliftedFFITypes #-} +{-# LANGUAGE CPP, MagicHash, UnliftedFFITypes, UnboxedTuples #-} +{-# LANGUAGE RankNTypes, KindSignatures, ScopedTypeVariables #-} +{-# LANGUAGE DataKinds #-} +#if __GLASGOW_HASKELL__ < 806 +{-# LANGUAGE TypeInType #-} +#endif -- | -- Module : Data.Primitive.Internal.Operations @@ -8,9 +13,7 @@ -- Maintainer : Roman Leshchinskiy -- Portability : non-portable -- --- Internal operations --- - +-- Internal operations. module Data.Primitive.Internal.Operations ( setWord8Array#, setWord16Array#, setWord32Array#, @@ -26,32 +29,67 @@ module Data.Primitive.Internal.Operations ( setInt64OffAddr#, setIntOffAddr#, setAddrOffAddr#, setFloatOffAddr#, setDoubleOffAddr#, setWideCharOffAddr#, setStablePtrOffAddr# + + +#if defined(HAVE_KEEPALIVE) + , keepAliveLiftedLifted# + , keepAliveUnliftedLifted# +#endif + , mutableByteArrayContentsShim + , UnliftedType ) where import Data.Primitive.MachDeps (Word64_#, Int64_#) import Foreign.C.Types import GHC.Exts +#if defined(HAVE_KEEPALIVE) +import Data.Kind (Type) +#endif + + +#if __GLASGOW_HASKELL__ >= 902 foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word8" setWord8Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Word8# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word16" setWord16Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Word16# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word32" setWord32Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Word32# -> IO () +#else +foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word8" + setWord8Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Word# -> IO () +foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word16" + setWord16Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Word# -> IO () +foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word32" + setWord32Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Word# -> IO () +#endif + foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word64" setWord64Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Word64_# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word" setWordArray# :: MutableByteArray# s -> CPtrdiff -> CSize -> Word# -> IO () + +#if __GLASGOW_HASKELL__ >= 902 foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word8" setInt8Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Int8# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word16" setInt16Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Int16# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word32" setInt32Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Int32# -> IO () +#else +foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word8" + setInt8Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Int# -> IO () +foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word16" + setInt16Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Int# -> IO () +foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word32" + setInt32Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Int# -> IO () +#endif + foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word64" setInt64Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Int64_# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word" setIntArray# :: MutableByteArray# s -> CPtrdiff -> CSize -> Int# -> IO () + foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Ptr" setAddrArray# :: MutableByteArray# s -> CPtrdiff -> CSize -> Addr# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Ptr" @@ -63,26 +101,48 @@ foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Double" foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Char" setWideCharArray# :: MutableByteArray# s -> CPtrdiff -> CSize -> Char# -> IO () +#if __GLASGOW_HASKELL__ >= 902 foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word8" setWord8OffAddr# :: Addr# -> CPtrdiff -> CSize -> Word8# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word16" setWord16OffAddr# :: Addr# -> CPtrdiff -> CSize -> Word16# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word32" setWord32OffAddr# :: Addr# -> CPtrdiff -> CSize -> Word32# -> IO () +#else +foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word8" + setWord8OffAddr# :: Addr# -> CPtrdiff -> CSize -> Word# -> IO () +foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word16" + setWord16OffAddr# :: Addr# -> CPtrdiff -> CSize -> Word# -> IO () +foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word32" + setWord32OffAddr# :: Addr# -> CPtrdiff -> CSize -> Word# -> IO () +#endif + foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word64" setWord64OffAddr# :: Addr# -> CPtrdiff -> CSize -> Word64_# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word" setWordOffAddr# :: Addr# -> CPtrdiff -> CSize -> Word# -> IO () + +#if __GLASGOW_HASKELL__ >= 902 foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word8" setInt8OffAddr# :: Addr# -> CPtrdiff -> CSize -> Int8# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word16" setInt16OffAddr# :: Addr# -> CPtrdiff -> CSize -> Int16# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word32" setInt32OffAddr# :: Addr# -> CPtrdiff -> CSize -> Int32# -> IO () +#else +foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word8" + setInt8OffAddr# :: Addr# -> CPtrdiff -> CSize -> Int# -> IO () +foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word16" + setInt16OffAddr# :: Addr# -> CPtrdiff -> CSize -> Int# -> IO () +foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word32" + setInt32OffAddr# :: Addr# -> CPtrdiff -> CSize -> Int# -> IO () +#endif + foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word64" setInt64OffAddr# :: Addr# -> CPtrdiff -> CSize -> Int64_# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word" setIntOffAddr# :: Addr# -> CPtrdiff -> CSize -> Int# -> IO () + foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Ptr" setAddrOffAddr# :: Addr# -> CPtrdiff -> CSize -> Addr# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Ptr" @@ -93,3 +153,53 @@ foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Double" setDoubleOffAddr# :: Addr# -> CPtrdiff -> CSize -> Double# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Char" setWideCharOffAddr# :: Addr# -> CPtrdiff -> CSize -> Char# -> IO () + +#if defined(HAVE_KEEPALIVE) +keepAliveLiftedLifted# :: forall (s :: Type) (a :: Type) (b :: Type). + a + -> State# s + -> (State# s -> (# State# s, b #)) + -> (# State# s, b #) +{-# inline keepAliveLiftedLifted# #-} +keepAliveLiftedLifted# x s0 f = + (unsafeCoerce# :: (# State# RealWorld, b #) -> (# State# s, b #)) + ( keepAlive# x + ((unsafeCoerce# :: State# s -> State# RealWorld) s0) + ((unsafeCoerce# :: + (State# s -> (# State# s, b #)) -> + (State# RealWorld -> (# State# RealWorld, b #)) + ) f) + ) + +keepAliveUnliftedLifted# :: forall (s :: Type) (a :: UnliftedType) (b :: Type). + a + -> State# s + -> (State# s -> (# State# s, b #)) + -> (# State# s, b #) +{-# inline keepAliveUnliftedLifted# #-} +keepAliveUnliftedLifted# x s0 f = + (unsafeCoerce# :: (# State# RealWorld, b #) -> (# State# s, b #)) + ( keepAlive# x + ((unsafeCoerce# :: State# s -> State# RealWorld) s0) + ((unsafeCoerce# :: + (State# s -> (# State# s, b #)) -> + (State# RealWorld -> (# State# RealWorld, b #)) + ) f) + ) +#endif + +#if __GLASGOW_HASKELL__ < 802 +type UnliftedType = TYPE 'PtrRepUnlifted +#elif __GLASGOW_HASKELL__ < 902 +type UnliftedType = TYPE 'UnliftedRep +#endif + +mutableByteArrayContentsShim :: MutableByteArray# s -> Addr# +{-# INLINE mutableByteArrayContentsShim #-} +mutableByteArrayContentsShim x = +#if __GLASGOW_HASKELL__ >= 902 + mutableByteArrayContents# x +#else + byteArrayContents# (unsafeCoerce# x) +#endif + diff --git a/examples/primitive/Data/Primitive/Internal/Read.hs b/examples/primitive/Data/Primitive/Internal/Read.hs new file mode 100644 index 000000000..5ec13282c --- /dev/null +++ b/examples/primitive/Data/Primitive/Internal/Read.hs @@ -0,0 +1,27 @@ +module Data.Primitive.Internal.Read + ( Tag(..) + , lexTag + ) where + +import Data.Char (isDigit) +import Text.ParserCombinators.ReadP + +data Tag = FromListTag | FromListNTag + +-- Why don't we just use lexP? The general problem with lexP is that +-- it doesn't always fail as fast as we might like. It will +-- happily read to the end of an absurdly long lexeme (e.g., a 200MB string +-- literal) before returning, at which point we'll immediately discard +-- the result because it's not an identifier. Doing the job ourselves, we +-- can see very quickly when we've run into a problem. We should also get +-- a slight efficiency boost by going through the string just once. +lexTag :: ReadP Tag +lexTag = do + _ <- string "fromList" + s <- look + case s of + 'N':c:_ + | isDigit c + -> fail "" -- We have fromListN3 or similar + | otherwise -> FromListNTag <$ get -- Skip the 'N' + _ -> return FromListTag diff --git a/examples/primitive/Data/Primitive/MVar.hs b/examples/primitive/Data/Primitive/MVar.hs index 3c7bfd1fa..b1300d1fe 100644 --- a/examples/primitive/Data/Primitive/MVar.hs +++ b/examples/primitive/Data/Primitive/MVar.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} @@ -8,14 +7,17 @@ -- License : BSD2 -- Portability : non-portable -- --- Primitive operations on @MVar@. This module provides a similar interface +-- Primitive operations on 'MVar'. This module provides a similar interface -- to "Control.Concurrent.MVar". However, the functions are generalized to -- work in any 'PrimMonad' instead of only working in 'IO'. Note that all -- of the functions here are completely deterministic. Users of 'MVar' are -- responsible for designing abstractions that guarantee determinism in -- the presence of multi-threading. -- +-- For a more detailed explanation, see "Control.Concurrent.MVar". +-- -- @since 0.6.4.0 + module Data.Primitive.MVar ( MVar(..) , newMVar @@ -30,14 +32,12 @@ module Data.Primitive.MVar ) where import Control.Monad.Primitive -import Data.Primitive.Internal.Compat (isTrue#) -import GHC.Exts (MVar#,newMVar#,takeMVar#,sameMVar#,putMVar#,tryTakeMVar#, - isEmptyMVar#,tryPutMVar#,(/=#)) - -#if __GLASGOW_HASKELL__ >= 708 -import GHC.Exts (readMVar#,tryReadMVar#) -#endif +import GHC.Exts + ( MVar#, newMVar#, takeMVar#, sameMVar#, putMVar#, tryTakeMVar#, isEmptyMVar#, tryPutMVar#, (/=#) + , readMVar#, tryReadMVar#, isTrue# ) +-- | A synchronizing variable, used for communication between concurrent threads. +-- It can be thought of as a box, which may be empty or full. data MVar s a = MVar (MVar# s a) instance Eq (MVar s a) where @@ -49,54 +49,62 @@ newEmptyMVar = primitive $ \ s# -> case newMVar# s# of (# s2#, svar# #) -> (# s2#, MVar svar# #) - -- | Create a new 'MVar' that holds the supplied argument. newMVar :: PrimMonad m => a -> m (MVar (PrimState m) a) -newMVar value = - newEmptyMVar >>= \ mvar -> - putMVar mvar value >> +newMVar value = do + mvar <- newEmptyMVar + putMVar mvar value return mvar --- | Return the contents of the 'MVar'. If the 'MVar' is currently --- empty, 'takeMVar' will wait until it is full. After a 'takeMVar', +-- | Return the contents of the 'MVar'. If the 'MVar' is currently +-- empty, 'takeMVar' will wait until it is full. After a 'takeMVar', -- the 'MVar' is left empty. +-- +-- There are two further important properties of 'takeMVar': +-- +-- * 'takeMVar' is single-wakeup. That is, if there are multiple +-- threads blocked in 'takeMVar', and the 'MVar' becomes full, +-- only one thread will be woken up. The runtime guarantees that +-- the woken thread completes its 'takeMVar' operation. +-- * When multiple threads are blocked on an 'MVar', they are +-- woken up in FIFO order. This is useful for providing +-- fairness properties of abstractions built using 'MVar's. takeMVar :: PrimMonad m => MVar (PrimState m) a -> m a takeMVar (MVar mvar#) = primitive $ \ s# -> takeMVar# mvar# s# --- | Atomically read the contents of an 'MVar'. If the 'MVar' is +-- | Atomically read the contents of an 'MVar'. If the 'MVar' is -- currently empty, 'readMVar' will wait until it is full. -- 'readMVar' is guaranteed to receive the next 'putMVar'. -- -- /Multiple Wakeup:/ 'readMVar' is multiple-wakeup, so when multiple readers -- are blocked on an 'MVar', all of them are woken up at the same time. -- --- /Compatibility note:/ On GHCs prior to 7.8, 'readMVar' is a combination --- of 'takeMVar' and 'putMVar'. Consequently, its behavior differs in the --- following ways: --- -- * It is single-wakeup instead of multiple-wakeup. -- * It might not receive the value from the next call to 'putMVar' if -- there is already a pending thread blocked on 'takeMVar'. -- * If another thread puts a value in the 'MVar' in between the -- calls to 'takeMVar' and 'putMVar', that value may be overridden. readMVar :: PrimMonad m => MVar (PrimState m) a -> m a -#if __GLASGOW_HASKELL__ >= 708 readMVar (MVar mvar#) = primitive $ \ s# -> readMVar# mvar# s# -#else -readMVar mv = do - a <- takeMVar mv - putMVar mv a - return a -#endif --- |Put a value into an 'MVar'. If the 'MVar' is currently full, +-- | Put a value into an 'MVar'. If the 'MVar' is currently full, -- 'putMVar' will wait until it becomes empty. +-- +-- There are two further important properties of 'putMVar': +-- +-- * 'putMVar' is single-wakeup. That is, if there are multiple +-- threads blocked in 'putMVar', and the 'MVar' becomes empty, +-- only one thread will be woken up. The runtime guarantees that +-- the woken thread completes its 'putMVar' operation. +-- * When multiple threads are blocked on an 'MVar', they are +-- woken up in FIFO order. This is useful for providing +-- fairness properties of abstractions built using 'MVar's. putMVar :: PrimMonad m => MVar (PrimState m) a -> a -> m () putMVar (MVar mvar#) x = primitive_ (putMVar# mvar# x) --- |A non-blocking version of 'takeMVar'. The 'tryTakeMVar' function +-- | A non-blocking version of 'takeMVar'. The 'tryTakeMVar' function -- returns immediately, with 'Nothing' if the 'MVar' was empty, or --- @'Just' a@ if the 'MVar' was full with contents @a@. After 'tryTakeMVar', +-- @'Just' a@ if the 'MVar' was full with contents @a@. After 'tryTakeMVar', -- the 'MVar' is left empty. tryTakeMVar :: PrimMonad m => MVar (PrimState m) a -> m (Maybe a) tryTakeMVar (MVar m) = primitive $ \ s -> @@ -104,8 +112,7 @@ tryTakeMVar (MVar m) = primitive $ \ s -> (# s', 0#, _ #) -> (# s', Nothing #) -- MVar is empty (# s', _, a #) -> (# s', Just a #) -- MVar is full - --- |A non-blocking version of 'putMVar'. The 'tryPutMVar' function +-- | A non-blocking version of 'putMVar'. The 'tryPutMVar' function -- attempts to put the value @a@ into the 'MVar', returning 'True' if -- it was successful, or 'False' otherwise. tryPutMVar :: PrimMonad m => MVar (PrimState m) a -> a -> m Bool @@ -114,41 +121,27 @@ tryPutMVar (MVar mvar#) x = primitive $ \ s# -> (# s, 0# #) -> (# s, False #) (# s, _ #) -> (# s, True #) --- | A non-blocking version of 'readMVar'. The 'tryReadMVar' function +-- | A non-blocking version of 'readMVar'. The 'tryReadMVar' function -- returns immediately, with 'Nothing' if the 'MVar' was empty, or -- @'Just' a@ if the 'MVar' was full with contents @a@. -- --- /Compatibility note:/ On GHCs prior to 7.8, 'tryReadMVar' is a combination --- of 'tryTakeMVar' and 'putMVar'. Consequently, its behavior differs in the --- following ways: --- -- * It is single-wakeup instead of multiple-wakeup. -- * In the presence of other threads calling 'putMVar', 'tryReadMVar' -- may block. -- * If another thread puts a value in the 'MVar' in between the -- calls to 'tryTakeMVar' and 'putMVar', that value may be overridden. tryReadMVar :: PrimMonad m => MVar (PrimState m) a -> m (Maybe a) -#if __GLASGOW_HASKELL__ >= 708 tryReadMVar (MVar m) = primitive $ \ s -> case tryReadMVar# m s of (# s', 0#, _ #) -> (# s', Nothing #) -- MVar is empty (# s', _, a #) -> (# s', Just a #) -- MVar is full -#else -tryReadMVar mv = do - ma <- tryTakeMVar mv - case ma of - Just a -> do - putMVar mv a - return (Just a) - Nothing -> return Nothing -#endif -- | Check whether a given 'MVar' is empty. -- --- Notice that the boolean value returned is just a snapshot of --- the state of the MVar. By the time you get to react on its result, --- the MVar may have been filled (or emptied) - so be extremely --- careful when using this operation. Use 'tryTakeMVar' instead if possible. +-- Notice that the boolean value returned is just a snapshot of +-- the state of the 'MVar'. By the time you get to react on its result, +-- the 'MVar' may have been filled (or emptied) - so be extremely +-- careful when using this operation. Use 'tryTakeMVar' instead if possible. isEmptyMVar :: PrimMonad m => MVar (PrimState m) a -> m Bool isEmptyMVar (MVar mv#) = primitive $ \ s# -> case isEmptyMVar# mv# s# of diff --git a/examples/primitive/Data/Primitive/MachDeps.hs b/examples/primitive/Data/Primitive/MachDeps.hs index bdf857bda..21d3db40a 100644 --- a/examples/primitive/Data/Primitive/MachDeps.hs +++ b/examples/primitive/Data/Primitive/MachDeps.hs @@ -1,4 +1,5 @@ {-# LANGUAGE CPP, MagicHash #-} + -- | -- Module : Data.Primitive.MachDeps -- Copyright : (c) Roman Leshchinskiy 2009-2012 @@ -7,8 +8,7 @@ -- Maintainer : Roman Leshchinskiy -- Portability : non-portable -- --- Machine-dependent constants --- +-- Machine-dependent constants. module Data.Primitive.MachDeps where @@ -113,11 +113,10 @@ aLIGNMENT_INT64 = ALIGNMENT_INT64 sIZEOF_WORD64 = SIZEOF_WORD64 aLIGNMENT_WORD64 = ALIGNMENT_WORD64 -#if WORD_SIZE_IN_BITS == 32 +#if WORD_SIZE_IN_BITS == 32 || __GLASGOW_HASKELL__ >= 903 type Word64_# = Word64# type Int64_# = Int64# #else type Word64_# = Word# type Int64_# = Int# #endif - diff --git a/examples/primitive/Data/Primitive/MutVar.hs b/examples/primitive/Data/Primitive/MutVar.hs index 85e728323..2578bc6d1 100644 --- a/examples/primitive/Data/Primitive/MutVar.hs +++ b/examples/primitive/Data/Primitive/MutVar.hs @@ -8,8 +8,9 @@ -- Maintainer : Roman Leshchinskiy -- Portability : non-portable -- --- Primitive boxed mutable variables --- +-- Primitive boxed mutable variables. This is a generalization of +-- "Data.IORef", "Data.STRef" and "Data.STRef.Lazy" to work in +-- any 'PrimMonad'. module Data.Primitive.MutVar ( MutVar(..), @@ -25,9 +26,9 @@ module Data.Primitive.MutVar ( ) where import Control.Monad.Primitive ( PrimMonad(..), primitive_ ) -import GHC.Exts ( MutVar#, sameMutVar#, newMutVar#, - readMutVar#, writeMutVar#, atomicModifyMutVar# ) -import Data.Primitive.Internal.Compat ( isTrue# ) +import GHC.Exts ( MutVar#, sameMutVar#, newMutVar# + , readMutVar#, writeMutVar#, atomicModifyMutVar# + , isTrue# ) import Data.Typeable ( Typeable ) -- | A 'MutVar' behaves like a single-element mutable array associated @@ -38,25 +39,38 @@ data MutVar s a = MutVar (MutVar# s a) instance Eq (MutVar s a) where MutVar mva# == MutVar mvb# = isTrue# (sameMutVar# mva# mvb#) --- | Create a new 'MutVar' with the specified initial value +-- | Create a new 'MutVar' with the specified initial value. newMutVar :: PrimMonad m => a -> m (MutVar (PrimState m) a) {-# INLINE newMutVar #-} newMutVar initialValue = primitive $ \s# -> case newMutVar# initialValue s# of (# s'#, mv# #) -> (# s'#, MutVar mv# #) --- | Read the value of a 'MutVar' +-- | Read the value of a 'MutVar'. readMutVar :: PrimMonad m => MutVar (PrimState m) a -> m a {-# INLINE readMutVar #-} readMutVar (MutVar mv#) = primitive (readMutVar# mv#) --- | Write a new value into a 'MutVar' +-- | Write a new value into a 'MutVar'. writeMutVar :: PrimMonad m => MutVar (PrimState m) a -> a -> m () {-# INLINE writeMutVar #-} writeMutVar (MutVar mv#) newValue = primitive_ (writeMutVar# mv# newValue) --- | Atomically mutate the contents of a 'MutVar' -atomicModifyMutVar :: PrimMonad m => MutVar (PrimState m) a -> (a -> (a,b)) -> m b +-- | Atomically mutate the contents of a 'MutVar'. +-- +-- This function is useful for using 'MutVar' in a safe way in a multithreaded program. +-- If you only have one 'MutVar', then using 'atomicModifyMutVar' to access and modify +-- it will prevent race conditions. +-- +-- Extending the atomicity to multiple 'MutVar's is problematic, +-- so if you need to do anything more complicated, +-- using 'Data.Primitive.MVar.MVar' instead is a good idea. +-- +-- 'atomicModifyMutVar' does not apply the function strictly. This means if a program +-- calls 'atomicModifyMutVar' many times, but seldom uses the value, thunks will pile up +-- in memory resulting in a space leak. +-- To avoid this problem, use 'atomicModifyMutVar'' instead. +atomicModifyMutVar :: PrimMonad m => MutVar (PrimState m) a -> (a -> (a, b)) -> m b {-# INLINE atomicModifyMutVar #-} atomicModifyMutVar (MutVar mv#) f = primitive $ atomicModifyMutVar# mv# f @@ -69,16 +83,21 @@ atomicModifyMutVar' mv f = do b `seq` return b where force x = case f x of - v@(x',_) -> x' `seq` v + v@(x', _) -> x' `seq` v --- | Mutate the contents of a 'MutVar' +-- | Mutate the contents of a 'MutVar'. +-- +-- 'modifyMutVar' does not apply the function strictly. This means if a program +-- calls 'modifyMutVar' many times, but seldom uses the value, thunks will pile up +-- in memory resulting in a space leak. +-- To avoid this problem, use 'modifyMutVar'' instead. modifyMutVar :: PrimMonad m => MutVar (PrimState m) a -> (a -> a) -> m () {-# INLINE modifyMutVar #-} modifyMutVar (MutVar mv#) g = primitive_ $ \s# -> case readMutVar# mv# s# of (# s'#, a #) -> writeMutVar# mv# (g a) s'# --- | Strict version of 'modifyMutVar' +-- | Strict version of 'modifyMutVar'. modifyMutVar' :: PrimMonad m => MutVar (PrimState m) a -> (a -> a) -> m () {-# INLINE modifyMutVar' #-} modifyMutVar' (MutVar mv#) g = primitive_ $ \s# -> diff --git a/examples/primitive/Data/Primitive/PrimArray.hs b/examples/primitive/Data/Primitive/PrimArray.hs index a99d605b4..c8c671bad 100644 --- a/examples/primitive/Data/Primitive/PrimArray.hs +++ b/examples/primitive/Data/Primitive/PrimArray.hs @@ -4,8 +4,10 @@ {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeApplications #-} {-# LANGUAGE UnboxedTuples #-} - +{-# LANGUAGE TemplateHaskellQuotes #-} +{-# LANGUAGE RoleAnnotations #-} -- | -- Module : Data.Primitive.PrimArray @@ -15,46 +17,59 @@ -- Maintainer : Roman Leshchinskiy -- Portability : non-portable -- --- Arrays of unboxed primitive types. The function provided by this module --- match the behavior of those provided by @Data.Primitive.ByteArray@, and +-- Arrays of unboxed primitive types. The functions provided by this module +-- match the behavior of those provided by "Data.Primitive.ByteArray", and -- the underlying types and primops that back them are the same. -- However, the type constructors 'PrimArray' and 'MutablePrimArray' take one additional --- argument than their respective counterparts 'ByteArray' and 'MutableByteArray'. +-- argument compared to their respective counterparts 'ByteArray' and 'Data.Primitive.ByteArray.MutableByteArray'. -- This argument is used to designate the type of element in the array. --- Consequently, all function this modules accepts length and incides in +-- Consequently, all functions in this module accept length and indices in -- terms of elements, not bytes. -- -- @since 0.6.4.0 + module Data.Primitive.PrimArray ( -- * Types PrimArray(..) , MutablePrimArray(..) -- * Allocation , newPrimArray + , newPinnedPrimArray + , newAlignedPinnedPrimArray , resizeMutablePrimArray -#if __GLASGOW_HASKELL__ >= 710 , shrinkMutablePrimArray -#endif -- * Element Access , readPrimArray , writePrimArray , indexPrimArray -- * Freezing and Thawing + , freezePrimArray + , thawPrimArray + , runPrimArray , unsafeFreezePrimArray , unsafeThawPrimArray -- * Block Operations , copyPrimArray , copyMutablePrimArray -#if __GLASGOW_HASKELL__ >= 708 , copyPrimArrayToPtr , copyMutablePrimArrayToPtr -#endif + , copyPtrToMutablePrimArray + , clonePrimArray + , cloneMutablePrimArray , setPrimArray -- * Information , sameMutablePrimArray , getSizeofMutablePrimArray , sizeofMutablePrimArray , sizeofPrimArray + , primArrayContents + , withPrimArrayContents + , mutablePrimArrayContents + , withMutablePrimArrayContents +#if __GLASGOW_HASKELL__ >= 802 + , isPrimArrayPinned + , isMutablePrimArrayPinned +#endif -- * List Conversion , primArrayToList , primArrayFromList @@ -69,6 +84,7 @@ module Data.Primitive.PrimArray , traversePrimArray_ , itraversePrimArray_ -- * Map/Create + , emptyPrimArray , mapPrimArray , imapPrimArray , generatePrimArray @@ -77,6 +93,7 @@ module Data.Primitive.PrimArray , mapMaybePrimArray -- * Effectful Map/Create -- $effectfulMapCreate + -- ** Lazy Applicative , traversePrimArray , itraversePrimArray @@ -94,59 +111,79 @@ module Data.Primitive.PrimArray ) where import GHC.Exts -import GHC.Base ( Int(..) ) -import Data.Primitive.Internal.Compat (isTrue#) import Data.Primitive.Types import Data.Primitive.ByteArray (ByteArray(..)) -import Data.Monoid (Monoid(..),(<>)) -import Control.Applicative +import Data.Proxy +#if !MIN_VERSION_base(4,18,0) +import Control.Applicative (liftA2) +#endif +import Control.DeepSeq +import Control.Monad (when) import Control.Monad.Primitive import Control.Monad.ST import qualified Data.List as L import qualified Data.Primitive.ByteArray as PB import qualified Data.Primitive.Types as PT - -#if MIN_VERSION_base(4,7,0) -import GHC.Exts (IsList(..)) +#if MIN_VERSION_base(4,10,0) +import qualified GHC.ST as GHCST #endif +import Language.Haskell.TH.Syntax (Lift (..)) + +import Data.Semigroup -#if MIN_VERSION_base(4,9,0) -import Data.Semigroup (Semigroup) -import qualified Data.Semigroup as SG +#if __GLASGOW_HASKELL__ >= 802 +import qualified GHC.Exts as Exts #endif +import Data.Primitive.Internal.Operations (mutableByteArrayContentsShim) + -- | Arrays of unboxed elements. This accepts types like 'Double', 'Char', --- 'Int', and 'Word', as well as their fixed-length variants ('Word8', +-- 'Int' and 'Word', as well as their fixed-length variants ('Word8', -- 'Word16', etc.). Since the elements are unboxed, a 'PrimArray' is strict --- in its elements. This differs from the behavior of 'Array', which is lazy --- in its elements. +-- in its elements. This differs from the behavior of 'Data.Primitive.Array.Array', +-- which is lazy in its elements. data PrimArray a = PrimArray ByteArray# +type role PrimArray nominal + +instance Lift (PrimArray a) where +#if MIN_VERSION_template_haskell(2,16,0) + liftTyped ary = [|| byteArrayToPrimArray ba ||] +#else + lift ary = [| byteArrayToPrimArray ba |] +#endif + where + ba = primArrayToByteArray ary + +instance NFData (PrimArray a) where + rnf (PrimArray _) = () + -- | Mutable primitive arrays associated with a primitive state token. -- These can be written to and read from in a monadic context that supports --- sequencing such as 'IO' or 'ST'. Typically, a mutable primitive array will --- be built and then convert to an immutable primitive array using +-- sequencing, such as 'IO' or 'ST'. Typically, a mutable primitive array will +-- be built and then converted to an immutable primitive array using -- 'unsafeFreezePrimArray'. However, it is also acceptable to simply discard -- a mutable primitive array since it lives in managed memory and will be -- garbage collected when no longer referenced. data MutablePrimArray s a = MutablePrimArray (MutableByteArray# s) +instance Eq (MutablePrimArray s a) where + (==) = sameMutablePrimArray + +instance NFData (MutablePrimArray s a) where + rnf (MutablePrimArray _) = () + sameByteArray :: ByteArray# -> ByteArray# -> Bool sameByteArray ba1 ba2 = case reallyUnsafePtrEquality# (unsafeCoerce# ba1 :: ()) (unsafeCoerce# ba2 :: ()) of -#if __GLASGOW_HASKELL__ >= 708 r -> isTrue# r -#else - 1# -> True - _ -> False -#endif -- | @since 0.6.4.0 instance (Eq a, Prim a) => Eq (PrimArray a) where a1@(PrimArray ba1#) == a2@(PrimArray ba2#) | sameByteArray ba1# ba2# = True | sz1 /= sz2 = False - | otherwise = loop (quot sz1 (sizeOf (undefined :: a)) - 1) + | otherwise = loop (quot sz1 (sizeOfType @a) - 1) where -- Here, we take the size in bytes, not in elements. We do this -- since it allows us to defer performing the division to @@ -155,12 +192,12 @@ instance (Eq a, Prim a) => Eq (PrimArray a) where sz2 = PB.sizeofByteArray (ByteArray ba2#) loop !i | i < 0 = True - | otherwise = indexPrimArray a1 i == indexPrimArray a2 i && loop (i-1) + | otherwise = indexPrimArray a1 i == indexPrimArray a2 i && loop (i - 1) {-# INLINE (==) #-} -- | Lexicographic ordering. Subject to change between major versions. -- --- @since 0.6.4.0 +-- @since 0.6.4.0 instance (Ord a, Prim a) => Ord (PrimArray a) where compare a1@(PrimArray ba1#) a2@(PrimArray ba2#) | sameByteArray ba1# ba2# = EQ @@ -168,33 +205,34 @@ instance (Ord a, Prim a) => Ord (PrimArray a) where where sz1 = PB.sizeofByteArray (ByteArray ba1#) sz2 = PB.sizeofByteArray (ByteArray ba2#) - sz = quot (min sz1 sz2) (sizeOf (undefined :: a)) + sz = quot (min sz1 sz2) (sizeOfType @a) loop !i - | i < sz = compare (indexPrimArray a1 i) (indexPrimArray a2 i) <> loop (i+1) + | i < sz = compare (indexPrimArray a1 i) (indexPrimArray a2 i) <> loop (i + 1) | otherwise = compare sz1 sz2 {-# INLINE compare #-} -#if MIN_VERSION_base(4,7,0) -- | @since 0.6.4.0 instance Prim a => IsList (PrimArray a) where type Item (PrimArray a) = a fromList = primArrayFromList fromListN = primArrayFromListN toList = primArrayToList -#endif -- | @since 0.6.4.0 instance (Show a, Prim a) => Show (PrimArray a) where - showsPrec p a = showParen (p > 10) $ - showString "fromListN " . shows (sizeofPrimArray a) . showString " " - . shows (primArrayToList a) + showsPrec _ a = shows (primArrayToList a) die :: String -> String -> a die fun problem = error $ "Data.Primitive.PrimArray." ++ fun ++ ": " ++ problem +-- | Create a 'PrimArray' from a list. +-- +-- @primArrayFromList vs = `primArrayFromListN` (length vs) vs@ primArrayFromList :: Prim a => [a] -> PrimArray a primArrayFromList vs = primArrayFromListN (L.length vs) vs +-- | Create a 'PrimArray' from a list of a known length. If the length +-- of the list does not match the given length, this throws an exception. primArrayFromListN :: forall a. Prim a => Int -> [a] -> PrimArray a primArrayFromListN len vs = runST run where run :: forall s. ST s (PrimArray a) @@ -212,7 +250,7 @@ primArrayFromListN len vs = runST run where go vs 0 unsafeFreezePrimArray arr --- | Convert the primitive array to a list. +-- | Convert a 'PrimArray' to a list. {-# INLINE primArrayToList #-} primArrayToList :: forall a. Prim a => PrimArray a -> [a] primArrayToList xs = build (\c n -> foldrPrimArray c n xs) @@ -223,23 +261,21 @@ primArrayToByteArray (PrimArray x) = PB.ByteArray x byteArrayToPrimArray :: ByteArray -> PrimArray a byteArrayToPrimArray (PB.ByteArray x) = PrimArray x -#if MIN_VERSION_base(4,9,0) -- | @since 0.6.4.0 instance Semigroup (PrimArray a) where - x <> y = byteArrayToPrimArray (primArrayToByteArray x SG.<> primArrayToByteArray y) - sconcat = byteArrayToPrimArray . SG.sconcat . fmap primArrayToByteArray - stimes i arr = byteArrayToPrimArray (SG.stimes i (primArrayToByteArray arr)) -#endif + x <> y = byteArrayToPrimArray (primArrayToByteArray x <> primArrayToByteArray y) + sconcat = byteArrayToPrimArray . sconcat . fmap primArrayToByteArray + stimes i arr = byteArrayToPrimArray (stimes i (primArrayToByteArray arr)) -- | @since 0.6.4.0 instance Monoid (PrimArray a) where mempty = emptyPrimArray #if !(MIN_VERSION_base(4,11,0)) - mappend x y = byteArrayToPrimArray (mappend (primArrayToByteArray x) (primArrayToByteArray y)) + mappend = (<>) #endif mconcat = byteArrayToPrimArray . mconcat . map primArrayToByteArray --- | The empty primitive array. +-- | The empty 'PrimArray'. emptyPrimArray :: PrimArray a {-# NOINLINE emptyPrimArray #-} emptyPrimArray = runST $ primitive $ \s0# -> case newByteArray# 0# s0# of @@ -248,11 +284,13 @@ emptyPrimArray = runST $ primitive $ \s0# -> case newByteArray# 0# s0# of -- | Create a new mutable primitive array of the given length. The -- underlying memory is left uninitialized. +-- +-- /Note:/ this function does not check if the input is non-negative. newPrimArray :: forall m a. (PrimMonad m, Prim a) => Int -> m (MutablePrimArray (PrimState m) a) {-# INLINE newPrimArray #-} newPrimArray (I# n#) = primitive (\s# -> - case newByteArray# (n# *# sizeOf# (undefined :: a)) s# of + case newByteArray# (n# *# sizeOfType# (Proxy :: Proxy a)) s# of (# s'#, arr# #) -> (# s'#, MutablePrimArray arr# #) ) @@ -271,40 +309,33 @@ resizeMutablePrimArray :: forall m a. (PrimMonad m, Prim a) -> Int -- ^ new size -> m (MutablePrimArray (PrimState m) a) {-# INLINE resizeMutablePrimArray #-} -#if __GLASGOW_HASKELL__ >= 710 resizeMutablePrimArray (MutablePrimArray arr#) (I# n#) - = primitive (\s# -> case resizeMutableByteArray# arr# (n# *# sizeOf# (undefined :: a)) s# of + = primitive (\s# -> case resizeMutableByteArray# arr# (n# *# sizeOfType# (Proxy :: Proxy a)) s# of (# s'#, arr'# #) -> (# s'#, MutablePrimArray arr'# #)) -#else -resizeMutablePrimArray arr n - = do arr' <- newPrimArray n - copyMutablePrimArray arr' 0 arr 0 (min (sizeofMutablePrimArray arr) n) - return arr' -#endif --- Although it is possible to shim resizeMutableByteArray for old GHCs, this --- is not the case with shrinkMutablePrimArray. -#if __GLASGOW_HASKELL__ >= 710 -- | Shrink a mutable primitive array. The new size is given in elements. -- It must be smaller than the old size. The array will be resized in place. --- This function is only available when compiling with GHC 7.10 or newer. shrinkMutablePrimArray :: forall m a. (PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -> Int -- ^ new size -> m () {-# INLINE shrinkMutablePrimArray #-} shrinkMutablePrimArray (MutablePrimArray arr#) (I# n#) - = primitive_ (shrinkMutableByteArray# arr# (n# *# sizeOf# (undefined :: a))) -#endif + = primitive_ (shrinkMutableByteArray# arr# (n# *# sizeOfType# (Proxy :: Proxy a))) +-- | Read a value from the array at the given index. +-- +-- /Note:/ this function does not do bounds checking. readPrimArray :: (Prim a, PrimMonad m) => MutablePrimArray (PrimState m) a -> Int -> m a {-# INLINE readPrimArray #-} readPrimArray (MutablePrimArray arr#) (I# i#) = primitive (readByteArray# arr# i#) -- | Write an element to the given index. -writePrimArray :: - (Prim a, PrimMonad m) +-- +-- /Note:/ this function does not do bounds checking. +writePrimArray + :: (Prim a, PrimMonad m) => MutablePrimArray (PrimState m) a -- ^ array -> Int -- ^ index -> a -- ^ element @@ -314,8 +345,10 @@ writePrimArray (MutablePrimArray arr#) (I# i#) x = primitive_ (writeByteArray# arr# i# x) -- | Copy part of a mutable array into another mutable array. --- In the case that the destination and --- source arrays are the same, the regions may overlap. +-- In the case that the destination and +-- source arrays are the same, the regions may overlap. +-- +-- /Note:/ this function does not do bounds or overlap checking. copyMutablePrimArray :: forall m a. (PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -- ^ destination array @@ -328,13 +361,15 @@ copyMutablePrimArray :: forall m a. copyMutablePrimArray (MutablePrimArray dst#) (I# doff#) (MutablePrimArray src#) (I# soff#) (I# n#) = primitive_ (copyMutableByteArray# src# - (soff# *# (sizeOf# (undefined :: a))) + (soff# *# sizeOfType# (Proxy :: Proxy a)) dst# - (doff# *# (sizeOf# (undefined :: a))) - (n# *# (sizeOf# (undefined :: a))) + (doff# *# sizeOfType# (Proxy :: Proxy a)) + (n# *# sizeOfType# (Proxy :: Proxy a)) ) -- | Copy part of an array into another mutable array. +-- +-- /Note:/ this function does not do bounds or overlap checking. copyPrimArray :: forall m a. (PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -- ^ destination array @@ -347,51 +382,71 @@ copyPrimArray :: forall m a. copyPrimArray (MutablePrimArray dst#) (I# doff#) (PrimArray src#) (I# soff#) (I# n#) = primitive_ (copyByteArray# src# - (soff# *# (sizeOf# (undefined :: a))) + (soff# *# sizeOfType# (Proxy :: Proxy a)) dst# - (doff# *# (sizeOf# (undefined :: a))) - (n# *# (sizeOf# (undefined :: a))) + (doff# *# sizeOfType# (Proxy :: Proxy a)) + (n# *# sizeOfType# (Proxy :: Proxy a)) ) -#if __GLASGOW_HASKELL__ >= 708 --- | Copy a slice of an immutable primitive array to an address. --- The offset and length are given in elements of type @a@. --- This function assumes that the 'Prim' instance of @a@ --- agrees with the 'Storable' instance. This function is only --- available when building with GHC 7.8 or newer. +-- | Copy a slice of an immutable primitive array to a pointer. +-- The offset and length are given in elements of type @a@. +-- This function assumes that the 'Prim' instance of @a@ +-- agrees with the 'Storable' instance. +-- +-- /Note:/ this function does not do bounds or overlap checking. copyPrimArrayToPtr :: forall m a. (PrimMonad m, Prim a) => Ptr a -- ^ destination pointer -> PrimArray a -- ^ source array -> Int -- ^ offset into source array - -> Int -- ^ number of prims to copy + -> Int -- ^ number of elements to copy -> m () {-# INLINE copyPrimArrayToPtr #-} copyPrimArrayToPtr (Ptr addr#) (PrimArray ba#) (I# soff#) (I# n#) = primitive (\ s# -> let s'# = copyByteArrayToAddr# ba# (soff# *# siz#) addr# (n# *# siz#) s# in (# s'#, () #)) - where siz# = sizeOf# (undefined :: a) + where siz# = sizeOfType# (Proxy :: Proxy a) --- | Copy a slice of an immutable primitive array to an address. --- The offset and length are given in elements of type @a@. --- This function assumes that the 'Prim' instance of @a@ --- agrees with the 'Storable' instance. This function is only --- available when building with GHC 7.8 or newer. +-- | Copy a slice of a mutable primitive array to a pointer. +-- The offset and length are given in elements of type @a@. +-- This function assumes that the 'Prim' instance of @a@ +-- agrees with the 'Storable' instance. +-- +-- /Note:/ this function does not do bounds or overlap checking. copyMutablePrimArrayToPtr :: forall m a. (PrimMonad m, Prim a) => Ptr a -- ^ destination pointer -> MutablePrimArray (PrimState m) a -- ^ source array -> Int -- ^ offset into source array - -> Int -- ^ number of prims to copy + -> Int -- ^ number of elements to copy -> m () {-# INLINE copyMutablePrimArrayToPtr #-} copyMutablePrimArrayToPtr (Ptr addr#) (MutablePrimArray mba#) (I# soff#) (I# n#) = primitive (\ s# -> let s'# = copyMutableByteArrayToAddr# mba# (soff# *# siz#) addr# (n# *# siz#) s# in (# s'#, () #)) - where siz# = sizeOf# (undefined :: a) -#endif + where siz# = sizeOfType# (Proxy :: Proxy a) + +-- | Copy from a pointer to a mutable primitive array. +-- The offset and length are given in elements of type @a@. +-- This function assumes that the 'Prim' instance of @a@ +-- agrees with the 'Storable' instance. +-- +-- /Note:/ this function does not do bounds or overlap checking. +copyPtrToMutablePrimArray :: forall m a. (PrimMonad m, Prim a) + => MutablePrimArray (PrimState m) a -- ^ destination array + -> Int -- ^ destination offset + -> Ptr a -- ^ source pointer + -> Int -- ^ number of elements + -> m () +{-# INLINE copyPtrToMutablePrimArray #-} +copyPtrToMutablePrimArray (MutablePrimArray ba#) (I# doff#) (Ptr addr#) (I# n#) = + primitive_ (copyAddrToByteArray# addr# ba# (doff# *# siz#) (n# *# siz#)) + where + siz# = sizeOfType# (Proxy :: Proxy a) -- | Fill a slice of a mutable primitive array with a value. +-- +-- /Note:/ this function does not do bounds checking. setPrimArray :: (Prim a, PrimMonad m) => MutablePrimArray (PrimState m) a -- ^ array to fill @@ -413,7 +468,7 @@ getSizeofMutablePrimArray :: forall m a. (PrimMonad m, Prim a) getSizeofMutablePrimArray (MutablePrimArray arr#) = primitive (\s# -> case getSizeofMutableByteArray# arr# s# of - (# s'#, sz# #) -> (# s'#, I# (quotInt# sz# (sizeOf# (undefined :: a))) #) + (# s'#, sz# #) -> (# s'#, I# (quotInt# sz# (sizeOfType# (Proxy :: Proxy a))) #) ) #else -- On older GHCs, it is not possible to resize a byte array, so @@ -424,12 +479,15 @@ getSizeofMutablePrimArray arr #endif -- | Size of the mutable primitive array in elements. This function shall not --- be used on primitive arrays that are an argument to or a result of --- 'resizeMutablePrimArray' or 'shrinkMutablePrimArray'. +-- be used on primitive arrays that are an argument to or a result of +-- 'resizeMutablePrimArray' or 'shrinkMutablePrimArray'. +-- +-- This function is deprecated and will be removed. sizeofMutablePrimArray :: forall s a. Prim a => MutablePrimArray s a -> Int {-# INLINE sizeofMutablePrimArray #-} +{-# DEPRECATED sizeofMutablePrimArray "use getSizeofMutablePrimArray instead" #-} sizeofMutablePrimArray (MutablePrimArray arr#) = - I# (quotInt# (sizeofMutableByteArray# arr#) (sizeOf# (undefined :: a))) + I# (quotInt# (sizeofMutableByteArray# arr#) (sizeOfType# (Proxy :: Proxy a))) -- | Check if the two arrays refer to the same memory block. sameMutablePrimArray :: MutablePrimArray s a -> MutablePrimArray s a -> Bool @@ -437,7 +495,49 @@ sameMutablePrimArray :: MutablePrimArray s a -> MutablePrimArray s a -> Bool sameMutablePrimArray (MutablePrimArray arr#) (MutablePrimArray brr#) = isTrue# (sameMutableByteArray# arr# brr#) --- | Convert a mutable byte array to an immutable one without copying. The +-- | Create an immutable copy of a slice of a primitive array. The offset and +-- length are given in elements. +-- +-- This operation makes a copy of the specified section, so it is safe to +-- continue using the mutable array afterward. +-- +-- /Note:/ The provided array should contain the full subrange +-- specified by the two Ints, but this is not checked. +freezePrimArray + :: (PrimMonad m, Prim a) + => MutablePrimArray (PrimState m) a -- ^ source + -> Int -- ^ offset in elements + -> Int -- ^ length in elements + -> m (PrimArray a) +{-# INLINE freezePrimArray #-} +freezePrimArray !src !off !len = do + dst <- newPrimArray len + copyMutablePrimArray dst 0 src off len + unsafeFreezePrimArray dst + +-- | Create a mutable primitive array from a slice of an immutable primitive array. +-- The offset and length are given in elements. +-- +-- This operation makes a copy of the specified slice, so it is safe to +-- use the immutable array afterward. +-- +-- /Note:/ The provided array should contain the full subrange +-- specified by the two Ints, but this is not checked. +-- +-- @since 0.7.2.0 +thawPrimArray + :: (PrimMonad m, Prim a) + => PrimArray a -- ^ source + -> Int -- ^ offset in elements + -> Int -- ^ length in elements + -> m (MutablePrimArray (PrimState m) a) +{-# INLINE thawPrimArray #-} +thawPrimArray !src !off !len = do + dst <- newPrimArray len + copyPrimArray dst 0 src off len + return dst + +-- | Convert a mutable primitive array to an immutable one without copying. The -- array should not be modified after the conversion. unsafeFreezePrimArray :: PrimMonad m => MutablePrimArray (PrimState m) a -> m (PrimArray a) @@ -455,6 +555,8 @@ unsafeThawPrimArray (PrimArray arr#) = primitive (\s# -> (# s#, MutablePrimArray (unsafeCoerce# arr#) #)) -- | Read a primitive value from the primitive array. +-- +-- /Note:/ this function does not do bounds checking. indexPrimArray :: forall a. Prim a => PrimArray a -> Int -> a {-# INLINE indexPrimArray #-} indexPrimArray (PrimArray arr#) (I# i#) = indexByteArray# arr# i# @@ -462,7 +564,27 @@ indexPrimArray (PrimArray arr#) (I# i#) = indexByteArray# arr# i# -- | Get the size, in elements, of the primitive array. sizeofPrimArray :: forall a. Prim a => PrimArray a -> Int {-# INLINE sizeofPrimArray #-} -sizeofPrimArray (PrimArray arr#) = I# (quotInt# (sizeofByteArray# arr#) (sizeOf# (undefined :: a))) +sizeofPrimArray (PrimArray arr#) = I# (quotInt# (sizeofByteArray# arr#) (sizeOfType# (Proxy :: Proxy a))) + +#if __GLASGOW_HASKELL__ >= 802 +-- | Check whether or not the primitive array is pinned. Pinned primitive arrays cannot +-- be moved by the garbage collector. It is safe to use 'primArrayContents' +-- on such arrays. This function is only available when compiling with +-- GHC 8.2 or newer. +-- +-- @since 0.7.1.0 +isPrimArrayPinned :: PrimArray a -> Bool +{-# INLINE isPrimArrayPinned #-} +isPrimArrayPinned (PrimArray arr#) = isTrue# (Exts.isByteArrayPinned# arr#) + +-- | Check whether or not the mutable primitive array is pinned. This function is +-- only available when compiling with GHC 8.2 or newer. +-- +-- @since 0.7.1.0 +isMutablePrimArrayPinned :: MutablePrimArray s a -> Bool +{-# INLINE isMutablePrimArrayPinned #-} +isMutablePrimArrayPinned (MutablePrimArray marr#) = isTrue# (Exts.isMutableByteArrayPinned# marr#) +#endif -- | Lazy right-associated fold over the elements of a 'PrimArray'. {-# INLINE foldrPrimArray #-} @@ -471,7 +593,7 @@ foldrPrimArray f z arr = go 0 where !sz = sizeofPrimArray arr go !i - | sz > i = f (indexPrimArray arr i) (go (i+1)) + | i < sz = f (indexPrimArray arr i) (go (i + 1)) | otherwise = z -- | Strict right-associated fold over the elements of a 'PrimArray'. @@ -549,17 +671,15 @@ traversePrimArrayP :: (PrimMonad m, Prim a, Prim b) traversePrimArrayP f arr = do let !sz = sizeofPrimArray arr marr <- newPrimArray sz - let go !ix = if ix < sz - then do - b <- f (indexPrimArray arr ix) - writePrimArray marr ix b - go (ix + 1) - else return () + let go !ix = when (ix < sz) $ do + b <- f (indexPrimArray arr ix) + writePrimArray marr ix b + go (ix + 1) go 0 unsafeFreezePrimArray marr -- | Filter the primitive array, keeping the elements for which the monadic --- predicate evaluates true. +-- predicate evaluates to true. {-# INLINE filterPrimArrayP #-} filterPrimArrayP :: (PrimMonad m, Prim a) => (a -> m Bool) @@ -615,12 +735,10 @@ generatePrimArrayP :: (PrimMonad m, Prim a) -> m (PrimArray a) generatePrimArrayP sz f = do marr <- newPrimArray sz - let go !ix = if ix < sz - then do - b <- f ix - writePrimArray marr ix b - go (ix + 1) - else return () + let go !ix = when (ix < sz) $ do + b <- f ix + writePrimArray marr ix b + go (ix + 1) go 0 unsafeFreezePrimArray marr @@ -633,16 +751,13 @@ replicatePrimArrayP :: (PrimMonad m, Prim a) -> m (PrimArray a) replicatePrimArrayP sz f = do marr <- newPrimArray sz - let go !ix = if ix < sz - then do - b <- f - writePrimArray marr ix b - go (ix + 1) - else return () + let go !ix = when (ix < sz) $ do + b <- f + writePrimArray marr ix b + go (ix + 1) go 0 unsafeFreezePrimArray marr - -- | Map over the elements of a primitive array. {-# INLINE mapPrimArray #-} mapPrimArray :: (Prim a, Prim b) @@ -652,12 +767,10 @@ mapPrimArray :: (Prim a, Prim b) mapPrimArray f arr = runST $ do let !sz = sizeofPrimArray arr marr <- newPrimArray sz - let go !ix = if ix < sz - then do - let b = f (indexPrimArray arr ix) - writePrimArray marr ix b - go (ix + 1) - else return () + let go !ix = when (ix < sz) $ do + let b = f (indexPrimArray arr ix) + writePrimArray marr ix b + go (ix + 1) go 0 unsafeFreezePrimArray marr @@ -670,12 +783,10 @@ imapPrimArray :: (Prim a, Prim b) imapPrimArray f arr = runST $ do let !sz = sizeofPrimArray arr marr <- newPrimArray sz - let go !ix = if ix < sz - then do - let b = f ix (indexPrimArray arr ix) - writePrimArray marr ix b - go (ix + 1) - else return () + let go !ix = when (ix < sz) $ do + let b = f ix (indexPrimArray arr ix) + writePrimArray marr ix b + go (ix + 1) go 0 unsafeFreezePrimArray marr @@ -703,8 +814,8 @@ filterPrimArray p arr = runST $ do -- | Filter the primitive array, keeping the elements for which the monadic -- predicate evaluates true. -filterPrimArrayA :: - (Applicative f, Prim a) +filterPrimArrayA + :: (Applicative f, Prim a) => (a -> f Bool) -- ^ mapping function -> PrimArray a -- ^ primitive array -> f (PrimArray a) @@ -727,8 +838,8 @@ filterPrimArrayA f = \ !ary -> -- | Map over the primitive array, keeping the elements for which the applicative -- predicate provides a 'Just'. -mapMaybePrimArrayA :: - (Applicative f, Prim a, Prim b) +mapMaybePrimArrayA + :: (Applicative f, Prim a, Prim b) => (a -> f (Maybe b)) -- ^ mapping function -> PrimArray a -- ^ primitive array -> f (PrimArray b) @@ -772,7 +883,6 @@ mapMaybePrimArray p arr = runST $ do marr' <- resizeMutablePrimArray marr dstLen unsafeFreezePrimArray marr' - -- | Traverse a primitive array. The traversal performs all of the applicative -- effects /before/ forcing the resulting values and writing them to the new -- primitive array. Consequently: @@ -786,8 +896,8 @@ mapMaybePrimArray p arr = runST $ do -- The function 'traversePrimArrayP' always outperforms this function, but it -- requires a 'PrimMonad' constraint, and it forces the values as -- it performs the effects. -traversePrimArray :: - (Applicative f, Prim a, Prim b) +traversePrimArray + :: (Applicative f, Prim a, Prim b) => (a -> f b) -- ^ mapping function -> PrimArray a -- ^ primitive array -> f (PrimArray b) @@ -805,8 +915,8 @@ traversePrimArray f = \ !ary -> else runSTA len <$> go 0 -- | Traverse a primitive array with the index of each element. -itraversePrimArray :: - (Applicative f, Prim a, Prim b) +itraversePrimArray + :: (Applicative f, Prim a, Prim b) => (Int -> a -> f b) -> PrimArray a -> f (PrimArray b) @@ -850,11 +960,9 @@ generatePrimArray :: Prim a -> PrimArray a generatePrimArray len f = runST $ do marr <- newPrimArray len - let go !ix = if ix < len - then do - writePrimArray marr ix (f ix) - go (ix + 1) - else return () + let go !ix = when (ix < len) $ do + writePrimArray marr ix (f ix) + go (ix + 1) go 0 unsafeFreezePrimArray marr @@ -873,8 +981,8 @@ replicatePrimArray len a = runST $ do -- | Generate a primitive array by evaluating the applicative generator -- function at each index. {-# INLINE generatePrimArrayA #-} -generatePrimArrayA :: - (Applicative f, Prim a) +generatePrimArrayA + :: (Applicative f, Prim a) => Int -- ^ length -> (Int -> f a) -- ^ element from index -> f (PrimArray a) @@ -891,10 +999,10 @@ generatePrimArrayA len f = else runSTA len <$> go 0 -- | Execute the applicative action the given number of times and store the --- results in a vector. +-- results in a 'PrimArray'. {-# INLINE replicatePrimArrayA #-} -replicatePrimArrayA :: - (Applicative f, Prim a) +replicatePrimArrayA + :: (Applicative f, Prim a) => Int -- ^ length -> f a -- ^ applicative element producer -> f (PrimArray a) @@ -911,32 +1019,30 @@ replicatePrimArrayA len f = else runSTA len <$> go 0 -- | Traverse the primitive array, discarding the results. There --- is no 'PrimMonad' variant of this function since it would not provide +-- is no 'PrimMonad' variant of this function, since it would not provide -- any performance benefit. -traversePrimArray_ :: - (Applicative f, Prim a) +traversePrimArray_ + :: (Applicative f, Prim a) => (a -> f b) -> PrimArray a -> f () traversePrimArray_ f a = go 0 where !sz = sizeofPrimArray a - go !ix = if ix < sz - then f (indexPrimArray a ix) *> go (ix + 1) - else pure () + go !ix = when (ix < sz) $ + f (indexPrimArray a ix) *> go (ix + 1) -- | Traverse the primitive array with the indices, discarding the results. --- There is no 'PrimMonad' variant of this function since it would not +-- There is no 'PrimMonad' variant of this function, since it would not -- provide any performance benefit. -itraversePrimArray_ :: - (Applicative f, Prim a) +itraversePrimArray_ + :: (Applicative f, Prim a) => (Int -> a -> f b) -> PrimArray a -> f () itraversePrimArray_ f a = go 0 where !sz = sizeofPrimArray a - go !ix = if ix < sz - then f ix (indexPrimArray a ix) *> go (ix + 1) - else pure () + go !ix = when (ix < sz) $ + f ix (indexPrimArray a ix) *> go (ix + 1) newtype IxSTA a = IxSTA {_runIxSTA :: forall s. Int -> MutableByteArray# s -> ST s Int} @@ -965,4 +1071,116 @@ The naming conventions adopted in this section are explained in the documentation of the @Data.Primitive@ module. -} +-- | Create a /pinned/ primitive array of the specified size (in elements). The garbage +-- collector is guaranteed not to move it. The underlying memory is left uninitialized. +-- +-- @since 0.7.1.0 +newPinnedPrimArray :: forall m a. (PrimMonad m, Prim a) + => Int -> m (MutablePrimArray (PrimState m) a) +{-# INLINE newPinnedPrimArray #-} +newPinnedPrimArray (I# n#) + = primitive (\s# -> case newPinnedByteArray# (n# *# sizeOfType# (Proxy :: Proxy a)) s# of + (# s'#, arr# #) -> (# s'#, MutablePrimArray arr# #)) + +-- | Create a /pinned/ primitive array of the specified size (in elements) and +-- with the alignment given by its 'Prim' instance. The garbage collector is +-- guaranteed not to move it. The underlying memory is left uninitialized. +-- +-- @since 0.7.0.0 +newAlignedPinnedPrimArray :: forall m a. (PrimMonad m, Prim a) + => Int -> m (MutablePrimArray (PrimState m) a) +{-# INLINE newAlignedPinnedPrimArray #-} +newAlignedPinnedPrimArray (I# n#) + = primitive (\s# -> case newAlignedPinnedByteArray# (n# *# sizeOfType# (Proxy :: Proxy a)) (alignmentOfType# (Proxy :: Proxy a)) s# of + (# s'#, arr# #) -> (# s'#, MutablePrimArray arr# #)) + +-- | Yield a pointer to the array's data. This operation is only safe on +-- /pinned/ prim arrays allocated by 'newPinnedByteArray' or +-- 'newAlignedPinnedByteArray'. +-- +-- @since 0.7.1.0 +primArrayContents :: PrimArray a -> Ptr a +{-# INLINE primArrayContents #-} +primArrayContents (PrimArray arr#) = Ptr (byteArrayContents# arr#) + +-- | Yield a pointer to the array's data. This operation is only safe on +-- /pinned/ byte arrays allocated by 'newPinnedByteArray' or +-- 'newAlignedPinnedByteArray'. +-- +-- @since 0.7.1.0 +mutablePrimArrayContents :: MutablePrimArray s a -> Ptr a +{-# INLINE mutablePrimArrayContents #-} +mutablePrimArrayContents (MutablePrimArray arr#) = + Ptr (mutableByteArrayContentsShim arr#) + +-- | Return a newly allocated array with the specified subrange of the +-- provided array. The provided array should contain the full subrange +-- specified by the two Ints, but this is not checked. +clonePrimArray :: Prim a + => PrimArray a -- ^ source array + -> Int -- ^ offset into destination array + -> Int -- ^ number of elements to copy + -> PrimArray a +{-# INLINE clonePrimArray #-} +clonePrimArray src off n = runPrimArray $ do + dst <- newPrimArray n + copyPrimArray dst 0 src off n + return dst + +-- | Return a newly allocated mutable array with the specified subrange of +-- the provided mutable array. The provided mutable array should contain the +-- full subrange specified by the two Ints, but this is not checked. +cloneMutablePrimArray :: (PrimMonad m, Prim a) + => MutablePrimArray (PrimState m) a -- ^ source array + -> Int -- ^ offset into destination array + -> Int -- ^ number of elements to copy + -> m (MutablePrimArray (PrimState m) a) +{-# INLINE cloneMutablePrimArray #-} +cloneMutablePrimArray src off n = do + dst <- newPrimArray n + copyMutablePrimArray dst 0 src off n + return dst + +-- | Execute the monadic action and freeze the resulting array. +-- +-- > runPrimArray m = runST $ m >>= unsafeFreezePrimArray +runPrimArray + :: (forall s. ST s (MutablePrimArray s a)) + -> PrimArray a +#if MIN_VERSION_base(4,10,0) /* In new GHCs, runRW# is available. */ +runPrimArray m = PrimArray (runPrimArray# m) + +runPrimArray# + :: (forall s. ST s (MutablePrimArray s a)) + -> ByteArray# +runPrimArray# m = case runRW# $ \s -> + case unST m s of { (# s', MutablePrimArray mary# #) -> + unsafeFreezeByteArray# mary# s'} of (# _, ary# #) -> ary# + +unST :: ST s a -> State# s -> (# State# s, a #) +unST (GHCST.ST f) = f +#else /* In older GHCs, runRW# is not available. */ +runPrimArray m = runST $ m >>= unsafeFreezePrimArray +#endif +-- | A composition of 'primArrayContents' and 'keepAliveUnlifted'. +-- The callback function must not return the pointer. The argument +-- array must be /pinned/. See 'primArrayContents' for an explanation +-- of which primitive arrays are pinned. +-- +-- Note: This could be implemented with 'keepAlive' instead of +-- 'keepAliveUnlifted', but 'keepAlive' here would cause GHC to materialize +-- the wrapper data constructor on the heap. +withPrimArrayContents :: PrimBase m => PrimArray a -> (Ptr a -> m a) -> m a +{-# INLINE withPrimArrayContents #-} +withPrimArrayContents (PrimArray arr#) f = + keepAliveUnlifted arr# (f (Ptr (byteArrayContents# arr#))) + +-- | A composition of 'mutablePrimArrayContents' and 'keepAliveUnlifted'. +-- The callback function must not return the pointer. The argument +-- array must be /pinned/. See 'primArrayContents' for an explanation +-- of which primitive arrays are pinned. +withMutablePrimArrayContents :: PrimBase m => MutablePrimArray (PrimState m) a -> (Ptr a -> m a) -> m a +{-# INLINE withMutablePrimArrayContents #-} +withMutablePrimArrayContents (MutablePrimArray arr#) f = + keepAliveUnlifted arr# (f (Ptr (mutableByteArrayContentsShim arr#))) diff --git a/examples/primitive/Data/Primitive/PrimVar.hs b/examples/primitive/Data/Primitive/PrimVar.hs new file mode 100644 index 000000000..f2924a67f --- /dev/null +++ b/examples/primitive/Data/Primitive/PrimVar.hs @@ -0,0 +1,167 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE RoleAnnotations #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE Unsafe #-} + +-- | Variant of @MutVar@ that has one less indirection for primitive types. +-- The difference is illustrated by comparing @MutVar Int@ and @PrimVar Int@: +-- +-- * @MutVar Int@: @MutVar# --> I#@ +-- * @PrimVar Int@: @MutableByteArray#@ +-- +-- This module is adapted from a module in Edward Kmett\'s @prim-ref@ library. +module Data.Primitive.PrimVar + ( + -- * Primitive References + PrimVar(..) + , newPrimVar + , newPinnedPrimVar + , newAlignedPinnedPrimVar + , readPrimVar + , writePrimVar + , modifyPrimVar + , primVarContents + , primVarToMutablePrimArray + -- * Atomic Operations + -- $atomic + , casInt + , fetchAddInt + , fetchSubInt + , fetchAndInt + , fetchNandInt + , fetchOrInt + , fetchXorInt + , atomicReadInt + , atomicWriteInt + ) where + +import Control.Monad.Primitive +import Data.Primitive +import GHC.Exts +import GHC.Ptr (castPtr) + +-------------------------------------------------------------------------------- +-- * Primitive References +-------------------------------------------------------------------------------- + +-- | A 'PrimVar' behaves like a single-element mutable primitive array. +newtype PrimVar s a = PrimVar (MutablePrimArray s a) + +type role PrimVar nominal nominal + +-- | Create a primitive reference. +newPrimVar :: (PrimMonad m, Prim a) => a -> m (PrimVar (PrimState m) a) +newPrimVar a = do + m <- newPrimArray 1 + writePrimArray m 0 a + return (PrimVar m) +{-# INLINE newPrimVar #-} + +-- | Create a pinned primitive reference. +newPinnedPrimVar :: (PrimMonad m, Prim a) => a -> m (PrimVar (PrimState m) a) +newPinnedPrimVar a = do + m <- newPinnedPrimArray 1 + writePrimArray m 0 a + return (PrimVar m) +{-# INLINE newPinnedPrimVar #-} + +-- | Create a pinned primitive reference with the appropriate alignment for its contents. +newAlignedPinnedPrimVar :: (PrimMonad m, Prim a) => a -> m (PrimVar (PrimState m) a) +newAlignedPinnedPrimVar a = do + m <- newAlignedPinnedPrimArray 1 + writePrimArray m 0 a + return (PrimVar m) +{-# INLINE newAlignedPinnedPrimVar #-} + +-- | Read a value from the 'PrimVar'. +readPrimVar :: (PrimMonad m, Prim a) => PrimVar (PrimState m) a -> m a +readPrimVar (PrimVar m) = readPrimArray m 0 +{-# INLINE readPrimVar #-} + +-- | Write a value to the 'PrimVar'. +writePrimVar :: (PrimMonad m, Prim a) => PrimVar (PrimState m) a -> a -> m () +writePrimVar (PrimVar m) a = writePrimArray m 0 a +{-# INLINE writePrimVar #-} + +-- | Mutate the contents of a 'PrimVar'. +modifyPrimVar :: (PrimMonad m, Prim a) => PrimVar (PrimState m) a -> (a -> a) -> m () +modifyPrimVar pv f = do + x <- readPrimVar pv + writePrimVar pv (f x) +{-# INLINE modifyPrimVar #-} + +instance Eq (PrimVar s a) where + PrimVar m == PrimVar n = sameMutablePrimArray m n + {-# INLINE (==) #-} + +-- | Yield a pointer to the data of a 'PrimVar'. This operation is only safe on pinned byte arrays allocated by +-- 'newPinnedPrimVar' or 'newAlignedPinnedPrimVar'. +primVarContents :: PrimVar s a -> Ptr a +primVarContents (PrimVar m) = castPtr $ mutablePrimArrayContents m +{-# INLINE primVarContents #-} + +-- | Convert a 'PrimVar' to a one-elment 'MutablePrimArray'. +primVarToMutablePrimArray :: PrimVar s a -> MutablePrimArray s a +primVarToMutablePrimArray (PrimVar m) = m +{-# INLINE primVarToMutablePrimArray #-} + +-------------------------------------------------------------------------------- +-- * Atomic Operations +-------------------------------------------------------------------------------- + +-- $atomic +-- Atomic operations on `PrimVar s Int`. All atomic operations imply a full memory barrier. + +-- | Given a primitive reference, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. +casInt :: PrimMonad m => PrimVar (PrimState m) Int -> Int -> Int -> m Int +casInt (PrimVar (MutablePrimArray m)) (I# old) (I# new) = primitive $ \s -> case casIntArray# m 0# old new s of + (# s', result #) -> (# s', I# result #) +{-# INLINE casInt #-} + +-- | Given a reference, and a value to add, atomically add the value to the element. Returns the value of the element before the operation. +fetchAddInt :: PrimMonad m => PrimVar (PrimState m) Int -> Int -> m Int +fetchAddInt (PrimVar (MutablePrimArray m)) (I# x) = primitive $ \s -> case fetchAddIntArray# m 0# x s of + (# s', result #) -> (# s', I# result #) +{-# INLINE fetchAddInt #-} + +-- | Given a reference, and a value to subtract, atomically subtract the value from the element. Returns the value of the element before the operation. +fetchSubInt :: PrimMonad m => PrimVar (PrimState m) Int -> Int -> m Int +fetchSubInt (PrimVar (MutablePrimArray m)) (I# x) = primitive $ \s -> case fetchSubIntArray# m 0# x s of + (# s', result #) -> (# s', I# result #) +{-# INLINE fetchSubInt #-} + +-- | Given a reference, and a value to bitwise and, atomically and the value with the element. Returns the value of the element before the operation. +fetchAndInt :: PrimMonad m => PrimVar (PrimState m) Int -> Int -> m Int +fetchAndInt (PrimVar (MutablePrimArray m)) (I# x) = primitive $ \s -> case fetchAndIntArray# m 0# x s of + (# s', result #) -> (# s', I# result #) +{-# INLINE fetchAndInt #-} + +-- | Given a reference, and a value to bitwise nand, atomically nand the value with the element. Returns the value of the element before the operation. +fetchNandInt :: PrimMonad m => PrimVar (PrimState m) Int -> Int -> m Int +fetchNandInt (PrimVar (MutablePrimArray m)) (I# x) = primitive $ \s -> case fetchNandIntArray# m 0# x s of + (# s', result #) -> (# s', I# result #) +{-# INLINE fetchNandInt #-} + +-- | Given a reference, and a value to bitwise or, atomically or the value with the element. Returns the value of the element before the operation. +fetchOrInt :: PrimMonad m => PrimVar (PrimState m) Int -> Int -> m Int +fetchOrInt (PrimVar (MutablePrimArray m)) (I# x) = primitive $ \s -> case fetchOrIntArray# m 0# x s of + (# s', result #) -> (# s', I# result #) +{-# INLINE fetchOrInt #-} + +-- | Given a reference, and a value to bitwise xor, atomically xor the value with the element. Returns the value of the element before the operation. +fetchXorInt :: PrimMonad m => PrimVar (PrimState m) Int -> Int -> m Int +fetchXorInt (PrimVar (MutablePrimArray m)) (I# x) = primitive $ \s -> case fetchXorIntArray# m 0# x s of + (# s', result #) -> (# s', I# result #) +{-# INLINE fetchXorInt #-} + +-- | Given a reference, atomically read an element. +atomicReadInt :: PrimMonad m => PrimVar (PrimState m) Int -> m Int +atomicReadInt (PrimVar (MutablePrimArray m)) = primitive $ \s -> case atomicReadIntArray# m 0# s of + (# s', result #) -> (# s', I# result #) +{-# INLINE atomicReadInt #-} + +-- | Given a reference, atomically write an element. +atomicWriteInt :: PrimMonad m => PrimVar (PrimState m) Int -> Int -> m () +atomicWriteInt (PrimVar (MutablePrimArray m)) (I# x) = primitive_ $ \s -> atomicWriteIntArray# m 0# x s +{-# INLINE atomicWriteInt #-} diff --git a/examples/primitive/Data/Primitive/Ptr.hs b/examples/primitive/Data/Primitive/Ptr.hs index bb3aeef6e..011abc359 100644 --- a/examples/primitive/Data/Primitive/Ptr.hs +++ b/examples/primitive/Data/Primitive/Ptr.hs @@ -1,7 +1,7 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE MagicHash #-} -{-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeApplications #-} -- | -- Module : Data.Primitive.Ptr @@ -11,7 +11,7 @@ -- Maintainer : Roman Leshchinskiy -- Portability : non-portable -- --- Primitive operations on machine addresses +-- Primitive operations on machine addresses. -- -- @since 0.6.4.0 @@ -28,20 +28,17 @@ module Data.Primitive.Ptr ( -- * Block operations copyPtr, movePtr, setPtr -#if __GLASGOW_HASKELL__ >= 708 , copyPtrToMutablePrimArray -#endif + , copyPtrToMutableByteArray ) where import Control.Monad.Primitive import Data.Primitive.Types -#if __GLASGOW_HASKELL__ >= 708 -import Data.Primitive.PrimArray (MutablePrimArray(..)) -#endif +import Data.Primitive.PrimArray (copyPtrToMutablePrimArray) +import Data.Primitive.ByteArray (copyPtrToMutableByteArray) -import GHC.Base ( Int(..) ) +import Data.Proxy import GHC.Exts - import GHC.Ptr import Foreign.Marshal.Utils @@ -49,14 +46,14 @@ import Foreign.Marshal.Utils -- | Offset a pointer by the given number of elements. advancePtr :: forall a. Prim a => Ptr a -> Int -> Ptr a {-# INLINE advancePtr #-} -advancePtr (Ptr a#) (I# i#) = Ptr (plusAddr# a# (i# *# sizeOf# (undefined :: a))) +advancePtr (Ptr a#) (I# i#) = Ptr (plusAddr# a# (i# *# sizeOfType# (Proxy :: Proxy a))) -- | Subtract a pointer from another pointer. The result represents --- the number of elements of type @a@ that fit in the contiguous --- memory range bounded by these two pointers. +-- the number of elements of type @a@ that fit in the contiguous +-- memory range bounded by these two pointers. subtractPtr :: forall a. Prim a => Ptr a -> Ptr a -> Int {-# INLINE subtractPtr #-} -subtractPtr (Ptr a#) (Ptr b#) = I# (quotInt# (minusAddr# a# b#) (sizeOf# (undefined :: a))) +subtractPtr (Ptr a#) (Ptr b#) = I# (quotInt# (minusAddr# a# b#) (sizeOfType# (Proxy :: Proxy a))) -- | Read a value from a memory position given by a pointer and an offset. -- The memory block the address refers to must be immutable. The offset is in @@ -86,40 +83,21 @@ copyPtr :: forall m a. (PrimMonad m, Prim a) -> m () {-# INLINE copyPtr #-} copyPtr (Ptr dst#) (Ptr src#) n - = unsafePrimToPrim $ copyBytes (Ptr dst#) (Ptr src#) (n * sizeOf (undefined :: a)) + = unsafePrimToPrim $ copyBytes (Ptr dst#) (Ptr src#) (n * sizeOfType @a) -- | Copy the given number of elements from the second 'Ptr' to the first. The -- areas may overlap. movePtr :: forall m a. (PrimMonad m, Prim a) - => Ptr a -- ^ destination address - -> Ptr a -- ^ source address + => Ptr a -- ^ destination pointer + -> Ptr a -- ^ source pointer -> Int -- ^ number of elements -> m () {-# INLINE movePtr #-} movePtr (Ptr dst#) (Ptr src#) n - = unsafePrimToPrim $ moveBytes (Ptr dst#) (Ptr src#) (n * sizeOf (undefined :: a)) + = unsafePrimToPrim $ moveBytes (Ptr dst#) (Ptr src#) (n * sizeOfType @a) -- | Fill a memory block with the given value. The length is in -- elements of type @a@ rather than in bytes. setPtr :: (Prim a, PrimMonad m) => Ptr a -> Int -> a -> m () {-# INLINE setPtr #-} setPtr (Ptr addr#) (I# n#) x = primitive_ (setOffAddr# addr# 0# n# x) - - -#if __GLASGOW_HASKELL__ >= 708 --- | Copy from a pointer to a mutable primitive array. --- The offset and length are given in elements of type @a@. --- This function is only available when building with GHC 7.8 --- or newer. -copyPtrToMutablePrimArray :: forall m a. (PrimMonad m, Prim a) - => MutablePrimArray (PrimState m) a -- ^ destination array - -> Int -- ^ destination offset - -> Ptr a -- ^ source pointer - -> Int -- ^ number of elements - -> m () -{-# INLINE copyPtrToMutablePrimArray #-} -copyPtrToMutablePrimArray (MutablePrimArray ba#) (I# doff#) (Ptr addr#) (I# n#) = - primitive_ (copyAddrToByteArray# addr# ba# (doff# *# siz#) (n# *# siz#)) - where - siz# = sizeOf# (undefined :: a) -#endif diff --git a/examples/primitive/Data/Primitive/SmallArray.hs b/examples/primitive/Data/Primitive/SmallArray.hs index 7e0eb413d..446c30716 100644 --- a/examples/primitive/Data/Primitive/SmallArray.hs +++ b/examples/primitive/Data/Primitive/SmallArray.hs @@ -7,6 +7,7 @@ {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE BangPatterns #-} +{-# LANGUAGE TemplateHaskellQuotes #-} -- | -- Module : Data.Primitive.SmallArray @@ -18,7 +19,7 @@ -- -- Small arrays are boxed (im)mutable arrays. -- --- The underlying structure of the 'Array' type contains a card table, allowing +-- The underlying structure of the 'Data.Primitive.Array.Array' type contains a card table, allowing -- segments of the array to be marked as having been mutated. This allows the -- garbage collector to only re-traverse segments of the array that have been -- marked during certain phases, rather than having to traverse the entire @@ -30,11 +31,8 @@ -- entire array. These advantages make them suitable for use as arrays that are -- known to be small. -- --- The card size is 128, so for uses much larger than that, 'Array' would likely --- be superior. --- --- The underlying type, 'SmallArray#', was introduced in GHC 7.10, so prior to --- that version, this module simply implements small arrays as 'Array'. +-- The card size is 128, so for uses much larger than that, +-- 'Data.Primitive.Array.Array' would likely be superior. module Data.Primitive.SmallArray ( SmallArray(..) @@ -52,27 +50,28 @@ module Data.Primitive.SmallArray , freezeSmallArray , unsafeFreezeSmallArray , thawSmallArray - , runSmallArray , unsafeThawSmallArray + , runSmallArray + , createSmallArray , sizeofSmallArray + , getSizeofSmallMutableArray , sizeofSmallMutableArray +#if MIN_VERSION_base(4,14,0) + , shrinkSmallMutableArray + , resizeSmallMutableArray +#endif + , emptySmallArray , smallArrayFromList , smallArrayFromListN , mapSmallArray' , traverseSmallArrayP ) where - -#if (__GLASGOW_HASKELL__ >= 710) -#define HAVE_SMALL_ARRAY 1 -#endif - -#if MIN_VERSION_base(4,7,0) import GHC.Exts hiding (toList) import qualified GHC.Exts -#endif import Control.Applicative +import Control.DeepSeq import Control.Monad import qualified Control.Monad.Fail as Fail import Control.Monad.Fix @@ -82,122 +81,105 @@ import Control.Monad.Zip import Data.Data import Data.Foldable as Foldable import Data.Functor.Identity -#if !(MIN_VERSION_base(4,10,0)) -import Data.Monoid -#endif -#if MIN_VERSION_base(4,9,0) +import Data.Primitive.Internal.Read (Tag(..),lexTag) +import Text.Read (Read (..), parens, prec) import qualified GHC.ST as GHCST -import qualified Data.Semigroup as Sem -#endif +import Data.Semigroup import Text.ParserCombinators.ReadP -#if MIN_VERSION_base(4,10,0) -import GHC.Exts (runRW#) -#elif MIN_VERSION_base(4,9,0) +import Text.ParserCombinators.ReadPrec (ReadPrec) +import qualified Text.ParserCombinators.ReadPrec as RdPrc +#if !MIN_VERSION_base(4,10,0) import GHC.Base (runRW#) #endif -#if !(HAVE_SMALL_ARRAY) -import Data.Primitive.Array -import Data.Traversable -import qualified Data.Primitive.Array as Array -#endif +import Data.Functor.Classes (Eq1(..), Ord1(..), Show1(..), Read1(..)) +import Language.Haskell.TH.Syntax (Lift(..)) -#if MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,4,0) -import Data.Functor.Classes (Eq1(..),Ord1(..),Show1(..),Read1(..)) -#endif - -#if HAVE_SMALL_ARRAY data SmallArray a = SmallArray (SmallArray# a) deriving Typeable -#else -newtype SmallArray a = SmallArray (Array a) deriving - ( Eq - , Ord - , Show - , Read - , Foldable - , Traversable - , Functor - , Applicative - , Alternative - , Monad - , MonadPlus - , MonadZip - , MonadFix - , Monoid - , Typeable -#if MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,4,0) - , Eq1 - , Ord1 - , Show1 - , Read1 -#endif - ) -#if MIN_VERSION_base(4,7,0) -instance IsList (SmallArray a) where - type Item (SmallArray a) = a - fromListN n l = SmallArray (fromListN n l) - fromList l = SmallArray (fromList l) - toList a = Foldable.toList a -#endif +#if MIN_VERSION_deepseq(1,4,3) +instance NFData1 SmallArray where + liftRnf r = foldl' (\_ -> r) () #endif -#if HAVE_SMALL_ARRAY +instance NFData a => NFData (SmallArray a) where + rnf = foldl' (\_ -> rnf) () + data SmallMutableArray s a = SmallMutableArray (SmallMutableArray# s a) deriving Typeable + +instance Lift a => Lift (SmallArray a) where +#if MIN_VERSION_template_haskell(2,16,0) + liftTyped ary = case lst of + [] -> [|| SmallArray (emptySmallArray# (##)) ||] + [x] -> [|| pure $! x ||] + x : xs -> [|| unsafeSmallArrayFromListN' len x xs ||] #else -newtype SmallMutableArray s a = SmallMutableArray (MutableArray s a) - deriving (Eq, Typeable) + lift ary = case lst of + [] -> [| SmallArray (emptySmallArray# (##)) |] + [x] -> [| pure $! x |] + x : xs -> [| unsafeSmallArrayFromListN' len x xs |] #endif + where + len = length ary + lst = toList ary + +-- | Strictly create an array from a nonempty list (represented as +-- a first element and a list of the rest) of a known length. If the length +-- of the list does not match the given length, this makes demons fly +-- out of your nose. We use it in the 'Lift' instance. If you edit the +-- splice and break it, you get to keep both pieces. +unsafeSmallArrayFromListN' :: Int -> a -> [a] -> SmallArray a +unsafeSmallArrayFromListN' n y ys = + createSmallArray n y $ \sma -> + let go !_ix [] = return () + go !ix (!x : xs) = do + writeSmallArray sma ix x + go (ix+1) xs + in go 1 ys -- | Create a new small mutable array. +-- +-- /Note:/ this function does not check if the input is non-negative. newSmallArray :: PrimMonad m => Int -- ^ size -> a -- ^ initial contents -> m (SmallMutableArray (PrimState m) a) -#if HAVE_SMALL_ARRAY newSmallArray (I# i#) x = primitive $ \s -> case newSmallArray# i# x s of (# s', sma# #) -> (# s', SmallMutableArray sma# #) -#else -newSmallArray n e = SmallMutableArray `liftM` newArray n e -#endif {-# INLINE newSmallArray #-} -- | Read the element at a given index in a mutable array. +-- +-- /Note:/ this function does not do bounds checking. readSmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -- ^ array -> Int -- ^ index -> m a -#if HAVE_SMALL_ARRAY readSmallArray (SmallMutableArray sma#) (I# i#) = primitive $ readSmallArray# sma# i# -#else -readSmallArray (SmallMutableArray a) = readArray a -#endif {-# INLINE readSmallArray #-} -- | Write an element at the given idex in a mutable array. +-- +-- /Note:/ this function does not do bounds checking. writeSmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -- ^ array -> Int -- ^ index -> a -- ^ new element -> m () -#if HAVE_SMALL_ARRAY writeSmallArray (SmallMutableArray sma#) (I# i#) x = primitive_ $ writeSmallArray# sma# i# x -#else -writeSmallArray (SmallMutableArray a) = writeArray a -#endif {-# INLINE writeSmallArray #-} -- | Look up an element in an immutable array. -- --- The purpose of returning a result using a monad is to allow the caller to +-- The purpose of returning a result using an applicative is to allow the caller to -- avoid retaining references to the array. Evaluating the return value will -- cause the array lookup to be performed, even though it may not require the -- element of the array to be evaluated (which could throw an exception). For @@ -214,95 +196,84 @@ writeSmallArray (SmallMutableArray a) = writeArray a -- -- > let x = indexSmallArray sa 0 -- --- And does not prevent 'sa' from being garbage collected. +-- It also does not prevent 'sa' from being garbage collected. -- -- Note that 'Identity' is not adequate for this use, as it is a newtype, and -- cannot be evaluated without evaluating the element. +-- +-- /Note:/ this function does not do bounds checking. indexSmallArrayM - :: Monad m + :: Applicative m => SmallArray a -- ^ array -> Int -- ^ index -> m a -#if HAVE_SMALL_ARRAY indexSmallArrayM (SmallArray sa#) (I# i#) = case indexSmallArray# sa# i# of (# x #) -> pure x -#else -indexSmallArrayM (SmallArray a) = indexArrayM a -#endif {-# INLINE indexSmallArrayM #-} -- | Look up an element in an immutable array. +-- +-- /Note:/ this function does not do bounds checking. indexSmallArray :: SmallArray a -- ^ array -> Int -- ^ index -> a -#if HAVE_SMALL_ARRAY indexSmallArray sa i = runIdentity $ indexSmallArrayM sa i -#else -indexSmallArray (SmallArray a) = indexArray a -#endif {-# INLINE indexSmallArray #-} -- | Read a value from the immutable array at the given index, returning -- the result in an unboxed unary tuple. This is currently used to implement -- folds. +-- +-- /Note:/ this function does not do bounds checking. indexSmallArray## :: SmallArray a -> Int -> (# a #) -#if HAVE_SMALL_ARRAY indexSmallArray## (SmallArray ary) (I# i) = indexSmallArray# ary i -#else -indexSmallArray## (SmallArray a) = indexArray## a -#endif {-# INLINE indexSmallArray## #-} -- | Create a copy of a slice of an immutable array. +-- +-- /Note:/ The provided array should contain the full subrange +-- specified by the two Ints, but this is not checked. cloneSmallArray :: SmallArray a -- ^ source -> Int -- ^ offset -> Int -- ^ length -> SmallArray a -#if HAVE_SMALL_ARRAY cloneSmallArray (SmallArray sa#) (I# i#) (I# j#) = SmallArray (cloneSmallArray# sa# i# j#) -#else -cloneSmallArray (SmallArray a) i j = SmallArray $ cloneArray a i j -#endif {-# INLINE cloneSmallArray #-} -- | Create a copy of a slice of a mutable array. +-- +-- /Note:/ The provided array should contain the full subrange +-- specified by the two Ints, but this is not checked. cloneSmallMutableArray :: PrimMonad m => SmallMutableArray (PrimState m) a -- ^ source -> Int -- ^ offset -> Int -- ^ length -> m (SmallMutableArray (PrimState m) a) -#if HAVE_SMALL_ARRAY cloneSmallMutableArray (SmallMutableArray sma#) (I# o#) (I# l#) = primitive $ \s -> case cloneSmallMutableArray# sma# o# l# s of (# s', smb# #) -> (# s', SmallMutableArray smb# #) -#else -cloneSmallMutableArray (SmallMutableArray ma) i j = - SmallMutableArray `liftM` cloneMutableArray ma i j -#endif {-# INLINE cloneSmallMutableArray #-} -- | Create an immutable array corresponding to a slice of a mutable array. -- -- This operation copies the portion of the array to be frozen. +-- +-- /Note:/ The provided array should contain the full subrange +-- specified by the two Ints, but this is not checked. freezeSmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -- ^ source -> Int -- ^ offset -> Int -- ^ length -> m (SmallArray a) -#if HAVE_SMALL_ARRAY freezeSmallArray (SmallMutableArray sma#) (I# i#) (I# j#) = primitive $ \s -> case freezeSmallArray# sma# i# j# s of (# s', sa# #) -> (# s', SmallArray sa# #) -#else -freezeSmallArray (SmallMutableArray ma) i j = - SmallArray `liftM` freezeArray ma i j -#endif {-# INLINE freezeSmallArray #-} -- | Render a mutable array immutable. @@ -311,33 +282,26 @@ freezeSmallArray (SmallMutableArray ma) i j = -- input array after freezing. unsafeFreezeSmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> m (SmallArray a) -#if HAVE_SMALL_ARRAY unsafeFreezeSmallArray (SmallMutableArray sma#) = primitive $ \s -> case unsafeFreezeSmallArray# sma# s of (# s', sa# #) -> (# s', SmallArray sa# #) -#else -unsafeFreezeSmallArray (SmallMutableArray ma) = - SmallArray `liftM` unsafeFreezeArray ma -#endif {-# INLINE unsafeFreezeSmallArray #-} -- | Create a mutable array corresponding to a slice of an immutable array. -- -- This operation copies the portion of the array to be thawed. +-- +-- /Note:/ The provided array should contain the full subrange +-- specified by the two Ints, but this is not checked. thawSmallArray :: PrimMonad m => SmallArray a -- ^ source -> Int -- ^ offset -> Int -- ^ length -> m (SmallMutableArray (PrimState m) a) -#if HAVE_SMALL_ARRAY thawSmallArray (SmallArray sa#) (I# o#) (I# l#) = primitive $ \s -> case thawSmallArray# sa# o# l# s of (# s', sma# #) -> (# s', SmallMutableArray sma# #) -#else -thawSmallArray (SmallArray a) off len = - SmallMutableArray `liftM` thawArray a off len -#endif {-# INLINE thawSmallArray #-} -- | Render an immutable array mutable. @@ -345,16 +309,14 @@ thawSmallArray (SmallArray a) off len = -- This operation performs no copying, so care must be taken with its use. unsafeThawSmallArray :: PrimMonad m => SmallArray a -> m (SmallMutableArray (PrimState m) a) -#if HAVE_SMALL_ARRAY unsafeThawSmallArray (SmallArray sa#) = primitive $ \s -> case unsafeThawSmallArray# sa# s of (# s', sma# #) -> (# s', SmallMutableArray sma# #) -#else -unsafeThawSmallArray (SmallArray a) = SmallMutableArray `liftM` unsafeThawArray a -#endif {-# INLINE unsafeThawSmallArray #-} -- | Copy a slice of an immutable array into a mutable array. +-- +-- /Note:/ this function does not do bounds or overlap checking. copySmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -- ^ destination @@ -363,16 +325,14 @@ copySmallArray -> Int -- ^ source offset -> Int -- ^ length -> m () -#if HAVE_SMALL_ARRAY copySmallArray (SmallMutableArray dst#) (I# do#) (SmallArray src#) (I# so#) (I# l#) = primitive_ $ copySmallArray# src# so# dst# do# l# -#else -copySmallArray (SmallMutableArray dst) i (SmallArray src) = copyArray dst i src -#endif {-# INLINE copySmallArray #-} -- | Copy a slice of one mutable array into another. +-- +-- /Note:/ this function does not do bounds or overlap checking. copySmallMutableArray :: PrimMonad m => SmallMutableArray (PrimState m) a -- ^ destination @@ -381,46 +341,78 @@ copySmallMutableArray -> Int -- ^ source offset -> Int -- ^ length -> m () -#if HAVE_SMALL_ARRAY copySmallMutableArray (SmallMutableArray dst#) (I# do#) (SmallMutableArray src#) (I# so#) (I# l#) = primitive_ $ copySmallMutableArray# src# so# dst# do# l# -#else -copySmallMutableArray (SmallMutableArray dst) i (SmallMutableArray src) = - copyMutableArray dst i src -#endif {-# INLINE copySmallMutableArray #-} +-- | The number of elements in an immutable array. sizeofSmallArray :: SmallArray a -> Int -#if HAVE_SMALL_ARRAY sizeofSmallArray (SmallArray sa#) = I# (sizeofSmallArray# sa#) +{-# INLINE sizeofSmallArray #-} + +-- | Get the number of elements in a mutable array. Unlike +-- 'sizeofSmallMutableArray', this function will be sure to produce the correct +-- result if 'SmallMutableArray' has been shrunk in place. Consider the following: +-- +-- @ +-- do +-- sa <- 'newSmallArray' 10 x +-- print $ 'sizeofSmallMutableArray' sa +-- 'shrinkSmallMutableArray' sa 5 +-- print $ sizeofSmallMutableArray sa +-- @ +-- +-- The compiler is well within its rights to eliminate the second size check +-- and print @10@ twice. However, 'getSizeofSmallMutableArray' will check +-- the size each time it's /executed/ (not /evaluated/), so it won't have this +-- problem: +-- +-- @ +-- do +-- sa <- 'newSmallArray' 10 x +-- print =<< getSizeofSmallMutableArray sa +-- 'shrinkSmallMutableArray' sa 5 +-- print =<< getSizeofSmallMutableArray sa +-- @ +-- +-- will certainly print @10@ and then @5@. +getSizeofSmallMutableArray + :: PrimMonad m + => SmallMutableArray (PrimState m) a + -> m Int +#if MIN_VERSION_base(4,14,0) +getSizeofSmallMutableArray (SmallMutableArray sa#) = primitive $ \s -> + case getSizeofSmallMutableArray# sa# s of + (# s', sz# #) -> (# s', I# sz# #) #else -sizeofSmallArray (SmallArray a) = sizeofArray a +getSizeofSmallMutableArray sa = pure $! sizeofSmallMutableArray sa #endif -{-# INLINE sizeofSmallArray #-} +{-# INLINE getSizeofSmallMutableArray #-} +-- | The number of elements in a mutable array. This should only be used +-- for arrays that are not shrunk in place. +-- +-- This is deprecated and will be removed in a future release. Use +-- 'getSizeofSmallMutableArray' instead. sizeofSmallMutableArray :: SmallMutableArray s a -> Int -#if HAVE_SMALL_ARRAY sizeofSmallMutableArray (SmallMutableArray sa#) = I# (sizeofSmallMutableArray# sa#) -#else -sizeofSmallMutableArray (SmallMutableArray ma) = sizeofMutableArray ma -#endif +{-# DEPRECATED sizeofSmallMutableArray "use getSizeofSmallMutableArray instead" #-} {-# INLINE sizeofSmallMutableArray #-} -- | This is the fastest, most straightforward way to traverse -- an array, but it only works correctly with a sufficiently -- "affine" 'PrimMonad' instance. In particular, it must only produce --- *one* result array. 'Control.Monad.Trans.List.ListT'-transformed +-- /one/ result array. 'Control.Monad.Trans.List.ListT'-transformed -- monads, for example, will not work right at all. traverseSmallArrayP :: PrimMonad m => (a -> m b) -> SmallArray a -> m (SmallArray b) -#if HAVE_SMALL_ARRAY traverseSmallArrayP f = \ !ary -> let !sz = sizeofSmallArray ary @@ -436,39 +428,24 @@ traverseSmallArrayP f = \ !ary -> in do mary <- newSmallArray sz badTraverseValue go 0 mary -#else -traverseSmallArrayP f (SmallArray ar) = SmallArray `liftM` traverseArrayP f ar -#endif {-# INLINE traverseSmallArrayP #-} -- | Strict map over the elements of the array. mapSmallArray' :: (a -> b) -> SmallArray a -> SmallArray b -#if HAVE_SMALL_ARRAY mapSmallArray' f sa = createSmallArray (length sa) (die "mapSmallArray'" "impossible") $ \smb -> fix ? 0 $ \go i -> when (i < length sa) $ do x <- indexSmallArrayM sa i let !y = f x - writeSmallArray smb i y *> go (i+1) -#else -mapSmallArray' f (SmallArray ar) = SmallArray (mapArray' f ar) -#endif + writeSmallArray smb i y *> go (i + 1) {-# INLINE mapSmallArray' #-} -#ifndef HAVE_SMALL_ARRAY -runSmallArray - :: (forall s. ST s (SmallMutableArray s a)) - -> SmallArray a -runSmallArray m = SmallArray $ runArray $ - m >>= \(SmallMutableArray mary) -> return mary - -#elif !MIN_VERSION_base(4,9,0) +-- | Execute the monadic action and freeze the resulting array. +-- +-- > runSmallArray m = runST $ m >>= unsafeFreezeSmallArray runSmallArray :: (forall s. ST s (SmallMutableArray s a)) -> SmallArray a -runSmallArray m = runST $ m >>= unsafeFreezeSmallArray - -#else -- This low-level business is designed to work with GHC's worker-wrapper -- transformation. A lot of the time, we don't actually need an Array -- constructor. By putting it on the outside, and being careful about @@ -476,9 +453,6 @@ runSmallArray m = runST $ m >>= unsafeFreezeSmallArray -- The only downside is that separately created 0-length arrays won't share -- their Array constructors, although they'll share their underlying -- Array#s. -runSmallArray - :: (forall s. ST s (SmallMutableArray s a)) - -> SmallArray a runSmallArray m = SmallArray (runSmallArray# m) runSmallArray# @@ -491,15 +465,21 @@ runSmallArray# m = case runRW# $ \s -> unST :: ST s a -> State# s -> (# State# s, a #) unST (GHCST.ST f) = f -#endif - -#if HAVE_SMALL_ARRAY --- See the comment on runSmallArray for why we use emptySmallArray#. +-- | Create an array of the given size with a default value, +-- apply the monadic function and freeze the result. If the +-- size is 0, return 'emptySmallArray' (rather than a new copy thereof). +-- +-- > createSmallArray 0 _ _ = emptySmallArray +-- > createSmallArray n x f = runSmallArray $ do +-- > mary <- newSmallArray n x +-- > f mary +-- > pure mary createSmallArray :: Int -> a -> (forall s. SmallMutableArray s a -> ST s ()) -> SmallArray a +-- See the comment on runSmallArray for why we use emptySmallArray#. createSmallArray 0 _ _ = SmallArray (emptySmallArray# (# #)) createSmallArray n x f = runSmallArray $ do mary <- newSmallArray n x @@ -513,6 +493,7 @@ emptySmallArray# _ = case emptySmallArray of SmallArray ar -> ar die :: String -> String -> a die fun problem = error $ "Data.Primitive.SmallArray." ++ fun ++ ": " ++ problem +-- | The empty 'SmallArray'. emptySmallArray :: SmallArray a emptySmallArray = runST $ newSmallArray 0 (die "emptySmallArray" "impossible") @@ -536,17 +517,11 @@ smallArrayLiftEq p sa1 sa2 = length sa1 == length sa2 && loop (length sa1 - 1) = True | (# x #) <- indexSmallArray## sa1 i , (# y #) <- indexSmallArray## sa2 i - = p x y && loop (i-1) + = p x y && loop (i - 1) -#if MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,4,0) -- | @since 0.6.4.0 instance Eq1 SmallArray where -#if MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,5,0) liftEq = smallArrayLiftEq -#else - eq1 = smallArrayLiftEq (==) -#endif -#endif instance Eq a => Eq (SmallArray a) where sa1 == sa2 = smallArrayLiftEq (==) sa1 sa2 @@ -563,18 +538,12 @@ smallArrayLiftCompare elemCompare a1 a2 = loop 0 | i < mn , (# x1 #) <- indexSmallArray## a1 i , (# x2 #) <- indexSmallArray## a2 i - = elemCompare x1 x2 `mappend` loop (i+1) + = elemCompare x1 x2 `mappend` loop (i + 1) | otherwise = compare (length a1) (length a2) -#if MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,4,0) -- | @since 0.6.4.0 instance Ord1 SmallArray where -#if MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,5,0) liftCompare = smallArrayLiftCompare -#else - compare1 = smallArrayLiftCompare compare -#endif -#endif -- | Lexicographic ordering. Subject to change between major versions. instance Ord a => Ord (SmallArray a) where @@ -590,7 +559,7 @@ instance Foldable SmallArray where go i | i == sz = z | (# x #) <- indexSmallArray## ary i - = f x (go (i+1)) + = f x (go (i + 1)) in go 0 {-# INLINE foldr #-} foldl f = \z !ary -> @@ -598,7 +567,7 @@ instance Foldable SmallArray where go i | i < 0 = z | (# x #) <- indexSmallArray## ary i - = f (go (i-1)) x + = f (go (i - 1)) x in go (sizeofSmallArray ary - 1) {-# INLINE foldl #-} foldr1 f = \ !ary -> @@ -607,7 +576,7 @@ instance Foldable SmallArray where go i = case indexSmallArray## ary i of (# x #) | i == sz -> x - | otherwise -> f x (go (i+1)) + | otherwise -> f x (go (i + 1)) in if sz < 0 then die "foldr1" "Empty SmallArray" else go 0 @@ -628,7 +597,7 @@ instance Foldable SmallArray where go i !acc | i == -1 = acc | (# x #) <- indexSmallArray## ary i - = go (i-1) (f x acc) + = go (i - 1) (f x acc) in go (sizeofSmallArray ary - 1) z {-# INLINE foldr' #-} foldl' f = \z !ary -> @@ -637,7 +606,7 @@ instance Foldable SmallArray where go i !acc | i == sz = acc | (# x #) <- indexSmallArray## ary i - = go (i+1) (f acc x) + = go (i + 1) (f acc x) in go 0 z {-# INLINE foldl' #-} null a = sizeofSmallArray a == 0 @@ -652,7 +621,7 @@ instance Foldable SmallArray where go i !e | i == sz = e | (# x #) <- indexSmallArray## ary i - = go (i+1) (max e x) + = go (i + 1) (max e x) {-# INLINE maximum #-} minimum ary | sz == 0 = die "minimum" "Empty SmallArray" | (# frst #) <- indexSmallArray## ary 0 @@ -661,14 +630,14 @@ instance Foldable SmallArray where go i !e | i == sz = e | (# x #) <- indexSmallArray## ary i - = go (i+1) (min e x) + = go (i + 1) (min e x) {-# INLINE minimum #-} sum = foldl' (+) 0 {-# INLINE sum #-} product = foldl' (*) 1 {-# INLINE product #-} -newtype STA a = STA {_runSTA :: forall s. SmallMutableArray# s a -> ST s (SmallArray a)} +newtype STA a = STA { _runSTA :: forall s. SmallMutableArray# s a -> ST s (SmallArray a) } runSTA :: Int -> STA a -> SmallArray a runSTA !sz = \ (STA m) -> runST $ newSmallArray_ sz >>= @@ -700,8 +669,8 @@ traverseSmallArray f = \ !ary -> writeSmallArray (SmallMutableArray mary) i b >> m mary) (f x) (go (i + 1)) in if len == 0 - then pure emptySmallArray - else runSTA len <$> go 0 + then pure emptySmallArray + else runSTA len <$> go 0 {-# INLINE [1] traverseSmallArray #-} {-# RULES @@ -718,7 +687,7 @@ instance Functor SmallArray where fix ? 0 $ \go i -> when (i < length sa) $ do x <- indexSmallArrayM sa i - writeSmallArray smb i (f x) *> go (i+1) + writeSmallArray smb i (f x) *> go (i + 1) {-# INLINE fmap #-} x <$ sa = createSmallArray (length sa) x noOp @@ -726,36 +695,36 @@ instance Functor SmallArray where instance Applicative SmallArray where pure x = createSmallArray 1 x noOp - sa *> sb = createSmallArray (la*lb) (die "*>" "impossible") $ \smb -> + sa *> sb = createSmallArray (la * lb) (die "*>" "impossible") $ \smb -> fix ? 0 $ \go i -> when (i < la) $ - copySmallArray smb 0 sb 0 lb *> go (i+1) + copySmallArray smb (i * lb) sb 0 lb *> go (i + 1) where - la = length sa ; lb = length sb + la = length sa; lb = length sb - a <* b = createSmallArray (sza*szb) (die "<*" "impossible") $ \ma -> + a <* b = createSmallArray (sza * szb) (die "<*" "impossible") $ \ma -> let fill off i e = when (i < szb) $ - writeSmallArray ma (off+i) e >> fill off (i+1) e + writeSmallArray ma (off + i) e >> fill off (i + 1) e go i = when (i < sza) $ do x <- indexSmallArrayM a i - fill (i*szb) 0 x - go (i+1) + fill (i * szb) 0 x + go (i + 1) in go 0 - where sza = sizeofSmallArray a ; szb = sizeofSmallArray b + where sza = sizeofSmallArray a; szb = sizeofSmallArray b - ab <*> a = createSmallArray (szab*sza) (die "<*>" "impossible") $ \mb -> + ab <*> a = createSmallArray (szab * sza) (die "<*>" "impossible") $ \mb -> let go1 i = when (i < szab) $ do f <- indexSmallArrayM ab i - go2 (i*sza) f 0 - go1 (i+1) + go2 (i * sza) f 0 + go1 (i + 1) go2 off f j = when (j < sza) $ do x <- indexSmallArrayM a j writeSmallArray mb (off + j) (f x) go2 off f (j + 1) in go1 0 - where szab = sizeofSmallArray ab ; sza = sizeofSmallArray a + where szab = sizeofSmallArray ab; sza = sizeofSmallArray a instance Alternative SmallArray where empty = emptySmallArray @@ -789,25 +758,25 @@ instance Monad SmallArray where return = pure (>>) = (*>) - sa >>= f = collect 0 EmptyStack (la-1) + sa >>= f = collect 0 EmptyStack (la - 1) where - la = length sa - collect sz stk i - | i < 0 = createSmallArray sz (die ">>=" "impossible") $ fill 0 stk - | (# x #) <- indexSmallArray## sa i - , let sb = f x - lsb = length sb - -- If we don't perform this check, we could end up allocating - -- a stack full of empty arrays if someone is filtering most - -- things out. So we refrain from pushing empty arrays. - = if lsb == 0 - then collect sz stk (i-1) - else collect (sz + lsb) (PushArray sb stk) (i-1) - - fill _ EmptyStack _ = return () - fill off (PushArray sb sbs) smb = - copySmallArray smb off sb 0 (length sb) - *> fill (off + length sb) sbs smb + la = length sa + collect sz stk i + | i < 0 = createSmallArray sz (die ">>=" "impossible") $ fill 0 stk + | (# x #) <- indexSmallArray## sa i + , let sb = f x + lsb = length sb + -- If we don't perform this check, we could end up allocating + -- a stack full of empty arrays if someone is filtering most + -- things out. So we refrain from pushing empty arrays. + = if lsb == 0 + then collect sz stk (i - 1) + else collect (sz + lsb) (PushArray sb stk) (i - 1) + + fill _ EmptyStack _ = return () + fill off (PushArray sb sbs) smb = + copySmallArray smb off sb 0 (length sb) + *> fill (off + length sb) sbs smb #if !(MIN_VERSION_base(4,13,0)) fail = Fail.fail @@ -827,7 +796,7 @@ zipW nm = \f sa sb -> let mn = length sa `min` length sb in x <- indexSmallArrayM sa i y <- indexSmallArrayM sb i writeSmallArray mc i (f x y) - go (i+1) + go (i + 1) {-# INLINE zipW #-} instance MonadZip SmallArray where @@ -842,13 +811,13 @@ instance MonadZip SmallArray where when (i < sz) $ case indexSmallArray sab i of (x, y) -> do writeSmallArray sma i x writeSmallArray smb i y - go $ i+1 + go (i + 1) (,) <$> unsafeFreezeSmallArray sma <*> unsafeFreezeSmallArray smb instance MonadFix SmallArray where mfix f = createSmallArray (sizeofSmallArray (f err)) - (die "mfix" "impossible") $ flip fix 0 $ + (die "mfix" "impossible") $ fix ? 0 $ \r !i !mary -> when (i < sz) $ do writeSmallArray mary i (fix (\xi -> f xi `indexSmallArray` i)) r (i + 1) mary @@ -856,24 +825,31 @@ instance MonadFix SmallArray where sz = sizeofSmallArray (f err) err = error "mfix for Data.Primitive.SmallArray applied to strict function." -#if MIN_VERSION_base(4,9,0) -- | @since 0.6.3.0 -instance Sem.Semigroup (SmallArray a) where +instance Semigroup (SmallArray a) where (<>) = (<|>) sconcat = mconcat . toList -#endif + stimes n arr = case compare n 0 of + LT -> die "stimes" "negative multiplier" + EQ -> empty + GT -> createSmallArray (n' * sizeofSmallArray arr) (die "stimes" "impossible") $ \sma -> + let go i = when (i < n') $ do + copySmallArray sma (i * sizeofSmallArray arr) arr 0 (sizeofSmallArray arr) + go (i + 1) + in go 0 + where n' = fromIntegral n :: Int instance Monoid (SmallArray a) where mempty = empty #if !(MIN_VERSION_base(4,11,0)) - mappend = (<|>) + mappend = (<>) #endif mconcat l = createSmallArray n (die "mconcat" "impossible") $ \ma -> let go !_ [ ] = return () go off (a:as) = copySmallArray ma off a 0 (sizeofSmallArray a) >> go (off + sizeofSmallArray a) as in go 0 l - where n = sum . fmap length $ l + where n = sum (fmap length l) instance IsList (SmallArray a) where type Item (SmallArray a) = a @@ -882,9 +858,8 @@ instance IsList (SmallArray a) where toList = Foldable.toList smallArrayLiftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> SmallArray a -> ShowS -smallArrayLiftShowsPrec elemShowsPrec elemListShowsPrec p sa = showParen (p > 10) $ - showString "fromListN " . shows (length sa) . showString " " - . listLiftShowsPrec elemShowsPrec elemListShowsPrec 11 (toList sa) +smallArrayLiftShowsPrec elemShowsPrec elemListShowsPrec _ sa = + listLiftShowsPrec elemShowsPrec elemListShowsPrec 11 (toList sa) -- this need to be included for older ghcs listLiftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> [a] -> ShowS @@ -893,40 +868,39 @@ listLiftShowsPrec _ sl _ = sl instance Show a => Show (SmallArray a) where showsPrec p sa = smallArrayLiftShowsPrec showsPrec showList p sa -#if MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,4,0) -- | @since 0.6.4.0 instance Show1 SmallArray where -#if MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,5,0) liftShowsPrec = smallArrayLiftShowsPrec -#else - showsPrec1 = smallArrayLiftShowsPrec showsPrec showList -#endif -#endif -smallArrayLiftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (SmallArray a) -smallArrayLiftReadsPrec _ listReadsPrec p = readParen (p > 10) . readP_to_S $ do - () <$ string "fromListN" - skipSpaces - n <- readS_to_P reads - skipSpaces - l <- readS_to_P listReadsPrec - return $ smallArrayFromListN n l +-- See Note [Forgiving Array Read Instance] +smallArrayLiftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (SmallArray a) +smallArrayLiftReadPrec _ read_list = + ( RdPrc.lift skipSpaces >> fmap fromList read_list ) + RdPrc.+++ + ( parens $ prec app_prec $ do + RdPrc.lift skipSpaces + tag <- RdPrc.lift lexTag + case tag of + FromListTag -> fromList <$> read_list + FromListNTag -> liftM2 fromListN readPrec read_list + ) + where + app_prec = 10 instance Read a => Read (SmallArray a) where - readsPrec = smallArrayLiftReadsPrec readsPrec readList + readPrec = smallArrayLiftReadPrec readPrec readListPrec -#if MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,4,0) -- | @since 0.6.4.0 instance Read1 SmallArray where -#if MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,5,0) - liftReadsPrec = smallArrayLiftReadsPrec +#if MIN_VERSION_base(4,10,0) + liftReadPrec = smallArrayLiftReadPrec #else - readsPrec1 = smallArrayLiftReadsPrec readsPrec readList -#endif + -- This is just the default implementation of liftReadsPrec, but + -- it is not present in older versions of base. + liftReadsPrec rp rl = RdPrc.readPrec_to_S $ + smallArrayLiftReadPrec (RdPrc.readS_to_Prec rp) (RdPrc.readS_to_Prec (const rl)) #endif - - smallArrayDataType :: DataType smallArrayDataType = mkDataType "Data.Primitive.SmallArray.SmallArray" [fromListConstr] @@ -946,12 +920,10 @@ instance (Typeable s, Typeable a) => Data (SmallMutableArray s a) where toConstr _ = die "toConstr" "SmallMutableArray" gunfold _ _ = die "gunfold" "SmallMutableArray" dataTypeOf _ = mkNoRepType "Data.Primitive.SmallArray.SmallMutableArray" -#endif -- | Create a 'SmallArray' from a list of a known length. If the length --- of the list does not match the given length, this throws an exception. +-- of the list does not match the given length, this throws an exception. smallArrayFromListN :: Int -> [a] -> SmallArray a -#if HAVE_SMALL_ARRAY smallArrayFromListN n l = createSmallArray n (die "smallArrayFromListN" "uninitialized element") $ \sma -> @@ -961,13 +933,46 @@ smallArrayFromListN n l = go !ix (x : xs) = if ix < n then do writeSmallArray sma ix x - go (ix+1) xs + go (ix + 1) xs else die "smallArrayFromListN" "list length greater than specified size" in go 0 l -#else -smallArrayFromListN n l = SmallArray (Array.fromListN n l) -#endif -- | Create a 'SmallArray' from a list. smallArrayFromList :: [a] -> SmallArray a smallArrayFromList l = smallArrayFromListN (length l) l + +#if MIN_VERSION_base(4,14,0) +-- | Shrink the mutable array in place. The size given must be equal to +-- or less than the current size of the array. This is not checked. +shrinkSmallMutableArray :: PrimMonad m + => SmallMutableArray (PrimState m) a + -> Int + -> m () +{-# inline shrinkSmallMutableArray #-} +shrinkSmallMutableArray (SmallMutableArray x) (I# n) = primitive + (\s0 -> case GHC.Exts.shrinkSmallMutableArray# x n s0 of + s1 -> (# s1, () #) + ) + +-- | Resize a mutable array to new specified size. The returned +-- 'SmallMutableArray' is either the original 'SmallMutableArray' +-- resized in-place or, if not possible, a newly allocated +-- 'SmallMutableArray' with the original content copied over. +-- +-- To avoid undefined behaviour, the original 'SmallMutableArray' +-- shall not be accessed anymore after a 'resizeSmallMutableArray' has +-- been performed. Moreover, no reference to the old one should be +-- kept in order to allow garbage collection of the original +-- 'SmallMutableArray' in case a new 'SmallMutableArray' had to be +-- allocated. +resizeSmallMutableArray :: PrimMonad m + => SmallMutableArray (PrimState m) a + -> Int -- ^ New size + -> a -- ^ Newly created slots initialized to this element. Only used when array is grown. + -> m (SmallMutableArray (PrimState m) a) +resizeSmallMutableArray (SmallMutableArray arr) (I# n) x = primitive + (\s0 -> case GHC.Exts.resizeSmallMutableArray# arr n x s0 of + (# s1, arr' #) -> (# s1, SmallMutableArray arr' #) + ) +{-# INLINE resizeSmallMutableArray #-} +#endif diff --git a/examples/primitive/Data/Primitive/Types.hs b/examples/primitive/Data/Primitive/Types.hs index 969e6e582..4bfcea9dc 100644 --- a/examples/primitive/Data/Primitive/Types.hs +++ b/examples/primitive/Data/Primitive/Types.hs @@ -1,9 +1,14 @@ -{-# LANGUAGE CPP, UnboxedTuples, MagicHash, DeriveDataTypeable #-} -{-# LANGUAGE GeneralizedNewtypeDeriving, StandaloneDeriving #-} +{-# LANGUAGE AllowAmbiguousTypes #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE ScopedTypeVariables #-} -#if __GLASGOW_HASKELL__ >= 800 +{-# LANGUAGE TypeApplications #-} + +#if __GLASGOW_HASKELL__ < 906 {-# LANGUAGE TypeInType #-} -{-# LANGUAGE DeriveGeneric #-} #endif #include "HsBaseConfig.h" @@ -16,66 +21,46 @@ -- Maintainer : Roman Leshchinskiy -- Portability : non-portable -- --- Basic types and classes for primitive array operations --- +-- Basic types and classes for primitive array operations. -module Data.Primitive.Types ( - Prim(..) - ,sizeOf, alignment, defaultSetByteArray#, defaultSetOffAddr# - ,PrimStorable(..) - ,Ptr(..) -) where +module Data.Primitive.Types + ( Prim(..) + , sizeOf, sizeOfType, alignment, alignmentOfType, defaultSetByteArray#, defaultSetOffAddr# + , PrimStorable(..) + , Ptr(..) + ) where import Control.Monad.Primitive import Data.Primitive.MachDeps import Data.Primitive.Internal.Operations +import Foreign.Ptr (IntPtr, intPtrToPtr, ptrToIntPtr, WordPtr, wordPtrToPtr, ptrToWordPtr) import Foreign.C.Types import System.Posix.Types +import Data.Complex -import GHC.Base ( - Int(..), Char(..), - ) -import GHC.Float ( - Float(..), Double(..) - ) -import GHC.Word ( - Word(..), Word8(..), Word16(..), Word32(..), Word64(..) - ) -import GHC.Int ( - Int8(..), Int16(..), Int32(..), Int64(..) - ) - -import GHC.Ptr ( - Ptr(..), FunPtr(..) - ) -import GHC.Stable ( - StablePtr(..) - ) - -import GHC.Exts -#if __GLASGOW_HASKELL__ >= 706 - hiding (setByteArray#) -#endif +import GHC.Word (Word8(..), Word16(..), Word32(..), Word64(..)) +import GHC.Int (Int8(..), Int16(..), Int32(..), Int64(..)) + +import GHC.Stable (StablePtr(..)) +import GHC.Exts hiding (setByteArray#) -import Data.Primitive.Internal.Compat ( isTrue# ) import Foreign.Storable (Storable) import qualified Foreign.Storable as FS +import GHC.IO (IO(..)) +import qualified GHC.Exts + import Control.Applicative (Const(..)) -#if MIN_VERSION_base(4,8,0) import Data.Functor.Identity (Identity(..)) import qualified Data.Monoid as Monoid -#endif -#if MIN_VERSION_base(4,6,0) -import Data.Ord (Down(..)) -#else -import GHC.Exts (Down(..)) -#endif -#if MIN_VERSION_base(4,9,0) import qualified Data.Semigroup as Semigroup +import Data.Proxy + +#if !MIN_VERSION_base(4,13,0) +import Data.Ord (Down(..)) #endif -- | Class of types supporting primitive array operations. This includes @@ -83,12 +68,31 @@ import qualified Data.Semigroup as Semigroup -- and interfacing with unmanaged memory (functions suffixed with @Addr#@). -- Endianness is platform-dependent. class Prim a where - - -- | Size of values of type @a@. The argument is not used. - sizeOf# :: a -> Int# - - -- | Alignment of values of type @a@. The argument is not used. + -- We use `Proxy` instead of `Proxy#`, since the latter doesn't work with GND for GHC <= 8.8. + + -- | The size of values of type @a@ in bytes. This has to be used with TypeApplications: @sizeOfType \@a@. + -- + -- @since 0.9.0.0 + sizeOfType# :: Proxy a -> Int# + sizeOfType# _ = sizeOf# (dummy :: a) + + -- | The size of values of type @a@ in bytes. The argument is not used. + -- + -- It is recommended to use 'sizeOfType#' instead. + sizeOf# :: a -> Int# + sizeOf# _ = sizeOfType# (Proxy :: Proxy a) + + -- | The alignment of values of type @a@ in bytes. This has to be used with TypeApplications: @alignmentOfType \@a@. + -- + -- @since 0.9.0.0 + alignmentOfType# :: Proxy a -> Int# + alignmentOfType# _ = alignment# (dummy :: a) + + -- | The alignment of values of type @a@ in bytes. The argument is not used. + -- + -- It is recommended to use 'alignmentOfType#' instead. alignment# :: a -> Int# + alignment# _ = alignmentOfType# (Proxy :: Proxy a) -- | Read a value from the array. The offset is in elements of type -- @a@ rather than in bytes. @@ -104,7 +108,14 @@ class Prim a where -- | Fill a slice of the mutable array with a value. The offset and length -- of the chunk are in elements of type @a@ rather than in bytes. - setByteArray# :: MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s + setByteArray# + :: MutableByteArray# s + -> Int# -- ^ offset + -> Int# -- ^ length + -> a + -> State# s + -> State# s + setByteArray# = defaultSetByteArray# -- | Read a value from a memory position given by an address and an offset. -- The memory block the address refers to must be immutable. The offset is in @@ -121,33 +132,106 @@ class Prim a where -- | Fill a memory block given by an address, an offset and a length. -- The offset and length are in elements of type @a@ rather than in bytes. - setOffAddr# :: Addr# -> Int# -> Int# -> a -> State# s -> State# s + setOffAddr# + :: Addr# + -> Int# -- ^ offset + -> Int# -- ^ length + -> a + -> State# s + -> State# s + setOffAddr# = defaultSetOffAddr# + + {-# MINIMAL (sizeOfType# | sizeOf#), (alignmentOfType# | alignment#), indexByteArray#, readByteArray#, writeByteArray#, + indexOffAddr#, readOffAddr#, writeOffAddr# #-} + +-- | A dummy value of type @a@. +dummy :: a +dummy = errorWithoutStackTrace "Data.Primitive.Types: implementation mistake in `Prim` instance" +{-# NOINLINE dummy #-} + +-- | The size of values of type @a@ in bytes. This has to be used with TypeApplications: @sizeOfType \@a@. +-- +-- >>> :set -XTypeApplications +-- >>> import Data.Int (Int32) +-- >>> sizeOfType @Int32 +-- 4 +-- +-- @since 0.9.0.0 +sizeOfType :: forall a. Prim a => Int +sizeOfType = I# (sizeOfType# (Proxy :: Proxy a)) --- | Size of values of type @a@. The argument is not used. +-- | The size of values of type @a@ in bytes. The argument is not used. +-- +-- It is recommended to use 'sizeOfType' instead. -- -- This function has existed since 0.1, but was moved from 'Data.Primitive' --- to 'Data.Primitive.Types' in version 0.6.3.0 +-- to 'Data.Primitive.Types' in version 0.6.3.0. sizeOf :: Prim a => a -> Int sizeOf x = I# (sizeOf# x) --- | Alignment of values of type @a@. The argument is not used. +-- | The alignment of values of type @a@ in bytes. This has to be used with TypeApplications: @alignmentOfType \@a@. +-- +-- @since 0.9.0.0 +alignmentOfType :: forall a. Prim a => Int +alignmentOfType = I# (alignmentOfType# (Proxy :: Proxy a)) + +-- | The alignment of values of type @a@ in bytes. The argument is not used. +-- +-- It is recommended to use 'alignmentOfType' instead. -- -- This function has existed since 0.1, but was moved from 'Data.Primitive' --- to 'Data.Primitive.Types' in version 0.6.3.0 +-- to 'Data.Primitive.Types' in version 0.6.3.0. alignment :: Prim a => a -> Int alignment x = I# (alignment# x) +-- | @since 0.9.0.0 +instance Prim a => Prim (Complex a) where + sizeOf# _ = 2# *# sizeOf# (undefined :: a) + alignment# _ = alignment# (undefined :: a) + indexByteArray# arr# i# = + let x = indexByteArray# arr# (2# *# i#) + y = indexByteArray# arr# (2# *# i# +# 1#) + in x :+ y + readByteArray# arr# i# = + \s0 -> case readByteArray# arr# (2# *# i#) s0 of + (# s1#, x #) -> case readByteArray# arr# (2# *# i# +# 1#) s1# of + (# s2#, y #) -> (# s2#, x :+ y #) + writeByteArray# arr# i# (a :+ b) = + \s0 -> case writeByteArray# arr# (2# *# i#) a s0 of + s1 -> case writeByteArray# arr# (2# *# i# +# 1#) b s1 of + s2 -> s2 + indexOffAddr# addr# i# = + let x = indexOffAddr# addr# (2# *# i#) + y = indexOffAddr# addr# (2# *# i# +# 1#) + in x :+ y + readOffAddr# addr# i# = + \s0 -> case readOffAddr# addr# (2# *# i#) s0 of + (# s1, x #) -> case readOffAddr# addr# (2# *# i# +# 1#) s1 of + (# s2, y #) -> (# s2, x :+ y #) + writeOffAddr# addr# i# (a :+ b) = + \s0 -> case writeOffAddr# addr# (2# *# i#) a s0 of + s1 -> case writeOffAddr# addr# (2# *# i# +# 1#) b s1 of + s2 -> s2 + {-# INLINE sizeOf# #-} + {-# INLINE alignment# #-} + {-# INLINE indexByteArray# #-} + {-# INLINE readByteArray# #-} + {-# INLINE writeByteArray# #-} + {-# INLINE indexOffAddr# #-} + {-# INLINE readOffAddr# #-} + {-# INLINE writeOffAddr# #-} + -- | An implementation of 'setByteArray#' that calls 'writeByteArray#' -- to set each element. This is helpful when writing a 'Prim' instance --- for a multi-word data type for which there is no cpu-accelerated way +-- for a multi-word data type for which there is no CPU-accelerated way -- to broadcast a value to contiguous memory. It is typically used -- alongside 'defaultSetOffAddr#'. For example: -- -- > data Trip = Trip Int Int Int -- > -- > instance Prim Trip --- > sizeOf# _ = 3# *# sizeOf# (undefined :: Int) --- > alignment# _ = alignment# (undefined :: Int) +-- > sizeOfType# _ = 3# *# sizeOfType# (proxy# :: Proxy# Int) +-- > alignmentOfType# _ = alignmentOfType# (proxy# :: Proxy# Int) -- > indexByteArray# arr# i# = ... -- > readByteArray# arr# i# = ... -- > writeByteArray# arr# i# (Trip a b c) = @@ -197,8 +281,8 @@ defaultSetOffAddr# addr# i# len# ident = go 0# newtype PrimStorable a = PrimStorable { getPrimStorable :: a } instance Prim a => Storable (PrimStorable a) where - sizeOf _ = sizeOf (undefined :: a) - alignment _ = alignment (undefined :: a) + sizeOf _ = sizeOfType @a + alignment _ = alignmentOfType @a peekElemOff (Ptr addr#) (I# i#) = primitive $ \s0# -> case readOffAddr# addr# i# s0# of (# s1, x #) -> (# s1, PrimStorable x #) @@ -206,42 +290,58 @@ instance Prim a => Storable (PrimStorable a) where writeOffAddr# addr# i# a s# #define derivePrim(ty, ctr, sz, align, idx_arr, rd_arr, wr_arr, set_arr, idx_addr, rd_addr, wr_addr, set_addr) \ -instance Prim (ty) where { \ - sizeOf# _ = unI# sz \ -; alignment# _ = unI# align \ -; indexByteArray# arr# i# = ctr (idx_arr arr# i#) \ -; readByteArray# arr# i# s# = case rd_arr arr# i# s# of \ - { (# s1#, x# #) -> (# s1#, ctr x# #) } \ -; writeByteArray# arr# i# (ctr x#) s# = wr_arr arr# i# x# s# \ -; setByteArray# arr# i# n# (ctr x#) s# \ - = let { i = fromIntegral (I# i#) \ - ; n = fromIntegral (I# n#) \ - } in \ - case unsafeCoerce# (internal (set_arr arr# i n x#)) s# of \ - { (# s1#, _ #) -> s1# } \ - \ -; indexOffAddr# addr# i# = ctr (idx_addr addr# i#) \ -; readOffAddr# addr# i# s# = case rd_addr addr# i# s# of \ - { (# s1#, x# #) -> (# s1#, ctr x# #) } \ -; writeOffAddr# addr# i# (ctr x#) s# = wr_addr addr# i# x# s# \ -; setOffAddr# addr# i# n# (ctr x#) s# \ - = let { i = fromIntegral (I# i#) \ - ; n = fromIntegral (I# n#) \ - } in \ +instance Prim (ty) where { \ + sizeOfType# _ = unI# sz \ +; alignmentOfType# _ = unI# align \ +; indexByteArray# arr# i# = ctr (idx_arr arr# i#) \ +; readByteArray# arr# i# s# = case rd_arr arr# i# s# of \ + { (# s1#, x# #) -> (# s1#, ctr x# #) } \ +; writeByteArray# arr# i# (ctr x#) s# = wr_arr arr# i# x# s# \ +; setByteArray# arr# i# n# (ctr x#) s# \ + = let { i = fromIntegral (I# i#) \ + ; n = fromIntegral (I# n#) \ + } in \ + case unsafeCoerce# (internal (set_arr arr# i n x#)) s# of \ + { (# s1#, _ #) -> s1# } \ + \ +; indexOffAddr# addr# i# = ctr (idx_addr addr# i#) \ +; readOffAddr# addr# i# s# = case rd_addr addr# i# s# of \ + { (# s1#, x# #) -> (# s1#, ctr x# #) } \ +; writeOffAddr# addr# i# (ctr x#) s# = wr_addr addr# i# x# s# \ +; setOffAddr# addr# i# n# (ctr x#) s# \ + = let { i = fromIntegral (I# i#) \ + ; n = fromIntegral (I# n#) \ + } in \ case unsafeCoerce# (internal (set_addr addr# i n x#)) s# of \ - { (# s1#, _ #) -> s1# } \ -; {-# INLINE sizeOf# #-} \ -; {-# INLINE alignment# #-} \ -; {-# INLINE indexByteArray# #-} \ -; {-# INLINE readByteArray# #-} \ -; {-# INLINE writeByteArray# #-} \ -; {-# INLINE setByteArray# #-} \ -; {-# INLINE indexOffAddr# #-} \ -; {-# INLINE readOffAddr# #-} \ -; {-# INLINE writeOffAddr# #-} \ -; {-# INLINE setOffAddr# #-} \ + { (# s1#, _ #) -> s1# } \ +; {-# INLINE sizeOfType# #-} \ +; {-# INLINE alignmentOfType# #-} \ +; {-# INLINE indexByteArray# #-} \ +; {-# INLINE readByteArray# #-} \ +; {-# INLINE writeByteArray# #-} \ +; {-# INLINE setByteArray# #-} \ +; {-# INLINE indexOffAddr# #-} \ +; {-# INLINE readOffAddr# #-} \ +; {-# INLINE writeOffAddr# #-} \ +; {-# INLINE setOffAddr# #-} \ } +#if __GLASGOW_HASKELL__ >= 902 +liberate# :: State# s -> State# r +liberate# = unsafeCoerce# +shimmedSetWord8Array# :: MutableByteArray# s -> Int -> Int -> Word8# -> IO () +shimmedSetWord8Array# m (I# off) (I# len) w = IO (\s -> (# liberate# (GHC.Exts.setByteArray# m off len (GHC.Exts.word2Int# (GHC.Exts.word8ToWord# w)) (liberate# s)), () #)) +shimmedSetInt8Array# :: MutableByteArray# s -> Int -> Int -> Int8# -> IO () +shimmedSetInt8Array# m (I# off) (I# len) i = IO (\s -> (# liberate# (GHC.Exts.setByteArray# m off len (GHC.Exts.int8ToInt# i) (liberate# s)), () #)) +#else +liberate# :: State# s -> State# r +liberate# = unsafeCoerce# +shimmedSetWord8Array# :: MutableByteArray# s -> Int -> Int -> Word# -> IO () +shimmedSetWord8Array# m (I# off) (I# len) w = IO (\s -> (# liberate# (GHC.Exts.setByteArray# m off len (GHC.Exts.word2Int# w) (liberate# s)), () #)) +shimmedSetInt8Array# :: MutableByteArray# s -> Int -> Int -> Int# -> IO () +shimmedSetInt8Array# m (I# off) (I# len) i = IO (\s -> (# liberate# (GHC.Exts.setByteArray# m off len i (liberate# s)), () #)) +#endif + unI# :: Int -> Int# unI# (I# n#) = n# @@ -249,7 +349,7 @@ derivePrim(Word, W#, sIZEOF_WORD, aLIGNMENT_WORD, indexWordArray#, readWordArray#, writeWordArray#, setWordArray#, indexWordOffAddr#, readWordOffAddr#, writeWordOffAddr#, setWordOffAddr#) derivePrim(Word8, W8#, sIZEOF_WORD8, aLIGNMENT_WORD8, - indexWord8Array#, readWord8Array#, writeWord8Array#, setWord8Array#, + indexWord8Array#, readWord8Array#, writeWord8Array#, shimmedSetWord8Array#, indexWord8OffAddr#, readWord8OffAddr#, writeWord8OffAddr#, setWord8OffAddr#) derivePrim(Word16, W16#, sIZEOF_WORD16, aLIGNMENT_WORD16, indexWord16Array#, readWord16Array#, writeWord16Array#, setWord16Array#, @@ -264,7 +364,7 @@ derivePrim(Int, I#, sIZEOF_INT, aLIGNMENT_INT, indexIntArray#, readIntArray#, writeIntArray#, setIntArray#, indexIntOffAddr#, readIntOffAddr#, writeIntOffAddr#, setIntOffAddr#) derivePrim(Int8, I8#, sIZEOF_INT8, aLIGNMENT_INT8, - indexInt8Array#, readInt8Array#, writeInt8Array#, setInt8Array#, + indexInt8Array#, readInt8Array#, writeInt8Array#, shimmedSetInt8Array#, indexInt8OffAddr#, readInt8OffAddr#, writeInt8OffAddr#, setInt8OffAddr#) derivePrim(Int16, I16#, sIZEOF_INT16, aLIGNMENT_INT16, indexInt16Array#, readInt16Array#, writeInt16Array#, setInt16Array#, @@ -390,11 +490,47 @@ deriving instance Prim CTimer #endif deriving instance Prim Fd +-- Andrew Martin: The instances for WordPtr and IntPtr are written out by +-- hand in a tedious way. We cannot use GND because the data constructors for +-- these types were not available before GHC 8.2. The CPP for generating code +-- for the Int and Word types does not work here. There is a way to clean this +-- up a little with CPP, and if anyone wants to do that, go for it. In the +-- meantime, I am going to ship this with the instances written out by hand. + +-- | @since 0.7.1.0 +instance Prim WordPtr where + sizeOfType# _ = sizeOfType# (Proxy :: Proxy (Ptr ())) + alignmentOfType# _ = alignmentOfType# (Proxy :: Proxy (Ptr ())) + indexByteArray# a i = ptrToWordPtr (indexByteArray# a i) + readByteArray# a i s0 = case readByteArray# a i s0 of + (# s1, p #) -> (# s1, ptrToWordPtr p #) + writeByteArray# a i wp = writeByteArray# a i (wordPtrToPtr wp) + setByteArray# a i n wp = setByteArray# a i n (wordPtrToPtr wp) + indexOffAddr# a i = ptrToWordPtr (indexOffAddr# a i) + readOffAddr# a i s0 = case readOffAddr# a i s0 of + (# s1, p #) -> (# s1, ptrToWordPtr p #) + writeOffAddr# a i wp = writeOffAddr# a i (wordPtrToPtr wp) + setOffAddr# a i n wp = setOffAddr# a i n (wordPtrToPtr wp) + +-- | @since 0.7.1.0 +instance Prim IntPtr where + sizeOfType# _ = sizeOfType# (Proxy :: Proxy (Ptr ())) + alignmentOfType# _ = alignmentOfType# (Proxy :: Proxy (Ptr ())) + indexByteArray# a i = ptrToIntPtr (indexByteArray# a i) + readByteArray# a i s0 = case readByteArray# a i s0 of + (# s1, p #) -> (# s1, ptrToIntPtr p #) + writeByteArray# a i wp = writeByteArray# a i (intPtrToPtr wp) + setByteArray# a i n wp = setByteArray# a i n (intPtrToPtr wp) + indexOffAddr# a i = ptrToIntPtr (indexOffAddr# a i) + readOffAddr# a i s0 = case readOffAddr# a i s0 of + (# s1, p #) -> (# s1, ptrToIntPtr p #) + writeOffAddr# a i wp = writeOffAddr# a i (intPtrToPtr wp) + setOffAddr# a i n wp = setOffAddr# a i n (intPtrToPtr wp) + -- | @since 0.6.5.0 deriving instance Prim a => Prim (Const a b) -- | @since 0.6.5.0 deriving instance Prim a => Prim (Down a) -#if MIN_VERSION_base(4,8,0) -- | @since 0.6.5.0 deriving instance Prim a => Prim (Identity a) -- | @since 0.6.5.0 @@ -403,8 +539,6 @@ deriving instance Prim a => Prim (Monoid.Dual a) deriving instance Prim a => Prim (Monoid.Sum a) -- | @since 0.6.5.0 deriving instance Prim a => Prim (Monoid.Product a) -#endif -#if MIN_VERSION_base(4,9,0) -- | @since 0.6.5.0 deriving instance Prim a => Prim (Semigroup.First a) -- | @since 0.6.5.0 @@ -413,4 +547,3 @@ deriving instance Prim a => Prim (Semigroup.Last a) deriving instance Prim a => Prim (Semigroup.Min a) -- | @since 0.6.5.0 deriving instance Prim a => Prim (Semigroup.Max a) -#endif diff --git a/examples/primitive/README.md b/examples/primitive/README.md new file mode 100644 index 000000000..9834b5cf5 --- /dev/null +++ b/examples/primitive/README.md @@ -0,0 +1,6 @@ +The `primitive` package [![Build Status](https://travis-ci.org/haskell/primitive.png?branch=master)](https://travis-ci.org/haskell/primitive) +======================= + +This package provides various primitive memory-related operations for Haskell. + +See [`primitive` on Hackage](http://hackage.haskell.org/package/primitive) for more information. diff --git a/examples/primitive/bench/Array/Traverse/Closure.hs b/examples/primitive/bench/Array/Traverse/Closure.hs new file mode 100644 index 000000000..4a7e64e7b --- /dev/null +++ b/examples/primitive/bench/Array/Traverse/Closure.hs @@ -0,0 +1,49 @@ +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE MagicHash #-} + +module Array.Traverse.Closure + ( traversePoly + ) where + +import Control.Applicative +import Control.Monad.ST +import Data.Primitive.Array +import GHC.Exts (Int(..),MutableArray#) + +{-# INLINE traversePoly #-} +traversePoly + :: Applicative f + => (a -> f b) + -> Array a + -> f (Array b) +traversePoly f = \ !ary -> + let + !len = sizeofArray ary + go !i + | i == len = pure $ STA $ \mary -> unsafeFreezeArray (MutableArray mary) + | (# x #) <- indexArray## ary i + = liftA2 (\b (STA m) -> STA $ \mary -> + writeArray (MutableArray mary) i b >> m mary) + (f x) (go (i + 1)) + in if len == 0 + then pure mempty + else runSTA len <$> go 0 + +badTraverseValue :: a +badTraverseValue = die "traversePoly" "bad indexing" +{-# NOINLINE badTraverseValue #-} + +die :: String -> String -> a +die fun problem = error $ "Array.Traverse.Closure" ++ fun ++ ": " ++ problem + +newtype STA a = STA {_runSTA :: forall s. MutableArray# s a -> ST s (Array a)} + +runSTA :: Int -> STA a -> Array a +runSTA !sz = \ (STA m) -> runST $ newArray_ sz >>= \ ar -> m (marray# ar) +{-# INLINE runSTA #-} + +newArray_ :: Int -> ST s (MutableArray s a) +newArray_ !n = newArray n badTraverseValue + diff --git a/examples/primitive/bench/Array/Traverse/Compose.hs b/examples/primitive/bench/Array/Traverse/Compose.hs new file mode 100644 index 000000000..b730852f8 --- /dev/null +++ b/examples/primitive/bench/Array/Traverse/Compose.hs @@ -0,0 +1,47 @@ +module Array.Traverse.Compose + ( traversePoly + , traverseMono + ) where + +import Data.Functor.Compose +import Data.Primitive.Array + +{-# INLINE traversePoly #-} +traversePoly + :: Applicative f + => (a -> f b) + -> Array a + -> f (Array b) +traversePoly f ary = runST $ do + let !sz = sizeofArray ary + mary <- newArray sz + let go !i = do + + !len = sizeofArray ary + go !i + | i == len = pure $ STA $ \mary -> unsafeFreezeArray (MutableArray mary) + | (# x #) <- indexArray## ary i + = liftA2 (\b (STA m) -> STA $ \mary -> + writeArray (MutableArray mary) i b >> m mary) + (f x) (go (i + 1)) + in if len == 0 + then pure emptyArray + else runSTA len <$> go 0 + +badTraverseValue :: a +badTraverseValue = die "traversePoly" "bad indexing" +{-# NOINLINE badTraverseValue #-} + +die :: String -> String -> a +die fun problem = error $ "Array.Traverse.Closure" ++ fun ++ ": " ++ problem + +newtype STA a = STA {_runSTA :: forall s. MutableArray# s a -> ST s (Array a)} + +runSTA :: Int -> STA a -> Array a +runSTA !sz = \ (STA m) -> runST $ newArray_ sz >>= \ ar -> m (marray# ar) +{-# INLINE runSTA #-} + +newArray_ :: Int -> ST s (MutableArray s a) +newArray_ !n = newArray n badTraverseValue + + diff --git a/examples/primitive/bench/Array/Traverse/Unsafe.hs b/examples/primitive/bench/Array/Traverse/Unsafe.hs new file mode 100644 index 000000000..e7615a4fd --- /dev/null +++ b/examples/primitive/bench/Array/Traverse/Unsafe.hs @@ -0,0 +1,48 @@ +{-# LANGUAGE BangPatterns #-} + +module Array.Traverse.Unsafe + ( traversePoly + , traverseMono + ) where + +import Control.Monad.ST +import Control.Monad.Trans.State.Strict +import Control.Monad.Primitive +import Data.Primitive.Array + +{-# INLINE traversePoly #-} +traversePoly + :: PrimMonad m + => (a -> m b) + -> Array a + -> m (Array b) +traversePoly f = \ !ary -> + let + !sz = sizeofArray ary + go !i !mary + | i == sz + = unsafeFreezeArray mary + | otherwise + = do + a <- indexArrayM ary i + b <- f a + writeArray mary i b + go (i + 1) mary + in do + mary <- newArray sz badTraverseValue + go 0 mary + +badTraverseValue :: a +badTraverseValue = die "traversePoly" "bad indexing" +{-# NOINLINE badTraverseValue #-} + +die :: String -> String -> a +die fun problem = error $ "Array.Traverse.Unsafe" ++ fun ++ ": " ++ problem + +-- Included to make it easy to inspect GHC Core that results +-- from inlining traversePoly. +traverseMono :: + (Int -> StateT Word (ST s) Int) + -> Array Int + -> StateT Word (ST s) (Array Int) +traverseMono f x = traversePoly f x diff --git a/examples/primitive/bench/ByteArray/Compare.hs b/examples/primitive/bench/ByteArray/Compare.hs new file mode 100644 index 000000000..ddebbe3b0 --- /dev/null +++ b/examples/primitive/bench/ByteArray/Compare.hs @@ -0,0 +1,96 @@ +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE ScopedTypeVariables #-} + +module ByteArray.Compare + ( benchmark + , argumentSmall + , argumentMedium + , argumentLarge + ) where + +import Data.Primitive +import Data.Word +import Control.Monad +import Control.Monad.ST (runST) +import GHC.Exts (fromList) + +-- This takes the cross product of the argument with itself +-- and compares each pair of combined ByteArrays. In other words, +-- it compare every ByteArray to every other ByteArray (including +-- itself). This is does efficiently and should not allocate +-- any memory. +benchmark :: Array ByteArray -> Int +benchmark !uarr = outer 0 + where + sz = sizeofArray uarr + outer :: Int -> Int + outer !v0 = + let go !v !ix = if ix < sz + then go (inner v (indexArray uarr ix)) (ix + 1) + else v + in go v0 0 + inner :: Int -> ByteArray -> Int + inner !v0 !barr = + let go !v !ix = if ix < sz + then + let !y = case compare barr (indexArray uarr ix) of + LT -> (-1) + EQ -> 0 + GT -> 1 + in go (v + y) (ix + 1) + else v + in go v0 0 + +-- This is an array of all byte arrays consistent of the bytes 0 and 1 +-- bewteen length 0 and 7 inclusive: +-- +-- [] +-- [0] +-- [1] +-- [0,0] +-- [0,1] +-- ... +-- [1,1,1,1,1,1,0] +-- [1,1,1,1,1,1,1] +-- +-- These are very small byte arrays. All of them are smaller than a +-- cache line. A comparison function that uses the FFI may perform +-- worse on such inputs than one that does not. +argumentSmall :: Array ByteArray +argumentSmall = runST $ do + let (ys :: [[Word8]]) = foldMap (\n -> replicateM n [0,1]) (enumFromTo 0 7) + marr <- newArray (length ys) undefined + let go !_ [] = return () + go !ix (x : xs) = do + writeArray marr ix (fromList x) + go (ix + 1) xs + go 0 ys + unsafeFreezeArray marr + + +-- This is an array of all byte arrays consistent of the bytes 0 and 1 +-- bewteen length 0 and 7 inclusive. However, they are all padded on the +-- left by the same 256 bytes. Comparing any two of them will require +-- walking and comparing the first 256 bytes. +argumentMedium :: Array ByteArray +argumentMedium = runST $ do + let (ys :: [[Word8]]) = foldMap (\n -> map (enumFromTo 0 255 ++) (replicateM n [0,1])) (enumFromTo 0 7) + marr <- newArray (length ys) undefined + let go !_ [] = return () + go !ix (x : xs) = do + writeArray marr ix (fromList x) + go (ix + 1) xs + go 0 ys + unsafeFreezeArray marr + +-- Same thing but with left padding of 1024 bytes. +argumentLarge :: Array ByteArray +argumentLarge = runST $ do + let (ys :: [[Word8]]) = foldMap (\n -> map (concat (replicate 4 (enumFromTo 0 255)) ++) (replicateM n [0,1])) (enumFromTo 0 7) + marr <- newArray (length ys) undefined + let go !_ [] = return () + go !ix (x : xs) = do + writeArray marr ix (fromList x) + go (ix + 1) xs + go 0 ys + unsafeFreezeArray marr diff --git a/examples/primitive/bench/PrimArray/Compare.hs b/examples/primitive/bench/PrimArray/Compare.hs new file mode 100644 index 000000000..562da72b1 --- /dev/null +++ b/examples/primitive/bench/PrimArray/Compare.hs @@ -0,0 +1,58 @@ +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE ScopedTypeVariables #-} + +module PrimArray.Compare + ( benchmarkLt + , benchmarkLtDef + , benchmarkLte + , benchmarkLteDef + , argumentA + , argumentB + ) 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 +benchmarkLtDef a b = case compare a b of + LT -> True + _ -> False + +benchmarkLteDef :: PrimArray Int -> PrimArray Int -> Bool +benchmarkLteDef a b = case compare a b of + GT -> False + _ -> True + +benchmarkLt :: PrimArray Int -> PrimArray Int -> Bool +benchmarkLt a b = + let !sz1 = sizeofPrimArray a + !sz2 = sizeofPrimArray b + !sz = min sz1 sz2 + loop !i + | i < sz = if indexPrimArray a i < indexPrimArray b i + then True + else loop (i + 1) + | otherwise = sz1 < sz2 + in loop 0 + +benchmarkLte :: PrimArray Int -> PrimArray Int -> Bool +benchmarkLte a b = + let !sz1 = sizeofPrimArray a + !sz2 = sizeofPrimArray b + !sz = min sz1 sz2 + loop !i + | i < sz = if indexPrimArray a i <= indexPrimArray b i + then loop (i + 1) + else False + | otherwise = sz1 < sz2 + in loop 0 + +argumentA :: PrimArray Int +argumentA = fromList (enumFromTo 0 8000 ++ [55]) + +argumentB :: PrimArray Int +argumentB = fromList (enumFromTo 0 8000 ++ [56]) + diff --git a/examples/primitive/bench/PrimArray/Traverse.hs b/examples/primitive/bench/PrimArray/Traverse.hs new file mode 100644 index 000000000..0e2f1d549 --- /dev/null +++ b/examples/primitive/bench/PrimArray/Traverse.hs @@ -0,0 +1,23 @@ +module PrimArray.Traverse + ( benchmarkApplicative + , benchmarkPrimMonad + , argument + ) where + +import Control.Monad.ST (runST) +import Control.Monad.Trans.Maybe (MaybeT(..)) +import Data.Bool (bool) +import Data.Primitive.PrimArray +import GHC.Exts (fromList) + +benchmarkApplicative :: PrimArray Int -> Maybe (PrimArray Int) +benchmarkApplicative xs = traversePrimArray (\x -> bool Nothing (Just (x + 1)) (x > 0)) xs + +benchmarkPrimMonad :: PrimArray Int -> Maybe (PrimArray Int) +benchmarkPrimMonad xs = runST $ runMaybeT $ traversePrimArrayP + (\x -> bool (MaybeT (return Nothing)) (MaybeT (return (Just (x + 1)))) (x > 0)) + xs + +argument :: PrimArray Int +argument = fromList (enumFromTo 1 10000) + diff --git a/examples/primitive/bench/main.hs b/examples/primitive/bench/main.hs new file mode 100644 index 000000000..caa3d67e2 --- /dev/null +++ b/examples/primitive/bench/main.hs @@ -0,0 +1,69 @@ +{-# 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 +import Control.Monad.Trans.State.Strict + +-- These are fixed implementations of certain operations. In the event +-- that primitive changes its implementation of a function, these +-- implementations stay the same. They are helpful for ensuring that +-- something that is a performance win in one version of GHC doesn't +-- become a regression later. They are also helpful for evaluating +-- how well different implementation hold up in different scenarios. +import qualified Array.Traverse.Unsafe +import qualified Array.Traverse.Closure + +-- These are particular scenarios that are tested against the +-- implementations actually used by primitive. +import qualified ByteArray.Compare +import qualified PrimArray.Compare +import qualified PrimArray.Traverse + +main :: IO () +main = defaultMain + [ bgroup "Array" + [ bgroup "implementations" + [ bgroup "traverse" + [ bench "closure" (nf (\x -> runST (runStateT (Array.Traverse.Closure.traversePoly cheap x) 0)) numbers) + , bench "unsafe" (nf (\x -> runST (runStateT (Array.Traverse.Unsafe.traversePoly cheap x) 0)) numbers) + ] + ] + ] + , bgroup "ByteArray" + [ bgroup "compare" + [ bench "small" (whnf ByteArray.Compare.benchmark ByteArray.Compare.argumentSmall) + , bench "medium" (whnf ByteArray.Compare.benchmark ByteArray.Compare.argumentMedium) + , bench "large" (whnf ByteArray.Compare.benchmark ByteArray.Compare.argumentLarge) + ] + ] + , bgroup "PrimArray" + [ bgroup "traverse" + [ bgroup "Maybe" + [ bench "Applicative" (whnf PrimArray.Traverse.benchmarkApplicative PrimArray.Traverse.argument) + , bench "PrimMonad" (whnf PrimArray.Traverse.benchmarkPrimMonad PrimArray.Traverse.argument) + ] + ] + , bgroup "implementations" + [ bgroup "less-than" + [ bench "default" (whnf (PrimArray.Compare.benchmarkLtDef PrimArray.Compare.argumentA) PrimArray.Compare.argumentB) + , bench "override" (whnf (PrimArray.Compare.benchmarkLt PrimArray.Compare.argumentA) PrimArray.Compare.argumentB) + ] + , bgroup "less-than-equal" + [ bench "default" (whnf (PrimArray.Compare.benchmarkLteDef PrimArray.Compare.argumentA) PrimArray.Compare.argumentB) + , bench "override" (whnf (PrimArray.Compare.benchmarkLte PrimArray.Compare.argumentA) PrimArray.Compare.argumentB) + ] + ] + ] + ] + +cheap :: Int -> StateT Int (ST s) Int +cheap i = modify (\x -> x + i) >> return (i * i) + +numbers :: Array Int +numbers = arrayFromList (enumFromTo 0 10000) diff --git a/examples/primitive/cabal.project b/examples/primitive/cabal.project new file mode 100644 index 000000000..465441983 --- /dev/null +++ b/examples/primitive/cabal.project @@ -0,0 +1,7 @@ +packages: primitive.cabal + + +package primitive + ghc-options: -Wall -Wcompat + +allow-newer: tagged-0.8.6.1:template-haskell diff --git a/examples/primitive/cbits/primitive-memops.c b/examples/primitive/cbits/primitive-memops.c index 81b1d6f57..680273e19 100644 --- a/examples/primitive/cbits/primitive-memops.c +++ b/examples/primitive/cbits/primitive-memops.c @@ -40,14 +40,19 @@ int hsprimitive_memcmp( HsWord8 *s1, HsWord8 *s2, size_t n ) return memcmp( s1, s2, n ); } -void hsprimitive_memset_Word8 (HsWord8 *p, ptrdiff_t off, size_t n, HsWord x) +int hsprimitive_memcmp_offset( HsWord8 *s1, HsInt off1, HsWord8 *s2, HsInt off2, size_t n ) +{ + return memcmp( s1 + off1, s2 + off2, n ); +} + +void hsprimitive_memset_Word8 (HsWord8 *p, ptrdiff_t off, size_t n, HsWord8 x) { memset( (char *)(p+off), x, n ); } /* MEMSET(HsWord8, HsWord) */ -MEMSET(Word16, HsWord) -MEMSET(Word32, HsWord) +MEMSET(Word16, HsWord16) +MEMSET(Word32, HsWord32) MEMSET(Word64, HsWord64) MEMSET(Word, HsWord) MEMSET(Ptr, HsPtr) diff --git a/examples/primitive/cbits/primitive-memops.h b/examples/primitive/cbits/primitive-memops.h index d7c3396f8..10c0931c5 100644 --- a/examples/primitive/cbits/primitive-memops.h +++ b/examples/primitive/cbits/primitive-memops.h @@ -1,23 +1,25 @@ #ifndef haskell_primitive_memops_h #define haskell_primitive_memops_h +// N.B. GHC RTS headers want to come first, lest things break on Windows. +#include + #include #include -#include -void hsprimitive_memcpy( void *dst, ptrdiff_t doff, void *src, ptrdiff_t soff, size_t len ); -void hsprimitive_memmove( void *dst, ptrdiff_t doff, void *src, ptrdiff_t soff, size_t len ); -int hsprimitive_memcmp( HsWord8 *s1, HsWord8 *s2, size_t n ); +void hsprimitive_memcpy(void *dst, ptrdiff_t doff, void *src, ptrdiff_t soff, size_t len); +void hsprimitive_memmove(void *dst, ptrdiff_t doff, void *src, ptrdiff_t soff, size_t len); +int hsprimitive_memcmp(HsWord8 *s1, HsWord8 *s2, size_t n); +int hsprimitive_memcmp_offset(HsWord8 *s1, HsInt off1, HsWord8 *s2, HsInt off2, size_t n); -void hsprimitive_memset_Word8 (HsWord8 *, ptrdiff_t, size_t, HsWord); -void hsprimitive_memset_Word16 (HsWord16 *, ptrdiff_t, size_t, HsWord); -void hsprimitive_memset_Word32 (HsWord32 *, ptrdiff_t, size_t, HsWord); -void hsprimitive_memset_Word64 (HsWord64 *, ptrdiff_t, size_t, HsWord64); -void hsprimitive_memset_Word (HsWord *, ptrdiff_t, size_t, HsWord); -void hsprimitive_memset_Ptr (HsPtr *, ptrdiff_t, size_t, HsPtr); -void hsprimitive_memset_Float (HsFloat *, ptrdiff_t, size_t, HsFloat); -void hsprimitive_memset_Double (HsDouble *, ptrdiff_t, size_t, HsDouble); -void hsprimitive_memset_Char (HsChar *, ptrdiff_t, size_t, HsChar); +void hsprimitive_memset_Word8(HsWord8 *, ptrdiff_t, size_t, HsWord8); +void hsprimitive_memset_Word16(HsWord16 *, ptrdiff_t, size_t, HsWord16); +void hsprimitive_memset_Word32(HsWord32 *, ptrdiff_t, size_t, HsWord32); +void hsprimitive_memset_Word64(HsWord64 *, ptrdiff_t, size_t, HsWord64); +void hsprimitive_memset_Word(HsWord *, ptrdiff_t, size_t, HsWord); +void hsprimitive_memset_Ptr(HsPtr *, ptrdiff_t, size_t, HsPtr); +void hsprimitive_memset_Float(HsFloat *, ptrdiff_t, size_t, HsFloat); +void hsprimitive_memset_Double(HsDouble *, ptrdiff_t, size_t, HsDouble); +void hsprimitive_memset_Char(HsChar *, ptrdiff_t, size_t, HsChar); #endif - diff --git a/examples/primitive/changelog.md b/examples/primitive/changelog.md index 02d72a40f..3b96affbe 100644 --- a/examples/primitive/changelog.md +++ b/examples/primitive/changelog.md @@ -1,3 +1,136 @@ +## Changes in version 0.9.0.0 + + * Add `withByteArrayContents`, `withMutableByteArrayContents`, + `withPrimArrayContents`, `withMutablePrimArrayContents`. + + * Fix signature of `keepAlive`. + + * Remove re-export of `fromList` and `fromListN` from `Data.Primitive.Array`. + + * Use `mutableByteArrayContents#` in GHC 9.2+ + + * Add `Prim` instance for `Complex`. + + * Add `getSizeofSmallMutableArray` that wraps `getSizeofSmallMutableArray#` + from `GHC.Exts`. + + * Add default definitions for the `setByteArray#` and `setOffAddr#` methods, + so they don't need to be defined explicitly anymore. + + * Add standalone `sizeOfType`/`alignmentOfType` (recommended over `sizeOf`/`alignment`) + and `Prim` class methods `sizeOfType#`/`alignmentOfType#` (recommended over `sizeOf#`/`alignment#`) + + * Change `Show` instances of `PrimArray`, `Array`, and `SmallArray`. These + previously used the `fromListN n [...]` form, but they now used the more + terse `[...]` form. + + * Correct the `Read` instances of `Array` and `SmallArray`. These instances + are supposed to be able to handle all three of these forms: `fromList [...]`, + `fromListN n [...]`, and `[...]`. They had been rejected the last form, but + this mistake was discovered by the test suite when the Show instances were + changed. + +## Changes in version 0.8.0.0 + + * Add `resizeSmallMutableArray` that wraps `resizeSmallMutableArray#` from + `GHC.Exts`. + + * New module `Data.Primitive.PrimVar`. This is essentially `PrimArray` with + element length 1. For types with `Prim` instances, this is a drop-in + replacement for `MutVar` with fewer indirections. + + * `PrimArray`'s type argument has been given a nominal role instead of a phantom role. + This is a breaking change. + + * Add `readCharArray`, `writeCharArray`, `indexCharArray` for operating on + 8-bit characters in a byte array. + + * When building with `base-4.17` and newer, re-export the `ByteArray` and + `MutableByteArray` types from `base` instead of defining them in this + library. This does not change the user-facing interface of + `Data.Primitive.ByteArray`. + + * Add `keepAlive` that wraps `keepAlive#` for GHC 9.2 and newer. It + falls back to using `touch` for older GHCs. + +## Changes in version 0.7.4.0 + + * Add Lift instances (#332) + + * Expose `copyPtrToMutablePrimArray` + + * Improve definitions for stimes (#326) + + * Support GHC 9.4. Note: GHC 9.4 is not released at the time of + primitive-0.7.4.0's release, so this support might be reverted by + a hackage metadata revision if things change. + + * Drop support for GHC 7.10 + +## Changes in version 0.7.3.0 + + * Correct implementations of `*>` for `Array` and `SmallArray`. + + * Drop support for GHC < 7.10 + + * Export `runByteArray` and `runPrimArray`. + + * Export `createArray` and `createSmallArray`. + + * Export `emptyByteArray`, `emptyPrimArray`, `emptyArray` and `emptySmallArray`. + +## Changes in version 0.7.2.0 + + * Add `thawByteArray` and `thawPrimArray`. + + * Changed the `Show` instance of `ByteArray`, so that all 8-bit words + are rendered as two digits. For example, display `0x0D` instead of `0xD`. + +## Changes in version 0.7.1.0 + + * Introduce convenience class `MonadPrim` and `MonadPrimBase`. + + * Add `PrimMonad` and `PrimBase` instances for `Lazy.ST` (GHC >= 8.2). + thanks to Avi Dessauer (@Avi-D-coder) for this first contribution + + * Add `freezeByteArray` and `freezePrimArray`. + + * Add `compareByteArrays`. + + * Add `shrinkMutableByteArray`. + + * Add `Eq` instances for `MutableByteArray` and `MutablePrimArray`. + by Andrew Martin + + * Add functions for manipulating pinned Prim Arrays + by Andrew Martin + + * Add `copyPtrToMutableByteArray`. + + * Add `NFData` instances for `ByteArray`, `MutableByteArray`, + `PrimArray` and `MutablePrimArray`. + by Callan McGill + + * Add `shrinkSmallMutableArray`. + + * Add `clonePrimArray` and `cloneMutablePrimArray`. + + * Add `cloneMutableByteArray` and `cloneByteArray`. + + * Add `Prim` instances for `WordPtr` and `IntPtr`. + + * Add `NFData` instances for `Array` and `SmallArray`. + by Callan McGill + + * Add `copyByteArrayToPtr` and `copyMutableByteArrayToPtr`. + + * Export `arrayFromList` and `arrayFromListN`. + +## Changes in version 0.7.0.1 + + * Allow building with GHC 8.12. + Thanks Ryan GL Scott for this and every compat patch over time. + ## Changes in version 0.7.0.0 * Remove `Addr` data type, lifted code should use `Ptr a` now diff --git a/examples/primitive/primitive.cabal b/examples/primitive/primitive.cabal new file mode 100644 index 000000000..57ecfe98b --- /dev/null +++ b/examples/primitive/primitive.cabal @@ -0,0 +1,123 @@ +Cabal-Version: 2.0 +Name: primitive +Version: 0.9.0.0 +License: BSD3 +License-File: LICENSE + +Author: Roman Leshchinskiy +Maintainer: libraries@haskell.org +Copyright: (c) Roman Leshchinskiy 2009-2012 +Homepage: https://github.com/haskell/primitive +Bug-Reports: https://github.com/haskell/primitive/issues +Category: Data +Synopsis: Primitive memory-related operations +Build-Type: Simple +Description: This package provides various primitive memory-related operations. + +Extra-Source-Files: changelog.md + test/*.hs + test/LICENSE + +Tested-With: + GHC == 8.0.2 + GHC == 8.2.2 + GHC == 8.4.4 + GHC == 8.6.5 + GHC == 8.8.4 + GHC == 8.10.7 + GHC == 9.0.2 + GHC == 9.2.5 + GHC == 9.4.4 + +Library + Default-Language: Haskell2010 + Default-Extensions: + TypeOperators + Other-Extensions: + BangPatterns, CPP, DeriveDataTypeable, + MagicHash, TypeFamilies, UnboxedTuples, UnliftedFFITypes + + Exposed-Modules: + Control.Monad.Primitive + Data.Primitive + Data.Primitive.MachDeps + Data.Primitive.Types + Data.Primitive.Array + Data.Primitive.ByteArray + Data.Primitive.PrimArray + Data.Primitive.SmallArray + Data.Primitive.Ptr + Data.Primitive.MutVar + Data.Primitive.MVar + Data.Primitive.PrimVar + + Other-Modules: + Data.Primitive.Internal.Operations + Data.Primitive.Internal.Read + + Build-Depends: base >= 4.9 && < 4.20 + , deepseq >= 1.1 && < 1.6 + , transformers >= 0.5 && < 0.7 + , template-haskell >= 2.11 + + if impl(ghc >= 9.2) + cpp-options: -DHAVE_KEEPALIVE + + if impl(ghc < 9.4) + build-depends: data-array-byte >= 0.1 && < 0.1.1 + + Ghc-Options: -O2 + + Include-Dirs: cbits + Install-Includes: primitive-memops.h + includes: primitive-memops.h + c-sources: cbits/primitive-memops.c + if !os(solaris) + cc-options: -ftree-vectorize + if arch(i386) || arch(x86_64) + cc-options: -msse2 + +test-suite test-qc + Default-Language: Haskell2010 + hs-source-dirs: test + test/src + main-is: Main.hs + Other-Modules: PrimLaws + type: exitcode-stdio-1.0 + build-depends: base + , base-orphans + , ghc-prim + , primitive + , quickcheck-classes-base >= 0.6 && <0.7 + , QuickCheck >= 2.13 && < 2.15 + , tasty ^>= 1.2 || ^>= 1.3 || ^>= 1.4 + , tasty-quickcheck + , tagged + , transformers >= 0.5 + , transformers-compat + + cpp-options: -DHAVE_UNARY_LAWS + ghc-options: -O2 + +benchmark bench + Default-Language: Haskell2010 + hs-source-dirs: bench + main-is: main.hs + type: exitcode-stdio-1.0 + ghc-options: -O2 + other-modules: + Array.Traverse.Closure + Array.Traverse.Unsafe + ByteArray.Compare + PrimArray.Compare + PrimArray.Traverse + build-depends: + base + , primitive + , deepseq + , tasty-bench + , transformers >= 0.5 + +source-repository head + type: git + location: https://github.com/haskell/primitive diff --git a/examples/primitive/test/main.hs b/examples/primitive/test/Main.hs similarity index 73% rename from examples/primitive/test/main.hs rename to examples/primitive/test/Main.hs index 1ce98ae8e..8e813cff5 100644 --- a/examples/primitive/test/main.hs +++ b/examples/primitive/test/Main.hs @@ -6,6 +6,7 @@ {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE TypeApplications #-} {-# OPTIONS_GHC -fno-warn-orphans #-} @@ -18,6 +19,7 @@ import Control.Monad import Control.Monad.ST +import Data.Complex import Data.Primitive import Data.Word import Data.Proxy (Proxy(..)) @@ -26,24 +28,13 @@ import GHC.IO import GHC.Exts import Data.Function (on) import Control.Applicative (Const(..)) -import PrimLawsWIP (primLaws) +import PrimLaws (primLaws) -#if !(MIN_VERSION_base(4,8,0)) -import Data.Monoid (Monoid(..)) -#endif -#if MIN_VERSION_base(4,8,0) import Data.Functor.Identity (Identity(..)) import qualified Data.Monoid as Monoid -#endif -#if MIN_VERSION_base(4,6,0) import Data.Ord (Down(..)) -#else -import GHC.Exts (Down(..)) -#endif -#if MIN_VERSION_base(4,9,0) -import Data.Semigroup (stimes) +import Data.Semigroup (stimes, stimesMonoid) import qualified Data.Semigroup as Semigroup -#endif #if !(MIN_VERSION_base(4,11,0)) import Data.Monoid ((<>)) #endif @@ -53,11 +44,11 @@ import Foreign.Storable (Storable) import Data.Orphans () import Test.Tasty (defaultMain,testGroup,TestTree) -import Test.QuickCheck (Arbitrary,Arbitrary1,Gen,(===),CoArbitrary,Function) +import Test.QuickCheck (Arbitrary,Arbitrary1,Gen,CoArbitrary,Function,(===),(==>)) import qualified Test.Tasty.QuickCheck as TQC import qualified Test.QuickCheck as QC -import qualified Test.QuickCheck.Classes as QCC -import qualified Test.QuickCheck.Classes.IsList as QCCL +import qualified Test.QuickCheck.Classes.Base as QCC +import qualified Test.QuickCheck.Classes.Base.IsList as QCCL import qualified Data.List as L main :: IO () @@ -70,57 +61,75 @@ main = do , lawsToTest (QCC.ordLaws (Proxy :: Proxy (Array Int))) , lawsToTest (QCC.monoidLaws (Proxy :: Proxy (Array Int))) , lawsToTest (QCC.showReadLaws (Proxy :: Proxy (Array Int))) -#if MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,4,0) - , lawsToTest (QCC.functorLaws (Proxy1 :: Proxy1 Array)) - , lawsToTest (QCC.applicativeLaws (Proxy1 :: Proxy1 Array)) - , lawsToTest (QCC.monadLaws (Proxy1 :: Proxy1 Array)) - , lawsToTest (QCC.foldableLaws (Proxy1 :: Proxy1 Array)) - , lawsToTest (QCC.traversableLaws (Proxy1 :: Proxy1 Array)) -#endif -#if MIN_VERSION_base(4,7,0) + , lawsToTest (QCC.functorLaws (Proxy :: Proxy Array)) + , lawsToTest (QCC.applicativeLaws (Proxy :: Proxy Array)) + , lawsToTest (QCC.alternativeLaws (Proxy :: Proxy Array)) + , lawsToTest (QCC.monadLaws (Proxy :: Proxy Array)) + , lawsToTest (QCC.monadZipLaws (Proxy :: Proxy Array)) + , lawsToTest (QCC.monadPlusLaws (Proxy :: Proxy Array)) + , lawsToTest (QCC.foldableLaws (Proxy :: Proxy Array)) + , lawsToTest (QCC.traversableLaws (Proxy :: Proxy Array)) , lawsToTest (QCC.isListLaws (Proxy :: Proxy (Array Int))) , TQC.testProperty "mapArray'" (QCCL.mapProp int16 int32 mapArray') -#endif + , TQC.testProperty "*>" $ \(xs :: Array Int) (ys :: Array Int) -> toList (xs *> ys) === (toList xs *> toList ys) + , TQC.testProperty "<*" $ \(xs :: Array Int) (ys :: Array Int) -> toList (xs <* ys) === (toList xs <* toList ys) + , lawsToTest (QCC.semigroupLaws (Proxy :: Proxy (Array Int))) + , TQC.testProperty "stimes" $ \(QC.NonNegative (n :: Int)) (xs :: Array Int) -> stimes n xs == stimesMonoid n xs ] , testGroup "SmallArray" [ lawsToTest (QCC.eqLaws (Proxy :: Proxy (SmallArray Int))) , lawsToTest (QCC.ordLaws (Proxy :: Proxy (SmallArray Int))) , lawsToTest (QCC.monoidLaws (Proxy :: Proxy (SmallArray Int))) , lawsToTest (QCC.showReadLaws (Proxy :: Proxy (Array Int))) -#if MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,4,0) - , lawsToTest (QCC.functorLaws (Proxy1 :: Proxy1 SmallArray)) - , lawsToTest (QCC.applicativeLaws (Proxy1 :: Proxy1 SmallArray)) - , lawsToTest (QCC.monadLaws (Proxy1 :: Proxy1 SmallArray)) - , lawsToTest (QCC.foldableLaws (Proxy1 :: Proxy1 SmallArray)) - , lawsToTest (QCC.traversableLaws (Proxy1 :: Proxy1 SmallArray)) -#endif -#if MIN_VERSION_base(4,7,0) + , lawsToTest (QCC.functorLaws (Proxy :: Proxy SmallArray)) + , lawsToTest (QCC.applicativeLaws (Proxy :: Proxy SmallArray)) + , lawsToTest (QCC.alternativeLaws (Proxy :: Proxy SmallArray)) + , lawsToTest (QCC.monadLaws (Proxy :: Proxy SmallArray)) + , lawsToTest (QCC.monadZipLaws (Proxy :: Proxy SmallArray)) + , lawsToTest (QCC.monadPlusLaws (Proxy :: Proxy SmallArray)) + , lawsToTest (QCC.foldableLaws (Proxy :: Proxy SmallArray)) + , lawsToTest (QCC.traversableLaws (Proxy :: Proxy SmallArray)) , lawsToTest (QCC.isListLaws (Proxy :: Proxy (SmallArray Int))) , TQC.testProperty "mapSmallArray'" (QCCL.mapProp int16 int32 mapSmallArray') -#endif + , TQC.testProperty "*>" $ \(xs :: SmallArray Int) (ys :: SmallArray Int) -> toList (xs *> ys) === (toList xs *> toList ys) + , TQC.testProperty "<*" $ \(xs :: SmallArray Int) (ys :: SmallArray Int) -> toList (xs <* ys) === (toList xs <* toList ys) + , lawsToTest (QCC.semigroupLaws (Proxy :: Proxy (SmallArray Int))) + , TQC.testProperty "stimes" $ \(QC.NonNegative (n :: Int)) (xs :: SmallArray Int) -> stimes n xs == stimesMonoid n xs ] , testGroup "ByteArray" [ testGroup "Ordering" [ TQC.testProperty "equality" byteArrayEqProp , TQC.testProperty "compare" byteArrayCompareProp + , testGroup "Filling" + [ TQC.testProperty "Int8" (setByteArrayProp (Proxy :: Proxy Int8)) + , TQC.testProperty "Int16" (setByteArrayProp (Proxy :: Proxy Int16)) + , TQC.testProperty "Int32" (setByteArrayProp (Proxy :: Proxy Int32)) + , TQC.testProperty "Int64" (setByteArrayProp (Proxy :: Proxy Int64)) + , TQC.testProperty "Int" (setByteArrayProp (Proxy :: Proxy Int)) + , TQC.testProperty "Word8" (setByteArrayProp (Proxy :: Proxy Word8)) + , TQC.testProperty "Word16" (setByteArrayProp (Proxy :: Proxy Word16)) + , TQC.testProperty "Word32" (setByteArrayProp (Proxy :: Proxy Word32)) + , TQC.testProperty "Word64" (setByteArrayProp (Proxy :: Proxy Word64)) + , TQC.testProperty "Word" (setByteArrayProp (Proxy :: Proxy Word)) ] + ] , testGroup "Resize" [ TQC.testProperty "shrink" byteArrayShrinkProp , TQC.testProperty "grow" byteArrayGrowProp ] , lawsToTest (QCC.eqLaws (Proxy :: Proxy ByteArray)) , lawsToTest (QCC.ordLaws (Proxy :: Proxy ByteArray)) + , lawsToTest (QCC.monoidLaws (Proxy :: Proxy ByteArray)) , lawsToTest (QCC.showReadLaws (Proxy :: Proxy (Array Int))) -#if MIN_VERSION_base(4,7,0) , lawsToTest (QCC.isListLaws (Proxy :: Proxy ByteArray)) , TQC.testProperty "foldrByteArray" (QCCL.foldrProp word8 foldrByteArray) -#endif + , lawsToTest (QCC.semigroupLaws (Proxy :: Proxy ByteArray)) + , TQC.testProperty "stimes" $ \(QC.NonNegative (n :: Int)) (xs :: ByteArray) -> stimes n xs == stimesMonoid n xs ] , testGroup "PrimArray" [ lawsToTest (QCC.eqLaws (Proxy :: Proxy (PrimArray Word16))) , lawsToTest (QCC.ordLaws (Proxy :: Proxy (PrimArray Word16))) , lawsToTest (QCC.monoidLaws (Proxy :: Proxy (PrimArray Word16))) -#if MIN_VERSION_base(4,7,0) , lawsToTest (QCC.isListLaws (Proxy :: Proxy (PrimArray Word16))) , TQC.testProperty "foldrPrimArray" (QCCL.foldrProp int16 foldrPrimArray) , TQC.testProperty "foldrPrimArray'" (QCCL.foldrProp int16 foldrPrimArray') @@ -145,20 +154,18 @@ main = do , TQC.testProperty "mapMaybePrimArray" (QCCL.mapMaybeProp int16 int32 mapMaybePrimArray) , TQC.testProperty "mapMaybePrimArrayA" (QCCL.mapMaybeMProp int16 int32 mapMaybePrimArrayA) , TQC.testProperty "mapMaybePrimArrayP" (QCCL.mapMaybeMProp int16 int32 mapMaybePrimArrayP) -#endif + , lawsToTest (QCC.semigroupLaws (Proxy :: Proxy (PrimArray Word16))) + , TQC.testProperty "stimes" $ \(QC.NonNegative (n :: Int)) (xs :: PrimArray Word16) -> stimes n xs == stimesMonoid n xs ] - - - - ,testGroup "DefaultSetMethod" + , testGroup "DefaultSetMethod" [ lawsToTest (primLaws (Proxy :: Proxy DefaultSetMethod)) ] #if __GLASGOW_HASKELL__ >= 805 - ,testGroup "PrimStorable" + , testGroup "PrimStorable" [ lawsToTest (QCC.storableLaws (Proxy :: Proxy Derived)) ] #endif - ,testGroup "Prim" + , testGroup "Prim" [ renameLawsToTest "Word" (primLaws (Proxy :: Proxy Word)) , renameLawsToTest "Word8" (primLaws (Proxy :: Proxy Word8)) , renameLawsToTest "Word16" (primLaws (Proxy :: Proxy Word16)) @@ -171,32 +178,25 @@ main = do , renameLawsToTest "Int64" (primLaws (Proxy :: Proxy Int64)) , renameLawsToTest "Const" (primLaws (Proxy :: Proxy (Const Int16 Int16))) , renameLawsToTest "Down" (primLaws (Proxy :: Proxy (Down Int16))) -#if MIN_VERSION_base(4,8,0) , renameLawsToTest "Identity" (primLaws (Proxy :: Proxy (Identity Int16))) , renameLawsToTest "Dual" (primLaws (Proxy :: Proxy (Monoid.Dual Int16))) , renameLawsToTest "Sum" (primLaws (Proxy :: Proxy (Monoid.Sum Int16))) , renameLawsToTest "Product" (primLaws (Proxy :: Proxy (Monoid.Product Int16))) -#endif -#if MIN_VERSION_base(4,9,0) , renameLawsToTest "First" (primLaws (Proxy :: Proxy (Semigroup.First Int16))) , renameLawsToTest "Last" (primLaws (Proxy :: Proxy (Semigroup.Last Int16))) , renameLawsToTest "Min" (primLaws (Proxy :: Proxy (Semigroup.Min Int16))) , renameLawsToTest "Max" (primLaws (Proxy :: Proxy (Semigroup.Max Int16))) -#endif - + , renameLawsToTest "Complex" (primLaws (Proxy :: Proxy (Complex Double))) ] - ] deriving instance Arbitrary a => Arbitrary (Down a) -- Const, Dual, Sum, Product: all have Arbitrary instances defined -- in QuickCheck itself -#if MIN_VERSION_base(4,9,0) deriving instance Arbitrary a => Arbitrary (Semigroup.First a) deriving instance Arbitrary a => Arbitrary (Semigroup.Last a) deriving instance Arbitrary a => Arbitrary (Semigroup.Min a) deriving instance Arbitrary a => Arbitrary (Semigroup.Max a) -#endif word8 :: Proxy Word8 word8 = Proxy @@ -208,6 +208,24 @@ int32 :: Proxy Int32 int32 = Proxy +setByteArrayProp :: forall a. (Prim a, Eq a, Arbitrary a, Show a) => Proxy a -> QC.Property +setByteArrayProp _ = QC.property $ \(QC.NonNegative (n :: Int)) (QC.NonNegative (off :: Int)) (QC.NonNegative (len :: Int)) (x :: a) (y :: a) -> + (off < n && off + len <= n) ==> + -- We use PrimArray in this test because it makes it easier to + -- get the element-vs-byte distinction right. + let actual = runST $ do + m <- newPrimArray n + forM_ (enumFromTo 0 (n - 1)) $ \ix -> writePrimArray m ix x + setPrimArray m off len y + unsafeFreezePrimArray m + expected = runST $ do + m <- newPrimArray n + forM_ (enumFromTo 0 (n - 1)) $ \ix -> writePrimArray m ix x + forM_ (enumFromTo off (off + len - 1)) $ \ix -> writePrimArray m ix y + unsafeFreezePrimArray m + in expected === actual + + -- Tests that using resizeByteArray to shrink a byte array produces -- the same results as calling Data.List.take on the list that the -- byte array corresponds to. @@ -217,8 +235,8 @@ byteArrayShrinkProp = QC.property $ \(QC.NonNegative (n :: Int)) (QC.NonNegative small = min n m xs = intsLessThan large ys = byteArrayFromList xs - largeBytes = large * sizeOf (undefined :: Int) - smallBytes = small * sizeOf (undefined :: Int) + largeBytes = large * sizeOfType @Int + smallBytes = small * sizeOfType @Int expected = byteArrayFromList (L.take small xs) actual = runST $ do mzs0 <- newByteArray largeBytes @@ -239,14 +257,14 @@ byteArrayGrowProp = QC.property $ \(QC.NonNegative (n :: Int)) (QC.NonNegative ( xs2 = intsLessThan (large - small) ys1 = byteArrayFromList xs1 ys2 = byteArrayFromList xs2 - largeBytes = large * sizeOf (undefined :: Int) - smallBytes = small * sizeOf (undefined :: Int) + largeBytes = large * sizeOfType @Int + smallBytes = small * sizeOfType @Int expected = byteArrayFromList (xs1 ++ xs2) actual = runST $ do mzs0 <- newByteArray smallBytes copyByteArray mzs0 0 ys1 0 smallBytes mzs1 <- resizeMutableByteArray mzs0 largeBytes - copyByteArray mzs1 smallBytes ys2 0 ((large - small) * sizeOf (undefined :: Int)) + copyByteArray mzs1 smallBytes ys2 0 ((large - small) * sizeOfType @Int) unsafeFreezeByteArray mzs1 in expected === actual @@ -296,9 +314,6 @@ byteArrayEqProp = QC.property $ \(xs :: [Word8]) (ys :: [Word8]) -> compareLengthFirst :: [Word8] -> [Word8] -> Ordering compareLengthFirst xs ys = (compare `on` length) xs ys <> compare xs ys --- on GHC 7.4, Proxy is not polykinded, so we need this instead. -data Proxy1 (f :: * -> *) = Proxy1 - lawsToTest :: QCC.Laws -> TestTree lawsToTest (QCC.Laws name pairs) = testGroup name (map (uncurry TQC.testProperty) pairs) @@ -327,8 +342,17 @@ testByteArray = do arr3 = mkByteArray ([0xde, 0xad, 0xbe, 0xee] :: [Word8]) arr4 = mkByteArray ([0xde, 0xad, 0xbe, 0xdd] :: [Word8]) arr5 = mkByteArray ([0xde, 0xad, 0xbe, 0xef, 0xde, 0xad, 0xbe, 0xdd] :: [Word8]) + arr6 = mkByteArray ([0xde, 0xad, 0x00, 0x01, 0xb0] :: [Word8]) when (show arr1 /= "[0xde, 0xad, 0xbe, 0xef]") $ fail $ "ByteArray Show incorrect: "++show arr1 + when (show arr6 /= "[0xde, 0xad, 0x00, 0x01, 0xb0]") $ + fail $ "ByteArray Show incorrect: "++ show arr6 + when (compareByteArrays arr3 1 arr4 1 3 /= GT) $ + fail $ "arr3[1,3] should be greater than arr4[1,3]" + when (compareByteArrays arr3 0 arr4 1 3 /= GT) $ + fail $ "arr3[0,3] should be greater than arr4[1,3]" + when (compareByteArrays arr5 1 arr2 1 3 /= EQ) $ + fail $ "arr3[1,3] should be equal to than arr4[1,3]" unless (arr1 > arr3) $ fail $ "ByteArray Ord incorrect" unless (arr1 == arr2) $ @@ -339,14 +363,12 @@ testByteArray = do fail $ "ByteArray Monoid mappend not associative" unless (mconcat [arr1,arr2,arr3,arr4,arr5] == (arr1 <> arr2 <> arr3 <> arr4 <> arr5)) $ fail $ "ByteArray Monoid mconcat incorrect" -#if MIN_VERSION_base(4,9,0) unless (stimes (3 :: Int) arr4 == (arr4 <> arr4 <> arr4)) $ fail $ "ByteArray Semigroup stimes incorrect" -#endif -mkByteArray :: Prim a => [a] -> ByteArray +mkByteArray :: forall a. Prim a => [a] -> ByteArray mkByteArray xs = runST $ do - marr <- newByteArray (length xs * sizeOf (head xs)) + marr <- newByteArray (length xs * sizeOfType @a) sequence_ $ zipWith (writeByteArray marr) [0..] xs unsafeFreezeByteArray marr @@ -397,8 +419,8 @@ newtype DefaultSetMethod = DefaultSetMethod Int16 deriving (Eq,Show,Arbitrary) instance Prim DefaultSetMethod where - sizeOf# _ = sizeOf# (undefined :: Int16) - alignment# _ = alignment# (undefined :: Int16) + sizeOfType# _ = sizeOfType# (Proxy :: Proxy Int16) + alignmentOfType# _ = alignmentOfType# (Proxy :: Proxy Int16) indexByteArray# arr ix = DefaultSetMethod (indexByteArray# arr ix) readByteArray# arr ix s0 = case readByteArray# arr ix s0 of (# s1, n #) -> (# s1, DefaultSetMethod n #) diff --git a/examples/primitive/test/README.md b/examples/primitive/test/README.md new file mode 100644 index 000000000..07228e9e6 --- /dev/null +++ b/examples/primitive/test/README.md @@ -0,0 +1,16 @@ +Test Suite +======================= + +The test suite for `primitive` cannot be included in the same package +as `primitive` itself. The test suite depends on `QuickCheck`, which +transitively depends on `primitive`. To break up this dependency cycle, +the test suite lives here in its own unpublished package. + +To accelerates builds of the test suite, it is recommended to use +`cabal new-build`, which will use the pass the flags specified in +the `cabal.project` file to build `quickcheck-classes`. From the +root directory of `primitive`, run the following command to build +the test suite: + + cabal new-build test --enable-tests + diff --git a/examples/primitive/test/primitive-tests.cabal b/examples/primitive/test/primitive-tests.cabal deleted file mode 100644 index 957fe5ee1..000000000 --- a/examples/primitive/test/primitive-tests.cabal +++ /dev/null @@ -1,45 +0,0 @@ -Name: primitive-tests -Version: 0.1 -License: BSD3 -License-File: LICENSE - -Author: Roman Leshchinskiy -Maintainer: libraries@haskell.org -Copyright: (c) Roman Leshchinskiy 2009-2012 -Homepage: https://github.com/haskell/primitive -Bug-Reports: https://github.com/haskell/primitive/issues -Category: Data -Synopsis: primitive tests -Cabal-Version: >= 1.10 -Build-Type: Simple -Description: @primitive@ tests - -Tested-With: - GHC == 7.4.2, - GHC == 7.6.3, - GHC == 7.8.4, - GHC == 7.10.3, - GHC == 8.0.2, - GHC == 8.2.2, - GHC == 8.4.2 - -test-suite test - Default-Language: Haskell2010 - hs-source-dirs: . - main-is: main.hs - type: exitcode-stdio-1.0 - build-depends: base >= 4.5 && < 4.12 - , ghc-prim - , primitive - , QuickCheck - , tasty - , tasty-quickcheck - , tagged - , transformers >= 0.3 - , quickcheck-classes >= 0.4.11.1 - ghc-options: -O2 - -source-repository head - type: git - location: https://github.com/haskell/primitive - subdir: test diff --git a/examples/primitive/test/src/PrimLaws.hs b/examples/primitive/test/src/PrimLaws.hs new file mode 100644 index 000000000..65a558530 --- /dev/null +++ b/examples/primitive/test/src/PrimLaws.hs @@ -0,0 +1,154 @@ +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeApplications #-} + +{-# OPTIONS_GHC -Wall #-} + +-- This module is almost an exact copy of the unexported module +-- Test.QuickCheck.Classes.Prim from quickcheck-classes. We cannot depend +-- on quickcheck-classes in the test suite since that would imply a circular +-- dependency between primitive and quickcheck-classes. Instead, we copy +-- this one module and then depend on quickcheck-classes-base to get +-- everything else we need. +module PrimLaws + ( primLaws + ) where + +import Control.Monad.Primitive (primitive_) +import Control.Monad.ST +import Data.Proxy (Proxy) +import Data.Primitive.PrimArray +import Data.Primitive.ByteArray +import Data.Primitive.Types +import Data.Primitive.Ptr +import Foreign.Marshal.Alloc +import GHC.Exts (State#, Int#, Int(I#), (+#), (<#), IsList(fromList,toList)) + +import System.IO.Unsafe +import Test.QuickCheck hiding ((.&.)) + +import qualified Data.List as L +import qualified Data.Primitive as P + +import Test.QuickCheck.Classes.Base (Laws(..)) +import Test.QuickCheck.Classes.Internal (isTrue#) + +-- | Test that a 'Prim' instance obey the several laws. +primLaws :: (Prim a, Eq a, Arbitrary a, Show a) => Proxy a -> Laws +primLaws p = Laws "Prim" + [ ("ByteArray Put-Get (you get back what you put in)", primPutGetByteArray p) + , ("ByteArray Get-Put (putting back what you got out has no effect)", primGetPutByteArray p) + , ("ByteArray Put-Put (putting twice is same as putting once)", primPutPutByteArray p) + , ("ByteArray Set Range", primSetByteArray p) + , ("ByteArray List Conversion Roundtrips", primListByteArray p) + , ("Ptr Put-Get (you get back what you put in)", primPutGetAddr p) + , ("Ptr List Conversion Roundtrips", primListAddr p) + ] + +primListAddr :: forall a. (Prim a, Eq a, Arbitrary a, Show a) => Proxy a -> Property +primListAddr _ = property $ \(as :: [a]) -> unsafePerformIO $ do + let len = L.length as + ptr :: Ptr a <- mallocBytes (len * P.sizeOfType @a) + let go :: Int -> [a] -> IO () + go !ix xs = case xs of + [] -> return () + (x : xsNext) -> do + writeOffPtr ptr ix x + go (ix + 1) xsNext + go 0 as + let rebuild :: Int -> IO [a] + rebuild !ix = if ix < len + then (:) <$> readOffPtr ptr ix <*> rebuild (ix + 1) + else return [] + asNew <- rebuild 0 + free ptr + return (as == asNew) + +primPutGetByteArray :: forall a. (Prim a, Eq a, Arbitrary a, Show a) => Proxy a -> Property +primPutGetByteArray _ = property $ \(a :: a) len -> (len > 0) ==> do + ix <- choose (0,len - 1) + return $ runST $ do + arr <- newPrimArray len + writePrimArray arr ix a + a' <- readPrimArray arr ix + return (a == a') + +primGetPutByteArray :: forall a. (Prim a, Eq a, Arbitrary a, Show a) => Proxy a -> Property +primGetPutByteArray _ = property $ \(as :: [a]) -> (not (L.null as)) ==> do + let arr1 = primArrayFromList as :: PrimArray a + len = L.length as + ix <- choose (0,len - 1) + arr2 <- return $ runST $ do + marr <- newPrimArray len + copyPrimArray marr 0 arr1 0 len + a <- readPrimArray marr ix + writePrimArray marr ix a + unsafeFreezePrimArray marr + return (arr1 == arr2) + +primPutPutByteArray :: forall a. (Prim a, Eq a, Arbitrary a, Show a) => Proxy a -> Property +primPutPutByteArray _ = property $ \(a :: a) (as :: [a]) -> (not (L.null as)) ==> do + let arr1 = primArrayFromList as :: PrimArray a + len = L.length as + ix <- choose (0,len - 1) + (arr2,arr3) <- return $ runST $ do + marr2 <- newPrimArray len + copyPrimArray marr2 0 arr1 0 len + writePrimArray marr2 ix a + marr3 <- newPrimArray len + copyMutablePrimArray marr3 0 marr2 0 len + arr2 <- unsafeFreezePrimArray marr2 + writePrimArray marr3 ix a + arr3 <- unsafeFreezePrimArray marr3 + return (arr2,arr3) + return (arr2 == arr3) + +primPutGetAddr :: forall a. (Prim a, Eq a, Arbitrary a, Show a) => Proxy a -> Property +primPutGetAddr _ = property $ \(a :: a) len -> (len > 0) ==> do + ix <- choose (0,len - 1) + return $ unsafePerformIO $ do + ptr :: Ptr a <- mallocBytes (len * P.sizeOfType @a) + writeOffPtr ptr ix a + a' <- readOffPtr ptr ix + free ptr + return (a == a') + +primSetByteArray :: forall a. (Prim a, Eq a, Arbitrary a, Show a) => Proxy a -> Property +primSetByteArray _ = property $ \(as :: [a]) (z :: a) -> do + let arr1 = primArrayFromList as :: PrimArray a + len = L.length as + x <- choose (0,len) + y <- choose (0,len) + let lo = min x y + hi = max x y + return $ runST $ do + marr2 <- newPrimArray len + copyPrimArray marr2 0 arr1 0 len + marr3 <- newPrimArray len + copyPrimArray marr3 0 arr1 0 len + setPrimArray marr2 lo (hi - lo) z + internalDefaultSetPrimArray marr3 lo (hi - lo) z + arr2 <- unsafeFreezePrimArray marr2 + arr3 <- unsafeFreezePrimArray marr3 + return (arr2 == arr3) + +primListByteArray :: forall a. (Prim a, Eq a, Arbitrary a, Show a) => Proxy a -> Property +primListByteArray _ = property $ \(as :: [a]) -> + as == toList (fromList as :: PrimArray a) + +internalDefaultSetPrimArray :: Prim a + => MutablePrimArray s a -> Int -> Int -> a -> ST s () +internalDefaultSetPrimArray (MutablePrimArray arr) (I# i) (I# len) ident = + primitive_ (internalDefaultSetByteArray# arr i len ident) + +internalDefaultSetByteArray# :: Prim a + => MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s +internalDefaultSetByteArray# arr# i# len# ident = go 0# + where + go ix# s0 = if isTrue# (ix# <# len#) + then case writeByteArray# arr# (i# +# ix#) ident s0 of + s1 -> go (ix# +# 1#) s1 + else s0 diff --git a/haskell/ghc.bzl b/haskell/ghc.bzl index c09d12c3c..a67025044 100644 --- a/haskell/ghc.bzl +++ b/haskell/ghc.bzl @@ -2,4 +2,4 @@ # (see stackage.org). # Currently, we are using GHC 9.2.x as default. -DEFAULT_GHC_VERSION = "9.2.8" +DEFAULT_GHC_VERSION = "9.4.6" diff --git a/rules_haskell_nix/MODULE.bazel b/rules_haskell_nix/MODULE.bazel index a0e3e5616..d83dd7c1f 100644 --- a/rules_haskell_nix/MODULE.bazel +++ b/rules_haskell_nix/MODULE.bazel @@ -42,9 +42,9 @@ nix_haskell_toolchains = use_extension( # Declare a default nix-based toolchain nix_haskell_toolchains.new( attribute_path = "", - nix_file_content = """with import {}; haskell.packages.ghc928.ghc""", + nix_file_content = """with import {}; haskell.packages.ghc946.ghc""", repository = "@nixpkgs_default", - version = "9.2.8", + version = "9.4.6", ) use_repo( nix_haskell_toolchains, diff --git a/rules_haskell_tests/MODULE.bazel b/rules_haskell_tests/MODULE.bazel index 28922c68e..fcde387d1 100644 --- a/rules_haskell_tests/MODULE.bazel +++ b/rules_haskell_tests/MODULE.bazel @@ -250,7 +250,7 @@ haskell_toolchains = use_extension( "haskell_toolchains", ) -test_ghc_version = "9.2.8" +test_ghc_version = "9.4.6" test_ghcopts = [ "-XStandaloneDeriving", # Flag used at compile time @@ -316,12 +316,13 @@ nix_haskell_toolchains = use_extension( "@rules_haskell_nix//extensions:nix_haskell_toolchains.bzl", "nix_haskell_toolchains", ) + nix_haskell_toolchains.new( attribute_path = "", cabalopts = test_cabalopts, ghcopts = test_ghcopts, haddock_flags = test_haddock_flags, - nix_file_content = """with import {}; haskell.packages.ghc928.ghc""", + nix_file_content = """with import {}; haskell.packages.ghc946.ghc""", repl_ghci_args = test_repl_ghci_args, repository = "@nixpkgs_default", version = test_ghc_version, diff --git a/rules_haskell_tests/shell.nix b/rules_haskell_tests/shell.nix index 18704fcf1..d3169348a 100644 --- a/rules_haskell_tests/shell.nix +++ b/rules_haskell_tests/shell.nix @@ -1,4 +1,4 @@ -{ pkgs ? import ./nixpkgs { }, docTools ? true, ghcVersion ? "9.2.8" }: +{ pkgs ? import ./nixpkgs { }, docTools ? true, ghcVersion ? "9.4.6" }: with pkgs; mkShell { diff --git a/rules_haskell_tests/stackage-pinning-test.yaml b/rules_haskell_tests/stackage-pinning-test.yaml deleted file mode 100644 index 93768f9e5..000000000 --- a/rules_haskell_tests/stackage-pinning-test.yaml +++ /dev/null @@ -1,32 +0,0 @@ -resolver: "lts-20.26" -packages: - - github: hspec/hspec - # NOTE Keep in sync with resolver version - commit: "4a4b27cb1d5284c94228c9c76c5fe79215597fb7" - sha256: "fb96ed7dd3e2b792300f3bc8bd2affc6bf78093289815f76ec785fea6d91be68" - subdirs: - - . - - hspec-contrib - - hspec-core - - hspec-discover - - - archive: https://github.com/tweag/rules_haskell/raw/e4e74f17f743488f564bd0d69c580106d5b910a5/tests/haskell_cabal_library_sublibrary_name/package1.tar - sha256: "302d8ddda8330c825da61fe0a2315c899ab083e641c7716ebdacb5c951682445" - - git: https://github.com/tweag/cabal - commit: 42f04c3f639f10dc3c7981a0c663bfe08ad833cb - subdirs: - - Cabal - -# We drop the Win32 package from the stack snapshot so that stack considers it a toolchain library. -# In this case we will use the Win32 provided by the compiler instead of recompiling it. -# -# Recompiling it should be fine for future versions of Win32, -# but with versions <= 2.13.2.0 we encounter the following issue: -# https://github.com/haskell/win32/issues/193 -drop-packages: - - Win32 - -# stackage lts-20.26/ghc 9.2.8 only contains Win32-2.12.0.1 -flags: - ansi-terminal: - Win32-2-13-1: false diff --git a/rules_haskell_tests/stackage-pinning-test.yaml b/rules_haskell_tests/stackage-pinning-test.yaml new file mode 120000 index 000000000..0810d0926 --- /dev/null +++ b/rules_haskell_tests/stackage-pinning-test.yaml @@ -0,0 +1 @@ +stackage-pinning-test_9.4.6.yaml \ No newline at end of file diff --git a/rules_haskell_tests/stackage-pinning-test_9.2.8.yaml b/rules_haskell_tests/stackage-pinning-test_9.2.8.yaml deleted file mode 120000 index e20166de1..000000000 --- a/rules_haskell_tests/stackage-pinning-test_9.2.8.yaml +++ /dev/null @@ -1 +0,0 @@ -stackage-pinning-test.yaml \ No newline at end of file diff --git a/rules_haskell_tests/stackage-pinning-test_9.2.8.yaml b/rules_haskell_tests/stackage-pinning-test_9.2.8.yaml new file mode 100644 index 000000000..93768f9e5 --- /dev/null +++ b/rules_haskell_tests/stackage-pinning-test_9.2.8.yaml @@ -0,0 +1,32 @@ +resolver: "lts-20.26" +packages: + - github: hspec/hspec + # NOTE Keep in sync with resolver version + commit: "4a4b27cb1d5284c94228c9c76c5fe79215597fb7" + sha256: "fb96ed7dd3e2b792300f3bc8bd2affc6bf78093289815f76ec785fea6d91be68" + subdirs: + - . + - hspec-contrib + - hspec-core + - hspec-discover + + - archive: https://github.com/tweag/rules_haskell/raw/e4e74f17f743488f564bd0d69c580106d5b910a5/tests/haskell_cabal_library_sublibrary_name/package1.tar + sha256: "302d8ddda8330c825da61fe0a2315c899ab083e641c7716ebdacb5c951682445" + - git: https://github.com/tweag/cabal + commit: 42f04c3f639f10dc3c7981a0c663bfe08ad833cb + subdirs: + - Cabal + +# We drop the Win32 package from the stack snapshot so that stack considers it a toolchain library. +# In this case we will use the Win32 provided by the compiler instead of recompiling it. +# +# Recompiling it should be fine for future versions of Win32, +# but with versions <= 2.13.2.0 we encounter the following issue: +# https://github.com/haskell/win32/issues/193 +drop-packages: + - Win32 + +# stackage lts-20.26/ghc 9.2.8 only contains Win32-2.12.0.1 +flags: + ansi-terminal: + Win32-2-13-1: false diff --git a/rules_haskell_tests/stackage-pinning-test_snapshot.json b/rules_haskell_tests/stackage-pinning-test_snapshot.json deleted file mode 100644 index 878512d6d..000000000 --- a/rules_haskell_tests/stackage-pinning-test_snapshot.json +++ /dev/null @@ -1,42 +0,0 @@ -{ - "__GENERATED_FILE_DO_NOT_MODIFY_MANUALLY": 1475609344, - "all-cabal-hashes": "https://raw.githubusercontent.com/commercialhaskell/all-cabal-hashes/64569eb85ade372e2e155d64169a99a43b94a29a", - "resolved": { - "Cabal": {"dependencies":["array","base","binary","bytestring","containers","deepseq","directory","filepath","mtl","parsec","pretty","process","text","time","transformers","unix"],"location":{"type":"git","url":"https://github.com/tweag/cabal","commit":"42f04c3f639f10dc3c7981a0c663bfe08ad833cb","subdir":"Cabal"},"name":"Cabal","version":"3.6.3.0"}, - "HUnit": {"dependencies":["base","call-stack","deepseq"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/HUnit-1.6.2.0/HUnit-1.6.2.0.tar.gz"},"name":"HUnit","pinned":{"url":["https://hackage.haskell.org/package/HUnit-1.6.2.0/HUnit-1.6.2.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/HUnit-1.6.2.0.tar.gz"],"sha256":"b0b7538871ffc058486fc00740886d2f3172f8fa6869936bfe83a5e10bd744ab","cabal-sha256":"1a79174e8af616117ad39464cac9de205ca923da6582825e97c10786fda933a4"},"version":"1.6.2.0"}, - "QuickCheck": {"dependencies":["base","containers","deepseq","random","splitmix","template-haskell","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/QuickCheck-2.14.3/QuickCheck-2.14.3.tar.gz"},"name":"QuickCheck","pinned":{"url":["https://hackage.haskell.org/package/QuickCheck-2.14.3/QuickCheck-2.14.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/QuickCheck-2.14.3.tar.gz"],"sha256":"5c0f22b36b28a1a8fa110b3819818d3f29494a3b0dedbae299f064123ca70501","cabal-sha256":"f03d2f404d5ba465453d0fbc1944832789a759fe7c4f9bf8616bc1378a02fde4"},"version":"2.14.3"}, - "ansi-terminal": {"dependencies":["base","colour"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/ansi-terminal-0.11.4/ansi-terminal-0.11.4.tar.gz"},"name":"ansi-terminal","pinned":{"url":["https://hackage.haskell.org/package/ansi-terminal-0.11.4/ansi-terminal-0.11.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/ansi-terminal-0.11.4.tar.gz"],"sha256":"7898e48f0a535c1857cde52c803f28096ba89759461fe4d157fd55dcdb420e25","cabal-sha256":"410737137c798e23339a08435a5511785ebf1db08700e37debbd7801cf73fc82"},"version":"0.11.4"}, - "array": {"dependencies":[],"location":{"type":"core"},"name":"array","version":"0.5.4.0"}, - "base": {"dependencies":[],"location":{"type":"core"},"name":"base","version":"4.16.4.0"}, - "binary": {"dependencies":[],"location":{"type":"core"},"name":"binary","version":"0.8.9.0"}, - "bytestring": {"dependencies":[],"location":{"type":"core"},"name":"bytestring","version":"0.11.4.0"}, - "call-stack": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/call-stack-0.4.0/call-stack-0.4.0.tar.gz"},"name":"call-stack","pinned":{"url":["https://hackage.haskell.org/package/call-stack-0.4.0/call-stack-0.4.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/call-stack-0.4.0.tar.gz"],"sha256":"430bcf8a3404f7e55319573c0b807b1356946f0c8f289bb3d9afb279c636b87b","cabal-sha256":"ac44d2c00931dc20b01750da8c92ec443eb63a7231e8550188cb2ac2385f7feb"},"version":"0.4.0"}, - "clock": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/clock-0.8.3/clock-0.8.3.tar.gz"},"name":"clock","pinned":{"url":["https://hackage.haskell.org/package/clock-0.8.3/clock-0.8.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/clock-0.8.3.tar.gz"],"sha256":"845ce5db4c98cefd517323e005f87effceff886987305e421c4ef616dc0505d1","cabal-sha256":"a692159828c2cd278eaec317b3a7e9fb6d7b787c8a19f086004d15d9fa1fd72c"},"version":"0.8.3"}, - "colour": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/colour-2.3.6/colour-2.3.6.tar.gz"},"name":"colour","pinned":{"url":["https://hackage.haskell.org/package/colour-2.3.6/colour-2.3.6.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/colour-2.3.6.tar.gz"],"sha256":"2cd35dcd6944a5abc9f108a5eb5ee564b6b1fa98a9ec79cefcc20b588991f871","cabal-sha256":"ebdcbf15023958838a527e381ab3c3b1e99ed12d1b25efeb7feaa4ad8c37664a"},"version":"2.3.6"}, - "containers": {"dependencies":[],"location":{"type":"core"},"name":"containers","version":"0.6.5.1"}, - "deepseq": {"dependencies":[],"location":{"type":"core"},"name":"deepseq","version":"1.4.6.1"}, - "directory": {"dependencies":[],"location":{"type":"core"},"name":"directory","version":"1.3.6.2"}, - "filepath": {"dependencies":[],"location":{"type":"core"},"name":"filepath","version":"1.4.2.2"}, - "hspec": {"dependencies":["QuickCheck","base","hspec-core","hspec-discover","hspec-expectations"],"location":{"type":"archive","url":"https://github.com/hspec/hspec/archive/4a4b27cb1d5284c94228c9c76c5fe79215597fb7.tar.gz"},"name":"hspec","pinned":{"sha256":"fb96ed7dd3e2b792300f3bc8bd2affc6bf78093289815f76ec785fea6d91be68","strip-prefix":"hspec-4a4b27cb1d5284c94228c9c76c5fe79215597fb7"},"version":"2.7.10"}, - "hspec-core": {"dependencies":["HUnit","QuickCheck","ansi-terminal","array","base","call-stack","clock","deepseq","directory","filepath","hspec-expectations","quickcheck-io","random","setenv","stm","tf-random","transformers"],"location":{"type":"archive","url":"https://github.com/hspec/hspec/archive/4a4b27cb1d5284c94228c9c76c5fe79215597fb7.tar.gz"},"name":"hspec-core","pinned":{"sha256":"fb96ed7dd3e2b792300f3bc8bd2affc6bf78093289815f76ec785fea6d91be68","strip-prefix":"hspec-4a4b27cb1d5284c94228c9c76c5fe79215597fb7/hspec-core"},"version":"2.7.10"}, - "hspec-discover": {"dependencies":["base","directory","filepath"],"location":{"type":"archive","url":"https://github.com/hspec/hspec/archive/4a4b27cb1d5284c94228c9c76c5fe79215597fb7.tar.gz"},"name":"hspec-discover","pinned":{"sha256":"fb96ed7dd3e2b792300f3bc8bd2affc6bf78093289815f76ec785fea6d91be68","strip-prefix":"hspec-4a4b27cb1d5284c94228c9c76c5fe79215597fb7/hspec-discover"},"version":"2.7.10"}, - "hspec-expectations": {"dependencies":["HUnit","base","call-stack"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/hspec-expectations-0.8.2/hspec-expectations-0.8.2.tar.gz"},"name":"hspec-expectations","pinned":{"url":["https://hackage.haskell.org/package/hspec-expectations-0.8.2/hspec-expectations-0.8.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/hspec-expectations-0.8.2.tar.gz"],"sha256":"819607ea1faf35ce5be34be61c6f50f3389ea43892d56fb28c57a9f5d54fb4ef","cabal-sha256":"e2db24881baadc2d9d23b03cb629e80dcbda89a6b04ace9adb5f4d02ef8b31aa"},"version":"0.8.2"}, - "mtl": {"dependencies":[],"location":{"type":"core"},"name":"mtl","version":"2.2.2"}, - "package1": {"dependencies":["Cabal","base"],"location":{"type":"archive","url":"https://github.com/tweag/rules_haskell/raw/e4e74f17f743488f564bd0d69c580106d5b910a5/tests/haskell_cabal_library_sublibrary_name/package1.tar"},"name":"package1","pinned":{"sha256":"302d8ddda8330c825da61fe0a2315c899ab083e641c7716ebdacb5c951682445","strip-prefix":""},"version":"0.1.0.0"}, - "parsec": {"dependencies":[],"location":{"type":"core"},"name":"parsec","version":"3.1.15.0"}, - "pretty": {"dependencies":[],"location":{"type":"core"},"name":"pretty","version":"1.1.3.6"}, - "primitive": {"dependencies":["base","deepseq","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/primitive-0.7.3.0/primitive-0.7.3.0.tar.gz"},"name":"primitive","pinned":{"url":["https://hackage.haskell.org/package/primitive-0.7.3.0/primitive-0.7.3.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/primitive-0.7.3.0.tar.gz"],"sha256":"3c0cfda67f1ee6f7f65108ad6f973b5bbb35ddba34b3c87746a7448f787501dc","cabal-sha256":"ce9361b4d2ed296ef639380411b4cfc217a19e4b3cd4170e03e6fce52daa0176"},"version":"0.7.3.0"}, - "process": {"dependencies":[],"location":{"type":"core"},"name":"process","version":"1.6.16.0"}, - "quickcheck-io": {"dependencies":["HUnit","QuickCheck","base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/quickcheck-io-0.2.0/quickcheck-io-0.2.0.tar.gz"},"name":"quickcheck-io","pinned":{"url":["https://hackage.haskell.org/package/quickcheck-io-0.2.0/quickcheck-io-0.2.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/quickcheck-io-0.2.0.tar.gz"],"sha256":"fb779119d79fe08ff4d502fb6869a70c9a8d5fd8ae0959f605c3c937efd96422","cabal-sha256":"7bf0b68fb90873825eb2e5e958c1b76126dcf984debb998e81673e6d837e0b2d"},"version":"0.2.0"}, - "random": {"dependencies":["base","bytestring","deepseq","mtl","splitmix"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/random-1.2.1.1/random-1.2.1.1.tar.gz"},"name":"random","pinned":{"url":["https://hackage.haskell.org/package/random-1.2.1.1/random-1.2.1.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/random-1.2.1.1.tar.gz"],"sha256":"3e1272f7ed6a4d7bd1712b90143ec326fee9b225789222379fea20a9c90c9b76","cabal-sha256":"e7c1f881159d5cc788619c9ee8b8f340ba2ff0db571cdf3d1a1968ebc5108789"},"version":"1.2.1.1"}, - "setenv": {"dependencies":["base","unix"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/setenv-0.1.1.3/setenv-0.1.1.3.tar.gz"},"name":"setenv","pinned":{"url":["https://hackage.haskell.org/package/setenv-0.1.1.3/setenv-0.1.1.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/setenv-0.1.1.3.tar.gz"],"sha256":"e358df39afc03d5a39e2ec650652d845c85c80cc98fe331654deafb4767ecb32","cabal-sha256":"c5916ac0d2a828473cd171261328a290afe0abd799db1ac8c310682fe778c45b"},"version":"0.1.1.3"}, - "splitmix": {"dependencies":["base","deepseq"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/splitmix-0.1.0.4/splitmix-0.1.0.4.tar.gz"},"name":"splitmix","pinned":{"url":["https://hackage.haskell.org/package/splitmix-0.1.0.4/splitmix-0.1.0.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/splitmix-0.1.0.4.tar.gz"],"sha256":"6d065402394e7a9117093dbb4530a21342c9b1e2ec509516c8a8d0ffed98ecaa","cabal-sha256":"db25c2e17967aa6b6046ab8b1b96ba3f344ca59a62b60fb6113d51ea305a3d8e"},"version":"0.1.0.4"}, - "stm": {"dependencies":[],"location":{"type":"core"},"name":"stm","version":"2.5.0.2"}, - "template-haskell": {"dependencies":[],"location":{"type":"core"},"name":"template-haskell","version":"2.18.0.0"}, - "text": {"dependencies":[],"location":{"type":"core"},"name":"text","version":"1.2.5.0"}, - "tf-random": {"dependencies":["base","primitive","random","time"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/tf-random-0.5/tf-random-0.5.tar.gz"},"name":"tf-random","pinned":{"url":["https://hackage.haskell.org/package/tf-random-0.5/tf-random-0.5.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/tf-random-0.5.tar.gz"],"sha256":"2e30cec027b313c9e1794d326635d8fc5f79b6bf6e7580ab4b00186dadc88510","cabal-sha256":"14012837d0f0e18fdbbe3d56e67da8622ee5e20b180abce952dd50bd9f36b326"},"version":"0.5"}, - "time": {"dependencies":[],"location":{"type":"core"},"name":"time","version":"1.11.1.1"}, - "transformers": {"dependencies":[],"location":{"type":"core"},"name":"transformers","version":"0.5.6.2"}, - "unix": {"dependencies":[],"location":{"type":"core"},"name":"unix","version":"2.7.2.2"} - } -} \ No newline at end of file diff --git a/rules_haskell_tests/stackage-pinning-test_snapshot.json b/rules_haskell_tests/stackage-pinning-test_snapshot.json new file mode 120000 index 000000000..26d35649f --- /dev/null +++ b/rules_haskell_tests/stackage-pinning-test_snapshot.json @@ -0,0 +1 @@ +stackage-pinning-test_snapshot_9.4.6.json \ No newline at end of file diff --git a/rules_haskell_tests/stackage-pinning-test_snapshot_9.2.8.json b/rules_haskell_tests/stackage-pinning-test_snapshot_9.2.8.json deleted file mode 120000 index ea957505a..000000000 --- a/rules_haskell_tests/stackage-pinning-test_snapshot_9.2.8.json +++ /dev/null @@ -1 +0,0 @@ -stackage-pinning-test_snapshot.json \ No newline at end of file diff --git a/rules_haskell_tests/stackage-pinning-test_snapshot_9.2.8.json b/rules_haskell_tests/stackage-pinning-test_snapshot_9.2.8.json new file mode 100644 index 000000000..878512d6d --- /dev/null +++ b/rules_haskell_tests/stackage-pinning-test_snapshot_9.2.8.json @@ -0,0 +1,42 @@ +{ + "__GENERATED_FILE_DO_NOT_MODIFY_MANUALLY": 1475609344, + "all-cabal-hashes": "https://raw.githubusercontent.com/commercialhaskell/all-cabal-hashes/64569eb85ade372e2e155d64169a99a43b94a29a", + "resolved": { + "Cabal": {"dependencies":["array","base","binary","bytestring","containers","deepseq","directory","filepath","mtl","parsec","pretty","process","text","time","transformers","unix"],"location":{"type":"git","url":"https://github.com/tweag/cabal","commit":"42f04c3f639f10dc3c7981a0c663bfe08ad833cb","subdir":"Cabal"},"name":"Cabal","version":"3.6.3.0"}, + "HUnit": {"dependencies":["base","call-stack","deepseq"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/HUnit-1.6.2.0/HUnit-1.6.2.0.tar.gz"},"name":"HUnit","pinned":{"url":["https://hackage.haskell.org/package/HUnit-1.6.2.0/HUnit-1.6.2.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/HUnit-1.6.2.0.tar.gz"],"sha256":"b0b7538871ffc058486fc00740886d2f3172f8fa6869936bfe83a5e10bd744ab","cabal-sha256":"1a79174e8af616117ad39464cac9de205ca923da6582825e97c10786fda933a4"},"version":"1.6.2.0"}, + "QuickCheck": {"dependencies":["base","containers","deepseq","random","splitmix","template-haskell","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/QuickCheck-2.14.3/QuickCheck-2.14.3.tar.gz"},"name":"QuickCheck","pinned":{"url":["https://hackage.haskell.org/package/QuickCheck-2.14.3/QuickCheck-2.14.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/QuickCheck-2.14.3.tar.gz"],"sha256":"5c0f22b36b28a1a8fa110b3819818d3f29494a3b0dedbae299f064123ca70501","cabal-sha256":"f03d2f404d5ba465453d0fbc1944832789a759fe7c4f9bf8616bc1378a02fde4"},"version":"2.14.3"}, + "ansi-terminal": {"dependencies":["base","colour"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/ansi-terminal-0.11.4/ansi-terminal-0.11.4.tar.gz"},"name":"ansi-terminal","pinned":{"url":["https://hackage.haskell.org/package/ansi-terminal-0.11.4/ansi-terminal-0.11.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/ansi-terminal-0.11.4.tar.gz"],"sha256":"7898e48f0a535c1857cde52c803f28096ba89759461fe4d157fd55dcdb420e25","cabal-sha256":"410737137c798e23339a08435a5511785ebf1db08700e37debbd7801cf73fc82"},"version":"0.11.4"}, + "array": {"dependencies":[],"location":{"type":"core"},"name":"array","version":"0.5.4.0"}, + "base": {"dependencies":[],"location":{"type":"core"},"name":"base","version":"4.16.4.0"}, + "binary": {"dependencies":[],"location":{"type":"core"},"name":"binary","version":"0.8.9.0"}, + "bytestring": {"dependencies":[],"location":{"type":"core"},"name":"bytestring","version":"0.11.4.0"}, + "call-stack": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/call-stack-0.4.0/call-stack-0.4.0.tar.gz"},"name":"call-stack","pinned":{"url":["https://hackage.haskell.org/package/call-stack-0.4.0/call-stack-0.4.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/call-stack-0.4.0.tar.gz"],"sha256":"430bcf8a3404f7e55319573c0b807b1356946f0c8f289bb3d9afb279c636b87b","cabal-sha256":"ac44d2c00931dc20b01750da8c92ec443eb63a7231e8550188cb2ac2385f7feb"},"version":"0.4.0"}, + "clock": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/clock-0.8.3/clock-0.8.3.tar.gz"},"name":"clock","pinned":{"url":["https://hackage.haskell.org/package/clock-0.8.3/clock-0.8.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/clock-0.8.3.tar.gz"],"sha256":"845ce5db4c98cefd517323e005f87effceff886987305e421c4ef616dc0505d1","cabal-sha256":"a692159828c2cd278eaec317b3a7e9fb6d7b787c8a19f086004d15d9fa1fd72c"},"version":"0.8.3"}, + "colour": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/colour-2.3.6/colour-2.3.6.tar.gz"},"name":"colour","pinned":{"url":["https://hackage.haskell.org/package/colour-2.3.6/colour-2.3.6.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/colour-2.3.6.tar.gz"],"sha256":"2cd35dcd6944a5abc9f108a5eb5ee564b6b1fa98a9ec79cefcc20b588991f871","cabal-sha256":"ebdcbf15023958838a527e381ab3c3b1e99ed12d1b25efeb7feaa4ad8c37664a"},"version":"2.3.6"}, + "containers": {"dependencies":[],"location":{"type":"core"},"name":"containers","version":"0.6.5.1"}, + "deepseq": {"dependencies":[],"location":{"type":"core"},"name":"deepseq","version":"1.4.6.1"}, + "directory": {"dependencies":[],"location":{"type":"core"},"name":"directory","version":"1.3.6.2"}, + "filepath": {"dependencies":[],"location":{"type":"core"},"name":"filepath","version":"1.4.2.2"}, + "hspec": {"dependencies":["QuickCheck","base","hspec-core","hspec-discover","hspec-expectations"],"location":{"type":"archive","url":"https://github.com/hspec/hspec/archive/4a4b27cb1d5284c94228c9c76c5fe79215597fb7.tar.gz"},"name":"hspec","pinned":{"sha256":"fb96ed7dd3e2b792300f3bc8bd2affc6bf78093289815f76ec785fea6d91be68","strip-prefix":"hspec-4a4b27cb1d5284c94228c9c76c5fe79215597fb7"},"version":"2.7.10"}, + "hspec-core": {"dependencies":["HUnit","QuickCheck","ansi-terminal","array","base","call-stack","clock","deepseq","directory","filepath","hspec-expectations","quickcheck-io","random","setenv","stm","tf-random","transformers"],"location":{"type":"archive","url":"https://github.com/hspec/hspec/archive/4a4b27cb1d5284c94228c9c76c5fe79215597fb7.tar.gz"},"name":"hspec-core","pinned":{"sha256":"fb96ed7dd3e2b792300f3bc8bd2affc6bf78093289815f76ec785fea6d91be68","strip-prefix":"hspec-4a4b27cb1d5284c94228c9c76c5fe79215597fb7/hspec-core"},"version":"2.7.10"}, + "hspec-discover": {"dependencies":["base","directory","filepath"],"location":{"type":"archive","url":"https://github.com/hspec/hspec/archive/4a4b27cb1d5284c94228c9c76c5fe79215597fb7.tar.gz"},"name":"hspec-discover","pinned":{"sha256":"fb96ed7dd3e2b792300f3bc8bd2affc6bf78093289815f76ec785fea6d91be68","strip-prefix":"hspec-4a4b27cb1d5284c94228c9c76c5fe79215597fb7/hspec-discover"},"version":"2.7.10"}, + "hspec-expectations": {"dependencies":["HUnit","base","call-stack"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/hspec-expectations-0.8.2/hspec-expectations-0.8.2.tar.gz"},"name":"hspec-expectations","pinned":{"url":["https://hackage.haskell.org/package/hspec-expectations-0.8.2/hspec-expectations-0.8.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/hspec-expectations-0.8.2.tar.gz"],"sha256":"819607ea1faf35ce5be34be61c6f50f3389ea43892d56fb28c57a9f5d54fb4ef","cabal-sha256":"e2db24881baadc2d9d23b03cb629e80dcbda89a6b04ace9adb5f4d02ef8b31aa"},"version":"0.8.2"}, + "mtl": {"dependencies":[],"location":{"type":"core"},"name":"mtl","version":"2.2.2"}, + "package1": {"dependencies":["Cabal","base"],"location":{"type":"archive","url":"https://github.com/tweag/rules_haskell/raw/e4e74f17f743488f564bd0d69c580106d5b910a5/tests/haskell_cabal_library_sublibrary_name/package1.tar"},"name":"package1","pinned":{"sha256":"302d8ddda8330c825da61fe0a2315c899ab083e641c7716ebdacb5c951682445","strip-prefix":""},"version":"0.1.0.0"}, + "parsec": {"dependencies":[],"location":{"type":"core"},"name":"parsec","version":"3.1.15.0"}, + "pretty": {"dependencies":[],"location":{"type":"core"},"name":"pretty","version":"1.1.3.6"}, + "primitive": {"dependencies":["base","deepseq","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/primitive-0.7.3.0/primitive-0.7.3.0.tar.gz"},"name":"primitive","pinned":{"url":["https://hackage.haskell.org/package/primitive-0.7.3.0/primitive-0.7.3.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/primitive-0.7.3.0.tar.gz"],"sha256":"3c0cfda67f1ee6f7f65108ad6f973b5bbb35ddba34b3c87746a7448f787501dc","cabal-sha256":"ce9361b4d2ed296ef639380411b4cfc217a19e4b3cd4170e03e6fce52daa0176"},"version":"0.7.3.0"}, + "process": {"dependencies":[],"location":{"type":"core"},"name":"process","version":"1.6.16.0"}, + "quickcheck-io": {"dependencies":["HUnit","QuickCheck","base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/quickcheck-io-0.2.0/quickcheck-io-0.2.0.tar.gz"},"name":"quickcheck-io","pinned":{"url":["https://hackage.haskell.org/package/quickcheck-io-0.2.0/quickcheck-io-0.2.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/quickcheck-io-0.2.0.tar.gz"],"sha256":"fb779119d79fe08ff4d502fb6869a70c9a8d5fd8ae0959f605c3c937efd96422","cabal-sha256":"7bf0b68fb90873825eb2e5e958c1b76126dcf984debb998e81673e6d837e0b2d"},"version":"0.2.0"}, + "random": {"dependencies":["base","bytestring","deepseq","mtl","splitmix"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/random-1.2.1.1/random-1.2.1.1.tar.gz"},"name":"random","pinned":{"url":["https://hackage.haskell.org/package/random-1.2.1.1/random-1.2.1.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/random-1.2.1.1.tar.gz"],"sha256":"3e1272f7ed6a4d7bd1712b90143ec326fee9b225789222379fea20a9c90c9b76","cabal-sha256":"e7c1f881159d5cc788619c9ee8b8f340ba2ff0db571cdf3d1a1968ebc5108789"},"version":"1.2.1.1"}, + "setenv": {"dependencies":["base","unix"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/setenv-0.1.1.3/setenv-0.1.1.3.tar.gz"},"name":"setenv","pinned":{"url":["https://hackage.haskell.org/package/setenv-0.1.1.3/setenv-0.1.1.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/setenv-0.1.1.3.tar.gz"],"sha256":"e358df39afc03d5a39e2ec650652d845c85c80cc98fe331654deafb4767ecb32","cabal-sha256":"c5916ac0d2a828473cd171261328a290afe0abd799db1ac8c310682fe778c45b"},"version":"0.1.1.3"}, + "splitmix": {"dependencies":["base","deepseq"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/splitmix-0.1.0.4/splitmix-0.1.0.4.tar.gz"},"name":"splitmix","pinned":{"url":["https://hackage.haskell.org/package/splitmix-0.1.0.4/splitmix-0.1.0.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/splitmix-0.1.0.4.tar.gz"],"sha256":"6d065402394e7a9117093dbb4530a21342c9b1e2ec509516c8a8d0ffed98ecaa","cabal-sha256":"db25c2e17967aa6b6046ab8b1b96ba3f344ca59a62b60fb6113d51ea305a3d8e"},"version":"0.1.0.4"}, + "stm": {"dependencies":[],"location":{"type":"core"},"name":"stm","version":"2.5.0.2"}, + "template-haskell": {"dependencies":[],"location":{"type":"core"},"name":"template-haskell","version":"2.18.0.0"}, + "text": {"dependencies":[],"location":{"type":"core"},"name":"text","version":"1.2.5.0"}, + "tf-random": {"dependencies":["base","primitive","random","time"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/tf-random-0.5/tf-random-0.5.tar.gz"},"name":"tf-random","pinned":{"url":["https://hackage.haskell.org/package/tf-random-0.5/tf-random-0.5.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/tf-random-0.5.tar.gz"],"sha256":"2e30cec027b313c9e1794d326635d8fc5f79b6bf6e7580ab4b00186dadc88510","cabal-sha256":"14012837d0f0e18fdbbe3d56e67da8622ee5e20b180abce952dd50bd9f36b326"},"version":"0.5"}, + "time": {"dependencies":[],"location":{"type":"core"},"name":"time","version":"1.11.1.1"}, + "transformers": {"dependencies":[],"location":{"type":"core"},"name":"transformers","version":"0.5.6.2"}, + "unix": {"dependencies":[],"location":{"type":"core"},"name":"unix","version":"2.7.2.2"} + } +} \ No newline at end of file diff --git a/rules_haskell_tests/stackage-zlib-snapshot.json b/rules_haskell_tests/stackage-zlib-snapshot.json deleted file mode 100644 index ae8387008..000000000 --- a/rules_haskell_tests/stackage-zlib-snapshot.json +++ /dev/null @@ -1,9 +0,0 @@ -{ - "__GENERATED_FILE_DO_NOT_MODIFY_MANUALLY": 514058195, - "all-cabal-hashes": "https://raw.githubusercontent.com/commercialhaskell/all-cabal-hashes/64569eb85ade372e2e155d64169a99a43b94a29a", - "resolved": { - "base": {"dependencies":[],"location":{"type":"core"},"name":"base","version":"4.16.4.0"}, - "bytestring": {"dependencies":[],"location":{"type":"core"},"name":"bytestring","version":"0.11.4.0"}, - "zlib": {"dependencies":["base","bytestring"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/zlib-0.6.3.0/zlib-0.6.3.0.tar.gz"},"name":"zlib","pinned":{"url":["https://hackage.haskell.org/package/zlib-0.6.3.0/zlib-0.6.3.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/zlib-0.6.3.0.tar.gz"],"sha256":"9eaa989ad4534438b5beb51c1d3a4c8f6a088fdff0b259a5394fbf39aaee04da","cabal-sha256":"cf2a8edc1f4086934638d11882423780dd096c4e77d9c6639ccc469c6c26f041"},"version":"0.6.3.0"} - } -} \ No newline at end of file diff --git a/rules_haskell_tests/stackage-zlib-snapshot.json b/rules_haskell_tests/stackage-zlib-snapshot.json new file mode 120000 index 000000000..3cbaed2d8 --- /dev/null +++ b/rules_haskell_tests/stackage-zlib-snapshot.json @@ -0,0 +1 @@ +stackage-zlib-snapshot_9.4.6.json \ No newline at end of file diff --git a/rules_haskell_tests/stackage-zlib-snapshot_9.2.8.json b/rules_haskell_tests/stackage-zlib-snapshot_9.2.8.json deleted file mode 120000 index 86462db71..000000000 --- a/rules_haskell_tests/stackage-zlib-snapshot_9.2.8.json +++ /dev/null @@ -1 +0,0 @@ -stackage-zlib-snapshot.json \ No newline at end of file diff --git a/rules_haskell_tests/stackage-zlib-snapshot_9.2.8.json b/rules_haskell_tests/stackage-zlib-snapshot_9.2.8.json new file mode 100644 index 000000000..ae8387008 --- /dev/null +++ b/rules_haskell_tests/stackage-zlib-snapshot_9.2.8.json @@ -0,0 +1,9 @@ +{ + "__GENERATED_FILE_DO_NOT_MODIFY_MANUALLY": 514058195, + "all-cabal-hashes": "https://raw.githubusercontent.com/commercialhaskell/all-cabal-hashes/64569eb85ade372e2e155d64169a99a43b94a29a", + "resolved": { + "base": {"dependencies":[],"location":{"type":"core"},"name":"base","version":"4.16.4.0"}, + "bytestring": {"dependencies":[],"location":{"type":"core"},"name":"bytestring","version":"0.11.4.0"}, + "zlib": {"dependencies":["base","bytestring"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/zlib-0.6.3.0/zlib-0.6.3.0.tar.gz"},"name":"zlib","pinned":{"url":["https://hackage.haskell.org/package/zlib-0.6.3.0/zlib-0.6.3.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/zlib-0.6.3.0.tar.gz"],"sha256":"9eaa989ad4534438b5beb51c1d3a4c8f6a088fdff0b259a5394fbf39aaee04da","cabal-sha256":"cf2a8edc1f4086934638d11882423780dd096c4e77d9c6639ccc469c6c26f041"},"version":"0.6.3.0"} + } +} \ No newline at end of file diff --git a/rules_haskell_tests/stackage_snapshot.json b/rules_haskell_tests/stackage_snapshot.json deleted file mode 100644 index 514dce582..000000000 --- a/rules_haskell_tests/stackage_snapshot.json +++ /dev/null @@ -1,116 +0,0 @@ -{ - "__GENERATED_FILE_DO_NOT_MODIFY_MANUALLY": 2037838104, - "all-cabal-hashes": "https://raw.githubusercontent.com/commercialhaskell/all-cabal-hashes/64569eb85ade372e2e155d64169a99a43b94a29a", - "resolved": { - "Cabal": {"dependencies":["array","base","binary","bytestring","containers","deepseq","directory","filepath","mtl","parsec","pretty","process","text","time","transformers","unix"],"location":{"type":"git","url":"https://github.com/tweag/cabal","commit":"42f04c3f639f10dc3c7981a0c663bfe08ad833cb","subdir":"Cabal"},"name":"Cabal","version":"3.6.3.0"}, - "HUnit": {"dependencies":["base","call-stack","deepseq"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/HUnit-1.6.2.0/HUnit-1.6.2.0.tar.gz"},"name":"HUnit","pinned":{"url":["https://hackage.haskell.org/package/HUnit-1.6.2.0/HUnit-1.6.2.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/HUnit-1.6.2.0.tar.gz"],"sha256":"b0b7538871ffc058486fc00740886d2f3172f8fa6869936bfe83a5e10bd744ab","cabal-sha256":"1a79174e8af616117ad39464cac9de205ca923da6582825e97c10786fda933a4"},"version":"1.6.2.0"}, - "QuickCheck": {"dependencies":["base","containers","deepseq","random","splitmix","template-haskell","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/QuickCheck-2.14.3/QuickCheck-2.14.3.tar.gz"},"name":"QuickCheck","pinned":{"url":["https://hackage.haskell.org/package/QuickCheck-2.14.3/QuickCheck-2.14.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/QuickCheck-2.14.3.tar.gz"],"sha256":"5c0f22b36b28a1a8fa110b3819818d3f29494a3b0dedbae299f064123ca70501","cabal-sha256":"f03d2f404d5ba465453d0fbc1944832789a759fe7c4f9bf8616bc1378a02fde4"},"version":"2.14.3"}, - "StateVar": {"dependencies":["base","stm","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/StateVar-1.2.2/StateVar-1.2.2.tar.gz"},"name":"StateVar","pinned":{"url":["https://hackage.haskell.org/package/StateVar-1.2.2/StateVar-1.2.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/StateVar-1.2.2.tar.gz"],"sha256":"5e4b39da395656a59827b0280508aafdc70335798b50e5d6fd52596026251825","cabal-sha256":"3c022c00485fe165e3080d5da6b3ca9c9b02f62c5deebc584d1b3d1309ce673e"},"version":"1.2.2"}, - "alex": {"dependencies":["array","base","containers","directory"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/alex-3.2.7.4/alex-3.2.7.4.tar.gz"},"name":"alex","pinned":{"url":["https://hackage.haskell.org/package/alex-3.2.7.4/alex-3.2.7.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/alex-3.2.7.4.tar.gz"],"sha256":"8a13fa01ea00883aa3d75d15ce848835b18631b8c9a4966961492d7c6095226f","cabal-sha256":"91f4b0bf2f0eca6966bab39975adc440a9d9929dc8729bf92c95c3296dcb25b9"},"version":"3.2.7.4"}, - "ansi-terminal": {"dependencies":["base","colour"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/ansi-terminal-0.11.4/ansi-terminal-0.11.4.tar.gz"},"name":"ansi-terminal","pinned":{"url":["https://hackage.haskell.org/package/ansi-terminal-0.11.4/ansi-terminal-0.11.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/ansi-terminal-0.11.4.tar.gz"],"sha256":"7898e48f0a535c1857cde52c803f28096ba89759461fe4d157fd55dcdb420e25","cabal-sha256":"410737137c798e23339a08435a5511785ebf1db08700e37debbd7801cf73fc82"},"version":"0.11.4"}, - "ansi-wl-pprint": {"dependencies":["ansi-terminal","base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/ansi-wl-pprint-0.6.9/ansi-wl-pprint-0.6.9.tar.gz"},"name":"ansi-wl-pprint","pinned":{"url":["https://hackage.haskell.org/package/ansi-wl-pprint-0.6.9/ansi-wl-pprint-0.6.9.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/ansi-wl-pprint-0.6.9.tar.gz"],"sha256":"a7b2e8e7cd3f02f2954e8b17dc60a0ccd889f49e2068ebb15abfa1d42f7a4eac","cabal-sha256":"fb737bc96e2aef34ad595d54ced7a73f648c521ebcb00fe0679aff45ccd49212"},"version":"0.6.9"}, - "array": {"dependencies":[],"location":{"type":"core"},"name":"array","version":"0.5.4.0"}, - "async": {"dependencies":["base","hashable","stm"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/async-2.2.4/async-2.2.4.tar.gz"},"name":"async","pinned":{"url":["https://hackage.haskell.org/package/async-2.2.4/async-2.2.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/async-2.2.4.tar.gz"],"sha256":"484df85be0e76c4fed9376451e48e1d0c6e97952ce79735b72d54297e7e0a725","cabal-sha256":"9b8ceefce014e490f9e1335fa5f511161309926c55d01cec795016f4363b5d2d"},"version":"2.2.4"}, - "atomic-primops": {"dependencies":["base","ghc-prim","primitive"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/atomic-primops-0.8.4/atomic-primops-0.8.4.tar.gz"},"name":"atomic-primops","pinned":{"url":["https://hackage.haskell.org/package/atomic-primops-0.8.4/atomic-primops-0.8.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/atomic-primops-0.8.4.tar.gz"],"sha256":"22a8617eb9e221b5daee1ae26ccce279ce3d7a53d76e82c767708f90a6c72d3e","cabal-sha256":"5218db0d8d4efe203a06c4643a0c6aeb3ab1abe159e92c122decc4f0dd1b5f38"},"version":"0.8.4"}, - "attoparsec": {"dependencies":["array","base","bytestring","containers","deepseq","ghc-prim","scientific","text","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/attoparsec-0.14.4/attoparsec-0.14.4.tar.gz"},"name":"attoparsec","pinned":{"url":["https://hackage.haskell.org/package/attoparsec-0.14.4/attoparsec-0.14.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/attoparsec-0.14.4.tar.gz"],"sha256":"3f337fe58624565de12426f607c23e60c7b09c86b4e3adfc827ca188c9979e6c","cabal-sha256":"ec709539b881d6431620bd7c40fbfa680aaf4a98c6f35b51536d8f455682b1ae"},"version":"0.14.4"}, - "base": {"dependencies":[],"location":{"type":"core"},"name":"base","version":"4.16.4.0"}, - "base-compat": {"dependencies":["base","ghc-prim","unix"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/base-compat-0.12.2/base-compat-0.12.2.tar.gz"},"name":"base-compat","pinned":{"url":["https://hackage.haskell.org/package/base-compat-0.12.2/base-compat-0.12.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/base-compat-0.12.2.tar.gz"],"sha256":"a62adc883a5ac436f80e4ae02c3c56111cf1007492f267c291139a668d2150bd","cabal-sha256":"85d820a15e3f00f1781ac939cb9cdccdcc6f38c43e4c74a6e83e5d75f67b61a0"},"version":"0.12.2"}, - "base-compat-batteries": {"dependencies":["base","base-compat","ghc-prim"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/base-compat-batteries-0.12.2/base-compat-batteries-0.12.2.tar.gz"},"name":"base-compat-batteries","pinned":{"url":["https://hackage.haskell.org/package/base-compat-batteries-0.12.2/base-compat-batteries-0.12.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/base-compat-batteries-0.12.2.tar.gz"],"sha256":"ede9092e07f904e0759160bf1ecd3fb7eb043bae6dc89a37c3dc94829ec5eb99","cabal-sha256":"ecf0bb2b39be54f1ffa185d37663702b0651d34d1cdcc32d32bb8f7279396afe"},"version":"0.12.2"}, - "base-orphans": {"dependencies":["base","ghc-prim"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/base-orphans-0.8.8.2/base-orphans-0.8.8.2.tar.gz"},"name":"base-orphans","pinned":{"url":["https://hackage.haskell.org/package/base-orphans-0.8.8.2/base-orphans-0.8.8.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/base-orphans-0.8.8.2.tar.gz"],"sha256":"61cae7063884128dc98596ab7d8e6d896f6b0fa3da4e12310c850c8c08825092","cabal-sha256":"b62d60c8b7c507f0d0085925fad398e4fcda928c14b524be0148effd99cfb97d"},"version":"0.8.8.2"}, - "bifunctors": {"dependencies":["base","base-orphans","comonad","containers","tagged","template-haskell","th-abstraction","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/bifunctors-5.5.15/bifunctors-5.5.15.tar.gz"},"name":"bifunctors","pinned":{"url":["https://hackage.haskell.org/package/bifunctors-5.5.15/bifunctors-5.5.15.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/bifunctors-5.5.15.tar.gz"],"sha256":"d6359d50d359dd6048dbf6d56c7628211a1785aab9174177faa6d2d8b0d9e3b7","cabal-sha256":"5ebaf9a1996de38ad9d77bec37a5585b6461b34f39446e8f1cadae7689a12bfd"},"version":"5.5.15"}, - "binary": {"dependencies":[],"location":{"type":"core"},"name":"binary","version":"0.8.9.0"}, - "bytestring": {"dependencies":[],"location":{"type":"core"},"name":"bytestring","version":"0.11.4.0"}, - "bytestring-builder": {"dependencies":["base","bytestring","deepseq"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/bytestring-builder-0.10.8.2.0/bytestring-builder-0.10.8.2.0.tar.gz"},"name":"bytestring-builder","pinned":{"url":["https://hackage.haskell.org/package/bytestring-builder-0.10.8.2.0/bytestring-builder-0.10.8.2.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/bytestring-builder-0.10.8.2.0.tar.gz"],"sha256":"27faef6db27c5be5a3715fd68b93725853e0e668849eaf92ce7c33cef9cb2c3f","cabal-sha256":"6b2b812cdac53f5a2c82376a416dde04adbb5ca3e1604c0d075368a0498f762b"},"version":"0.10.8.2.0"}, - "c2hs": {"dependencies":["array","base","bytestring","containers","directory","dlist","filepath","language-c","pretty","process"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/c2hs-0.28.8/c2hs-0.28.8.tar.gz"},"name":"c2hs","pinned":{"url":["https://hackage.haskell.org/package/c2hs-0.28.8/c2hs-0.28.8.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/c2hs-0.28.8.tar.gz"],"sha256":"390632cffc561c32483af474aac50168a68f0fa382096552e37749923617884c","cabal-sha256":"c399132e2273e70770be403fba4795d7d8c60d7bd147f0ef174342bebbd44392"},"version":"0.28.8"}, - "cabal-doctest": {"dependencies":["Cabal","base","directory","filepath"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/cabal-doctest-1.0.9/cabal-doctest-1.0.9.tar.gz"},"name":"cabal-doctest","pinned":{"url":["https://hackage.haskell.org/package/cabal-doctest-1.0.9/cabal-doctest-1.0.9.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/cabal-doctest-1.0.9.tar.gz"],"sha256":"5556088496111d33810c4ae6c4a065bb37fa3315e9e8891e8000b1ab6707ba73","cabal-sha256":"6dea0dbd1457f43d96ce1cfb1bab8b9f55d4fb82940e2bfa5aad78e6e2260656"},"version":"1.0.9"}, - "call-stack": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/call-stack-0.4.0/call-stack-0.4.0.tar.gz"},"name":"call-stack","pinned":{"url":["https://hackage.haskell.org/package/call-stack-0.4.0/call-stack-0.4.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/call-stack-0.4.0.tar.gz"],"sha256":"430bcf8a3404f7e55319573c0b807b1356946f0c8f289bb3d9afb279c636b87b","cabal-sha256":"ac44d2c00931dc20b01750da8c92ec443eb63a7231e8550188cb2ac2385f7feb"},"version":"0.4.0"}, - "clock": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/clock-0.8.3/clock-0.8.3.tar.gz"},"name":"clock","pinned":{"url":["https://hackage.haskell.org/package/clock-0.8.3/clock-0.8.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/clock-0.8.3.tar.gz"],"sha256":"845ce5db4c98cefd517323e005f87effceff886987305e421c4ef616dc0505d1","cabal-sha256":"a692159828c2cd278eaec317b3a7e9fb6d7b787c8a19f086004d15d9fa1fd72c"},"version":"0.8.3"}, - "code-page": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/code-page-0.2.1/code-page-0.2.1.tar.gz"},"name":"code-page","pinned":{"url":["https://hackage.haskell.org/package/code-page-0.2.1/code-page-0.2.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/code-page-0.2.1.tar.gz"],"sha256":"b2f90e19c61ed8a6ff7295f7f123d4a9913c790d4cf2c6029bc299293fdb2aaa","cabal-sha256":"fe596b0f421abd2894fdb7049b3d76230eb1de6e04e9f635e2695dd55ded856e"},"version":"0.2.1"}, - "colour": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/colour-2.3.6/colour-2.3.6.tar.gz"},"name":"colour","pinned":{"url":["https://hackage.haskell.org/package/colour-2.3.6/colour-2.3.6.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/colour-2.3.6.tar.gz"],"sha256":"2cd35dcd6944a5abc9f108a5eb5ee564b6b1fa98a9ec79cefcc20b588991f871","cabal-sha256":"ebdcbf15023958838a527e381ab3c3b1e99ed12d1b25efeb7feaa4ad8c37664a"},"version":"2.3.6"}, - "comonad": {"dependencies":["base","containers","distributive","indexed-traversable","tagged","transformers","transformers-compat"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/comonad-5.0.8/comonad-5.0.8.tar.gz"},"name":"comonad","pinned":{"url":["https://hackage.haskell.org/package/comonad-5.0.8/comonad-5.0.8.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/comonad-5.0.8.tar.gz"],"sha256":"ef6cdf2cc292cc43ee6aa96c581b235fdea8ab44a0bffb24dc79ae2b2ef33d13","cabal-sha256":"4a4dbfbd03fb4963987710fca994e8b5624bd05a33e5f95b7581b26f8229c5e3"},"version":"5.0.8"}, - "conduit": {"dependencies":["base","bytestring","directory","exceptions","filepath","mono-traversable","mtl","primitive","resourcet","text","transformers","unix","unliftio-core","vector"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/conduit-1.3.5/conduit-1.3.5.tar.gz"},"name":"conduit","pinned":{"url":["https://hackage.haskell.org/package/conduit-1.3.5/conduit-1.3.5.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/conduit-1.3.5.tar.gz"],"sha256":"2bb0d3e0eecc43e3d1d8cfc2125914f9175cde752be2d5908a1e120f321c782d","cabal-sha256":"22665df25c9c158d5fcfb299e46b0b642868add42a6bb13b79d457dc7ff7be1a"},"version":"1.3.5"}, - "conduit-extra": {"dependencies":["async","attoparsec","base","bytestring","conduit","directory","filepath","network","primitive","process","resourcet","stm","streaming-commons","text","transformers","typed-process","unliftio-core"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/conduit-extra-1.3.6/conduit-extra-1.3.6.tar.gz"},"name":"conduit-extra","pinned":{"url":["https://hackage.haskell.org/package/conduit-extra-1.3.6/conduit-extra-1.3.6.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/conduit-extra-1.3.6.tar.gz"],"sha256":"8950c38049d892c38590d389bed49ecf880671f58ec63dd4709d9fe3d4b8f153","cabal-sha256":"83303e6fea78a683fdbb41682fc8dbc47b1d8830da1f09e88940f9a744a7f984"},"version":"1.3.6"}, - "containers": {"dependencies":[],"location":{"type":"core"},"name":"containers","version":"0.6.5.1"}, - "contravariant": {"dependencies":["StateVar","base","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/contravariant-1.5.5/contravariant-1.5.5.tar.gz"},"name":"contravariant","pinned":{"url":["https://hackage.haskell.org/package/contravariant-1.5.5/contravariant-1.5.5.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/contravariant-1.5.5.tar.gz"],"sha256":"062fd66580d7aad0b5ba93e644ffa7feee69276ef50f20d4ed9f1deb7642dffa","cabal-sha256":"470ed0e040e879e2da4af1b2c8f94e199f6135852a8107858d5ae0a95365835f"},"version":"1.5.5"}, - "data-array-byte": {"dependencies":["base","deepseq","template-haskell"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/data-array-byte-0.1.0.1/data-array-byte-0.1.0.1.tar.gz"},"name":"data-array-byte","pinned":{"url":["https://hackage.haskell.org/package/data-array-byte-0.1.0.1/data-array-byte-0.1.0.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/data-array-byte-0.1.0.1.tar.gz"],"sha256":"1bb6eca0b3e02d057fe7f4e14c81ef395216f421ab30fdaa1b18017c9c025600","cabal-sha256":"ad89e28b2b046175698fbf542af2ce43e5d2af50aae9f48d12566b1bb3de1d3c"},"version":"0.1.0.1"}, - "data-default-class": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/data-default-class-0.1.2.0/data-default-class-0.1.2.0.tar.gz"},"name":"data-default-class","pinned":{"url":["https://hackage.haskell.org/package/data-default-class-0.1.2.0/data-default-class-0.1.2.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/data-default-class-0.1.2.0.tar.gz"],"sha256":"4f01b423f000c3e069aaf52a348564a6536797f31498bb85c3db4bd2d0973e56","cabal-sha256":"63e62120b7efd733a5a17cf59ceb43268e9a929c748127172d7d42f4a336e327"},"version":"0.1.2.0"}, - "deepseq": {"dependencies":[],"location":{"type":"core"},"name":"deepseq","version":"1.4.6.1"}, - "directory": {"dependencies":[],"location":{"type":"core"},"name":"directory","version":"1.3.6.2"}, - "distributive": {"dependencies":["base","base-orphans","tagged","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/distributive-0.6.2.1/distributive-0.6.2.1.tar.gz"},"name":"distributive","pinned":{"url":["https://hackage.haskell.org/package/distributive-0.6.2.1/distributive-0.6.2.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/distributive-0.6.2.1.tar.gz"],"sha256":"d7351392e078f58caa46630a4b9c643e1e2e9dddee45848c5c8358e7b1316b91","cabal-sha256":"0f99f5541cca04acf89b64432b03422b6408e830a8dff30e6c4334ef1a48680c"},"version":"0.6.2.1"}, - "dlist": {"dependencies":["base","deepseq"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/dlist-1.0/dlist-1.0.tar.gz"},"name":"dlist","pinned":{"url":["https://hackage.haskell.org/package/dlist-1.0/dlist-1.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/dlist-1.0.tar.gz"],"sha256":"173d637328bb173fcc365f30d29ff4a94292a1e0e5558aeb3dfc11de81510115","cabal-sha256":"55ff69d20ce638fc7727342ee67f2f868da61d3dcf3763f790bf9aa0b145e568"},"version":"1.0"}, - "doctest": {"dependencies":["base","base-compat","code-page","deepseq","directory","exceptions","filepath","ghc","ghc-paths","process","syb","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/doctest-0.20.1/doctest-0.20.1.tar.gz"},"name":"doctest","pinned":{"url":["https://hackage.haskell.org/package/doctest-0.20.1/doctest-0.20.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/doctest-0.20.1.tar.gz"],"sha256":"44a56fd4b70f22f314ad67dcff21e32e8e96da2129d2405cb5a177cc36be4b02","cabal-sha256":"c0e08af88e034f41673477be0350ceae69faea2db03a4c10b289fa9c20d27cbb"},"version":"0.20.1"}, - "exceptions": {"dependencies":[],"location":{"type":"core"},"name":"exceptions","version":"0.10.4"}, - "filepath": {"dependencies":[],"location":{"type":"core"},"name":"filepath","version":"1.4.2.2"}, - "first-class-families": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/first-class-families-0.8.0.1/first-class-families-0.8.0.1.tar.gz"},"name":"first-class-families","pinned":{"url":["https://hackage.haskell.org/package/first-class-families-0.8.0.1/first-class-families-0.8.0.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/first-class-families-0.8.0.1.tar.gz"],"sha256":"4a1c8fbdbe01757ea8dc3190050d7a4a72c86e205d23676182292fe192c1da72","cabal-sha256":"d7a60485a2f392818808d4decbc6af7c20281713ec1d81948747f1c9c8c2b145"},"version":"0.8.0.1"}, - "generic-deriving": {"dependencies":["base","containers","ghc-prim","template-haskell","th-abstraction"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/generic-deriving-1.14.4/generic-deriving-1.14.4.tar.gz"},"name":"generic-deriving","pinned":{"url":["https://hackage.haskell.org/package/generic-deriving-1.14.4/generic-deriving-1.14.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/generic-deriving-1.14.4.tar.gz"],"sha256":"372b87b2c91ed4ceff8602024a484944f4653456066755803b5cb268fed8195c","cabal-sha256":"8395764ff8bef9e688b9681dff3bcd0dbb324a22192e5981bcba10afa75b9ac4"},"version":"1.14.4"}, - "ghc": {"dependencies":[],"location":{"type":"core"},"name":"ghc","version":"9.2.8"}, - "ghc-bignum": {"dependencies":[],"location":{"type":"core"},"name":"ghc-bignum","version":"1.2"}, - "ghc-boot": {"dependencies":[],"location":{"type":"core"},"name":"ghc-boot","version":"9.2.8"}, - "ghc-boot-th": {"dependencies":[],"location":{"type":"core"},"name":"ghc-boot-th","version":"9.2.8"}, - "ghc-check": {"dependencies":["base","containers","directory","filepath","ghc","ghc-boot","ghc-paths","process","safe-exceptions","template-haskell","th-compat","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/ghc-check-0.5.0.8/ghc-check-0.5.0.8.tar.gz"},"name":"ghc-check","pinned":{"url":["https://hackage.haskell.org/package/ghc-check-0.5.0.8/ghc-check-0.5.0.8.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/ghc-check-0.5.0.8.tar.gz"],"sha256":"1025a8353fb7c318b27b8dc6b268d22f1f64c271031ed0ce4defb0f9100d7cd4","cabal-sha256":"4abee5e907b63c986ff4f130fa5a02a933a165af18bda98bff380763a9c1ad47"},"version":"0.5.0.8"}, - "ghc-heap": {"dependencies":[],"location":{"type":"core"},"name":"ghc-heap","version":"9.2.8"}, - "ghc-paths": {"dependencies":["base"],"location":{"type":"vendored"},"name":"ghc-paths","version":"0.1.0.11"}, - "ghc-prim": {"dependencies":[],"location":{"type":"core"},"name":"ghc-prim","version":"0.8.0"}, - "ghc-source-gen": {"dependencies":["base","ghc"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/ghc-source-gen-0.4.3.0/ghc-source-gen-0.4.3.0.tar.gz"},"name":"ghc-source-gen","pinned":{"url":["https://hackage.haskell.org/package/ghc-source-gen-0.4.3.0/ghc-source-gen-0.4.3.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/ghc-source-gen-0.4.3.0.tar.gz"],"sha256":"0e88038ab714cbe420da8ea15f5cd78565828e9dd956a461283bbe15e9d418d2","cabal-sha256":"9058ddc2e3201d7b2e5a91b79d76f952c5fb01fb34d742143e9c9b365589ad35"},"version":"0.4.3.0"}, - "happy": {"dependencies":["array","base","containers","mtl"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/happy-1.20.1.1/happy-1.20.1.1.tar.gz"},"name":"happy","pinned":{"url":["https://hackage.haskell.org/package/happy-1.20.1.1/happy-1.20.1.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/happy-1.20.1.1.tar.gz"],"sha256":"8b4e7dc5a6c5fd666f8f7163232931ab28746d0d17da8fa1cbd68be9e878881b","cabal-sha256":"a381633c5e8f9e9e5a8e1900930ce13172397b4677fcfcc08cd38eb3f73b61b1"},"version":"1.20.1.1"}, - "hashable": {"dependencies":["base","bytestring","containers","data-array-byte","deepseq","filepath","ghc-bignum","ghc-prim","text"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/hashable-1.4.2.0/hashable-1.4.2.0.tar.gz"},"name":"hashable","pinned":{"url":["https://hackage.haskell.org/package/hashable-1.4.2.0/hashable-1.4.2.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/hashable-1.4.2.0.tar.gz"],"sha256":"1b4000ea82b81f69d46d0af4152c10c6303873510738e24cfc4767760d30e3f8","cabal-sha256":"585792335d5541dba78fa8dfcb291a89cd5812a281825ff7a44afa296ab5d58a"},"version":"1.4.2.0"}, - "hspec": {"dependencies":["QuickCheck","base","hspec-core","hspec-discover","hspec-expectations"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/hspec-2.9.7/hspec-2.9.7.tar.gz"},"name":"hspec","pinned":{"url":["https://hackage.haskell.org/package/hspec-2.9.7/hspec-2.9.7.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/hspec-2.9.7.tar.gz"],"sha256":"81ddacf76445fb547010d3582ec9d81d7cd9285258ca74bfeefd653525765a24","cabal-sha256":"68732c76946f111db3ecf28fa1ab11f1468c287448b139e57d543bd25a382cf0"},"version":"2.9.7"}, - "hspec-core": {"dependencies":["HUnit","QuickCheck","ansi-terminal","array","base","call-stack","clock","deepseq","directory","filepath","ghc","ghc-boot-th","hspec-expectations","quickcheck-io","random","setenv","stm","tf-random","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/hspec-core-2.9.7/hspec-core-2.9.7.tar.gz"},"name":"hspec-core","pinned":{"url":["https://hackage.haskell.org/package/hspec-core-2.9.7/hspec-core-2.9.7.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/hspec-core-2.9.7.tar.gz"],"sha256":"16819b4b10fd22be4a72ec7f919417f722b0eba448c62be538e34e8e23fe1910","cabal-sha256":"153ca954ceb8eb7dff782d3de9af59553bc54284a45e7085aca5b443a5486111"},"version":"2.9.7"}, - "hspec-discover": {"dependencies":["base","directory","filepath"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/hspec-discover-2.9.7/hspec-discover-2.9.7.tar.gz"},"name":"hspec-discover","pinned":{"url":["https://hackage.haskell.org/package/hspec-discover-2.9.7/hspec-discover-2.9.7.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/hspec-discover-2.9.7.tar.gz"],"sha256":"65e933fe21a88a15409b0ec4d6d67fccacbaa410b96ece9e59e81a2e7b9b6614","cabal-sha256":"7b8e52d85c07e8cfed6723255f738fb69ae08d3c0edfd3e458837496897ee629"},"version":"2.9.7"}, - "hspec-expectations": {"dependencies":["HUnit","base","call-stack"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/hspec-expectations-0.8.2/hspec-expectations-0.8.2.tar.gz"},"name":"hspec-expectations","pinned":{"url":["https://hackage.haskell.org/package/hspec-expectations-0.8.2/hspec-expectations-0.8.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/hspec-expectations-0.8.2.tar.gz"],"sha256":"819607ea1faf35ce5be34be61c6f50f3389ea43892d56fb28c57a9f5d54fb4ef","cabal-sha256":"e2db24881baadc2d9d23b03cb629e80dcbda89a6b04ace9adb5f4d02ef8b31aa"},"version":"0.8.2"}, - "indexed-traversable": {"dependencies":["array","base","containers","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/indexed-traversable-0.1.2.1/indexed-traversable-0.1.2.1.tar.gz"},"name":"indexed-traversable","pinned":{"url":["https://hackage.haskell.org/package/indexed-traversable-0.1.2.1/indexed-traversable-0.1.2.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/indexed-traversable-0.1.2.1.tar.gz"],"sha256":"fe854c10285debc7d6fe3e09da0928a740ebc091ad2911ae695bb007e6f746a4","cabal-sha256":"154b4649199a602dea948a93cb34a6c4be71576c4f78410733dd9f6bc79b6e0b"},"version":"0.1.2.1"}, - "integer-logarithms": {"dependencies":["array","base","ghc-bignum","ghc-prim"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/integer-logarithms-1.0.3.1/integer-logarithms-1.0.3.1.tar.gz"},"name":"integer-logarithms","pinned":{"url":["https://hackage.haskell.org/package/integer-logarithms-1.0.3.1/integer-logarithms-1.0.3.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/integer-logarithms-1.0.3.1.tar.gz"],"sha256":"9b0a9f9fab609b15cd015865721fb05f744a1bc77ae92fd133872de528bbea7f","cabal-sha256":"4d0dfc334e64ff57bb1a08717afa4a4a7f28e4cdc46615dd287be31ef63ec00d"},"version":"1.0.3.1"}, - "language-c": {"dependencies":["alex","array","base","bytestring","containers","deepseq","directory","filepath","happy","mtl","pretty","process"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/language-c-0.9.2/language-c-0.9.2.tar.gz"},"name":"language-c","pinned":{"url":["https://hackage.haskell.org/package/language-c-0.9.2/language-c-0.9.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/language-c-0.9.2.tar.gz"],"sha256":"b2310d2fda16df72e9f8f63ef18bec2e09ae3aff5891dc948c3d9cb72cef6cb3","cabal-sha256":"a4b77129d7d30d777e0f203ba9c18b88f4791f95c079fef573b554f915dcf57d"},"version":"0.9.2"}, - "lens-family": {"dependencies":["base","containers","lens-family-core","mtl","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/lens-family-2.1.2/lens-family-2.1.2.tar.gz"},"name":"lens-family","pinned":{"url":["https://hackage.haskell.org/package/lens-family-2.1.2/lens-family-2.1.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/lens-family-2.1.2.tar.gz"],"sha256":"2b60afc3afc03b6e328fc96e291e21bb0a63b563657cabe7ba5febd471283648","cabal-sha256":"c13af34889ed9637b2dbd4542122c01a6ec1351cc6dda673de0079f9b02747ef"},"version":"2.1.2"}, - "lens-family-core": {"dependencies":["base","containers","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/lens-family-core-2.1.2/lens-family-core-2.1.2.tar.gz"},"name":"lens-family-core","pinned":{"url":["https://hackage.haskell.org/package/lens-family-core-2.1.2/lens-family-core-2.1.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/lens-family-core-2.1.2.tar.gz"],"sha256":"1b5a997276c8b77a96f99f48b95b204d34f3bb84fa3691747cd30bc8c76873b6","cabal-sha256":"702013af981089f991c93598762b8804314266c2bd7d92fc35fb6a8b62af1883"},"version":"2.1.2"}, - "mmorph": {"dependencies":["base","mtl","transformers","transformers-compat"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/mmorph-1.2.0/mmorph-1.2.0.tar.gz"},"name":"mmorph","pinned":{"url":["https://hackage.haskell.org/package/mmorph-1.2.0/mmorph-1.2.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/mmorph-1.2.0.tar.gz"],"sha256":"61338058eb676b466a462ca45d59f436a77a3bd6b816e4268c6d88522b6a4280","cabal-sha256":"df9b213ec18f811cb3137b478d148f3f1680ee43f841cb775835fa282fdb0295"},"version":"1.2.0"}, - "mono-traversable": {"dependencies":["base","bytestring","containers","hashable","split","text","transformers","unordered-containers","vector","vector-algorithms"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/mono-traversable-1.0.15.3/mono-traversable-1.0.15.3.tar.gz"},"name":"mono-traversable","pinned":{"url":["https://hackage.haskell.org/package/mono-traversable-1.0.15.3/mono-traversable-1.0.15.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/mono-traversable-1.0.15.3.tar.gz"],"sha256":"98b220f3313d74227a4249210c8818e839678343e62b3ebb1b8c867cf2b974b7","cabal-sha256":"059bf3c05cdbef2d06b765333fe41c2168ced2503a23de674e2a59ceb2548c48"},"version":"1.0.15.3"}, - "mtl": {"dependencies":[],"location":{"type":"core"},"name":"mtl","version":"2.2.2"}, - "network": {"dependencies":["base","bytestring","deepseq","directory"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/network-3.1.4.0/network-3.1.4.0.tar.gz"},"name":"network","pinned":{"url":["https://hackage.haskell.org/package/network-3.1.4.0/network-3.1.4.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/network-3.1.4.0.tar.gz"],"sha256":"b452a2afac95d9207357eb3820c719c7c7d27871ef4b6ed7bfcd03a036b9158e","cabal-sha256":"e152cdb03243afb52bbc740cfbe96905ca298a6f6342f0c47b3f2e227ff19def"},"version":"3.1.4.0"}, - "optparse-applicative": {"dependencies":["ansi-wl-pprint","base","process","transformers","transformers-compat"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/optparse-applicative-0.17.1.0/optparse-applicative-0.17.1.0.tar.gz"},"name":"optparse-applicative","pinned":{"url":["https://hackage.haskell.org/package/optparse-applicative-0.17.1.0/optparse-applicative-0.17.1.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/optparse-applicative-0.17.1.0.tar.gz"],"sha256":"d179cb740139c55e6dada3c00efaea45f6853a1974d374668323bbbd07e0a5ef","cabal-sha256":"cb5f5f0dc9749846fc0e3df0041a8efee6368cc1cff07336acd4c3b02a951ed6"},"version":"0.17.1.0"}, - "parsec": {"dependencies":[],"location":{"type":"core"},"name":"parsec","version":"3.1.15.0"}, - "polysemy": {"dependencies":["Cabal","QuickCheck","async","base","cabal-doctest","containers","first-class-families","mtl","stm","syb","template-haskell","th-abstraction","transformers","type-errors","unagi-chan"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/polysemy-1.7.1.0/polysemy-1.7.1.0.tar.gz"},"name":"polysemy","pinned":{"url":["https://hackage.haskell.org/package/polysemy-1.7.1.0/polysemy-1.7.1.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/polysemy-1.7.1.0.tar.gz"],"sha256":"4c9556c0c3f38f5fa655567106ecb53cd357e6ffaf8289753ba6dc26fd4bc224","cabal-sha256":"3ead7a332abd70b202920ed3bf2e36866de163f821e643adfdcc9d39867b8033"},"version":"1.7.1.0"}, - "pretty": {"dependencies":[],"location":{"type":"core"},"name":"pretty","version":"1.1.3.6"}, - "primitive": {"dependencies":["base","deepseq","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/primitive-0.7.3.0/primitive-0.7.3.0.tar.gz"},"name":"primitive","pinned":{"url":["https://hackage.haskell.org/package/primitive-0.7.3.0/primitive-0.7.3.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/primitive-0.7.3.0.tar.gz"],"sha256":"3c0cfda67f1ee6f7f65108ad6f973b5bbb35ddba34b3c87746a7448f787501dc","cabal-sha256":"ce9361b4d2ed296ef639380411b4cfc217a19e4b3cd4170e03e6fce52daa0176"},"version":"0.7.3.0"}, - "process": {"dependencies":[],"location":{"type":"core"},"name":"process","version":"1.6.16.0"}, - "profunctors": {"dependencies":["base","base-orphans","bifunctors","comonad","contravariant","distributive","tagged","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/profunctors-5.6.2/profunctors-5.6.2.tar.gz"},"name":"profunctors","pinned":{"url":["https://hackage.haskell.org/package/profunctors-5.6.2/profunctors-5.6.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/profunctors-5.6.2.tar.gz"],"sha256":"65955d7b50525a4a3bccdab1d982d2ae342897fd38140d5a94b5ef3800d8c92a","cabal-sha256":"e178ba4468982326656626e2089e296f64485e68fdddc9f4476dcd5d612b4f78"},"version":"5.6.2"}, - "proto-lens": {"dependencies":["base","bytestring","containers","deepseq","ghc-prim","lens-family","parsec","pretty","primitive","profunctors","tagged","text","transformers","vector"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/proto-lens-0.7.1.3/proto-lens-0.7.1.3.tar.gz"},"name":"proto-lens","pinned":{"url":["https://hackage.haskell.org/package/proto-lens-0.7.1.3/proto-lens-0.7.1.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/proto-lens-0.7.1.3.tar.gz"],"sha256":"aac4317671a31d5f76cb120b5c4f75e644c45b441b4a2b9cfa7015bd8bbae3ac","cabal-sha256":"2d56bf8c37e21d741385e155d0dd327468ab1bc6897d10b0462b7e241d8e61a3"},"version":"0.7.1.3"}, - "proto-lens-protoc": {"dependencies":["base","bytestring","containers","filepath","ghc","ghc-paths","ghc-source-gen","lens-family","pretty","proto-lens","proto-lens-runtime","text"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/proto-lens-protoc-0.7.1.1/proto-lens-protoc-0.7.1.1.tar.gz"},"name":"proto-lens-protoc","pinned":{"url":["https://hackage.haskell.org/package/proto-lens-protoc-0.7.1.1/proto-lens-protoc-0.7.1.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/proto-lens-protoc-0.7.1.1.tar.gz"],"sha256":"0c412b47bce8a3898a61509b9a61c16e00ee947764bd22a07817ecc97a4080f2","cabal-sha256":"4b3b97d5caac9a9f8a85d426d5ad8a129f36e852dd05f42e614d9912030b9700"},"version":"0.7.1.1"}, - "proto-lens-runtime": {"dependencies":["base","bytestring","containers","deepseq","filepath","lens-family","proto-lens","text","vector"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/proto-lens-runtime-0.7.0.4/proto-lens-runtime-0.7.0.4.tar.gz"},"name":"proto-lens-runtime","pinned":{"url":["https://hackage.haskell.org/package/proto-lens-runtime-0.7.0.4/proto-lens-runtime-0.7.0.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/proto-lens-runtime-0.7.0.4.tar.gz"],"sha256":"5749cd01d97fd56bae5698830ba78adcc147e4b65b5e1b4b1cb6f9ee52587f47","cabal-sha256":"1a64cb98b49541e53ea8a19270d7247960445083a2327a091ce0a1cafdef16f3"},"version":"0.7.0.4"}, - "quickcheck-io": {"dependencies":["HUnit","QuickCheck","base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/quickcheck-io-0.2.0/quickcheck-io-0.2.0.tar.gz"},"name":"quickcheck-io","pinned":{"url":["https://hackage.haskell.org/package/quickcheck-io-0.2.0/quickcheck-io-0.2.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/quickcheck-io-0.2.0.tar.gz"],"sha256":"fb779119d79fe08ff4d502fb6869a70c9a8d5fd8ae0959f605c3c937efd96422","cabal-sha256":"7bf0b68fb90873825eb2e5e958c1b76126dcf984debb998e81673e6d837e0b2d"},"version":"0.2.0"}, - "random": {"dependencies":["base","bytestring","deepseq","mtl","splitmix"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/random-1.2.1.1/random-1.2.1.1.tar.gz"},"name":"random","pinned":{"url":["https://hackage.haskell.org/package/random-1.2.1.1/random-1.2.1.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/random-1.2.1.1.tar.gz"],"sha256":"3e1272f7ed6a4d7bd1712b90143ec326fee9b225789222379fea20a9c90c9b76","cabal-sha256":"e7c1f881159d5cc788619c9ee8b8f340ba2ff0db571cdf3d1a1968ebc5108789"},"version":"1.2.1.1"}, - "resourcet": {"dependencies":["base","containers","exceptions","mtl","primitive","transformers","unliftio-core"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/resourcet-1.2.6/resourcet-1.2.6.tar.gz"},"name":"resourcet","pinned":{"url":["https://hackage.haskell.org/package/resourcet-1.2.6/resourcet-1.2.6.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/resourcet-1.2.6.tar.gz"],"sha256":"f83b35b2106854750ef5f1c34695ea8b7bba6e0572cedf9f2993c5acfdb5fd34","cabal-sha256":"0c55be13d24c1e9c1e6d82327ac039a0bf41469c456e3ae678efa8a9beda3a74"},"version":"1.2.6"}, - "safe-exceptions": {"dependencies":["base","deepseq","exceptions","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/safe-exceptions-0.1.7.3/safe-exceptions-0.1.7.3.tar.gz"},"name":"safe-exceptions","pinned":{"url":["https://hackage.haskell.org/package/safe-exceptions-0.1.7.3/safe-exceptions-0.1.7.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/safe-exceptions-0.1.7.3.tar.gz"],"sha256":"91ce28d8f8a6efd31788d4827ed5cdcb9a546ad4053a86c56f7947c66a30b5bf","cabal-sha256":"6e9b1b233af80cc0aa17ea858d2641ba146fb11cbcc5970a52649e89d77282e2"},"version":"0.1.7.3"}, - "scientific": {"dependencies":["base","binary","bytestring","containers","deepseq","hashable","integer-logarithms","primitive","template-haskell","text"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/scientific-0.3.7.0/scientific-0.3.7.0.tar.gz"},"name":"scientific","pinned":{"url":["https://hackage.haskell.org/package/scientific-0.3.7.0/scientific-0.3.7.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/scientific-0.3.7.0.tar.gz"],"sha256":"a3a121c4b3d68fb8b9f8c709ab012e48f090ed553609247a805ad070d6b343a9","cabal-sha256":"909755ab19b453169ff85281323da1488407776b2360bd9f7afdd219fd306ef2"},"version":"0.3.7.0"}, - "setenv": {"dependencies":["base","unix"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/setenv-0.1.1.3/setenv-0.1.1.3.tar.gz"},"name":"setenv","pinned":{"url":["https://hackage.haskell.org/package/setenv-0.1.1.3/setenv-0.1.1.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/setenv-0.1.1.3.tar.gz"],"sha256":"e358df39afc03d5a39e2ec650652d845c85c80cc98fe331654deafb4767ecb32","cabal-sha256":"c5916ac0d2a828473cd171261328a290afe0abd799db1ac8c310682fe778c45b"},"version":"0.1.1.3"}, - "split": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/split-0.2.3.5/split-0.2.3.5.tar.gz"},"name":"split","pinned":{"url":["https://hackage.haskell.org/package/split-0.2.3.5/split-0.2.3.5.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/split-0.2.3.5.tar.gz"],"sha256":"bf8aa8d610354a2b576946a6c838251ec5988c8374100638e6b2604513b93159","cabal-sha256":"f472fa7019647cacac3267742a6f7ac0a5c816f9890e80e4b826cd937436de87"},"version":"0.2.3.5"}, - "splitmix": {"dependencies":["base","deepseq"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/splitmix-0.1.0.4/splitmix-0.1.0.4.tar.gz"},"name":"splitmix","pinned":{"url":["https://hackage.haskell.org/package/splitmix-0.1.0.4/splitmix-0.1.0.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/splitmix-0.1.0.4.tar.gz"],"sha256":"6d065402394e7a9117093dbb4530a21342c9b1e2ec509516c8a8d0ffed98ecaa","cabal-sha256":"db25c2e17967aa6b6046ab8b1b96ba3f344ca59a62b60fb6113d51ea305a3d8e"},"version":"0.1.0.4"}, - "stm": {"dependencies":[],"location":{"type":"core"},"name":"stm","version":"2.5.0.2"}, - "streaming": {"dependencies":["base","containers","ghc-prim","mmorph","mtl","transformers","transformers-base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/streaming-0.2.3.1/streaming-0.2.3.1.tar.gz"},"name":"streaming","pinned":{"url":["https://hackage.haskell.org/package/streaming-0.2.3.1/streaming-0.2.3.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/streaming-0.2.3.1.tar.gz"],"sha256":"fc5efae393750b9729ce5c5e979edcd3b9a5bf41ab927636174b01f999ffea88","cabal-sha256":"1f8866432934fe00d317576ddff3bba70a671b16073339c8f5e37fce42827518"},"version":"0.2.3.1"}, - "streaming-commons": {"dependencies":["array","async","base","bytestring","directory","network","process","random","stm","text","transformers","unix","zlib"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/streaming-commons-0.2.2.6/streaming-commons-0.2.2.6.tar.gz"},"name":"streaming-commons","pinned":{"url":["https://hackage.haskell.org/package/streaming-commons-0.2.2.6/streaming-commons-0.2.2.6.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/streaming-commons-0.2.2.6.tar.gz"],"sha256":"0180958a882eb0f6262b812fe886c2b1b8285474b5b958f814ae4f05409fbf79","cabal-sha256":"d5c6fb99efd4e71bdb0351d55f2d87e16c11880f42998e39363eb63f057ae24b"},"version":"0.2.2.6"}, - "syb": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/syb-0.7.2.3/syb-0.7.2.3.tar.gz"},"name":"syb","pinned":{"url":["https://hackage.haskell.org/package/syb-0.7.2.3/syb-0.7.2.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/syb-0.7.2.3.tar.gz"],"sha256":"d0b72daf16a947c4d9cb2d5774072f2153433224a04fd60fad60be9ffac8d91a","cabal-sha256":"d71f6747016466b0766491eae36be842ba98ba25e2aec26eaedbeea965c0586a"},"version":"0.7.2.3"}, - "tagged": {"dependencies":["base","deepseq","template-haskell","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/tagged-0.8.6.1/tagged-0.8.6.1.tar.gz"},"name":"tagged","pinned":{"url":["https://hackage.haskell.org/package/tagged-0.8.6.1/tagged-0.8.6.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/tagged-0.8.6.1.tar.gz"],"sha256":"f5e0fcf95f0bb4aa63f428f2c01955a41ea1a42cfcf39145ed631f59a9616c02","cabal-sha256":"8a24aef29b8e35447ccc56658ea07c2aded30bfa8130ea057e382936e17c74a6"},"version":"0.8.6.1"}, - "template-haskell": {"dependencies":[],"location":{"type":"core"},"name":"template-haskell","version":"2.18.0.0"}, - "temporary": {"dependencies":["base","directory","exceptions","filepath","random","transformers","unix"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/temporary-1.3/temporary-1.3.tar.gz"},"name":"temporary","pinned":{"url":["https://hackage.haskell.org/package/temporary-1.3/temporary-1.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/temporary-1.3.tar.gz"],"sha256":"8c442993694b5ffca823ce864af95bd2841fb5264ee511c61cf48cc71d879890","cabal-sha256":"3a66c136f700dbf42f3c5000ca93e80b26dead51e54322c83272b236c1ec8ef1"},"version":"1.3"}, - "text": {"dependencies":[],"location":{"type":"core"},"name":"text","version":"1.2.5.0"}, - "text-show": {"dependencies":["array","base","base-compat-batteries","bifunctors","bytestring","bytestring-builder","containers","generic-deriving","ghc-boot-th","ghc-prim","template-haskell","text","th-abstraction","th-lift","transformers","transformers-compat"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/text-show-3.10.3/text-show-3.10.3.tar.gz"},"name":"text-show","pinned":{"url":["https://hackage.haskell.org/package/text-show-3.10.3/text-show-3.10.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/text-show-3.10.3.tar.gz"],"sha256":"1e6afb6e36ae9580829c2806778cf75a55e3a8412afcde1b5c5378bc4266a938","cabal-sha256":"86b426acef96087f85565028ca7558f3ba1fd0a211deec7673fdb17ee0e3a747"},"version":"3.10.3"}, - "tf-random": {"dependencies":["base","primitive","random","time"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/tf-random-0.5/tf-random-0.5.tar.gz"},"name":"tf-random","pinned":{"url":["https://hackage.haskell.org/package/tf-random-0.5/tf-random-0.5.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/tf-random-0.5.tar.gz"],"sha256":"2e30cec027b313c9e1794d326635d8fc5f79b6bf6e7580ab4b00186dadc88510","cabal-sha256":"14012837d0f0e18fdbbe3d56e67da8622ee5e20b180abce952dd50bd9f36b326"},"version":"0.5"}, - "th-abstraction": {"dependencies":["base","containers","ghc-prim","template-haskell"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/th-abstraction-0.4.5.0/th-abstraction-0.4.5.0.tar.gz"},"name":"th-abstraction","pinned":{"url":["https://hackage.haskell.org/package/th-abstraction-0.4.5.0/th-abstraction-0.4.5.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/th-abstraction-0.4.5.0.tar.gz"],"sha256":"00d5e24f247e328bd9898d5af5915c1e86b134b4d40baa680258635f95031526","cabal-sha256":"c28f186ae9817a059e54f63689f8985194b7f58d8fbd79e157d12374b6f9d2c3"},"version":"0.4.5.0"}, - "th-compat": {"dependencies":["base","directory","filepath","template-haskell"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/th-compat-0.1.4/th-compat-0.1.4.tar.gz"},"name":"th-compat","pinned":{"url":["https://hackage.haskell.org/package/th-compat-0.1.4/th-compat-0.1.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/th-compat-0.1.4.tar.gz"],"sha256":"d8f97ac14ab47b6b8a7b0fdb4ff95426322ec56badd01652ac15da4a44d4bab8","cabal-sha256":"3e7d1b8f9c72cab04c8dfdfd26589dd7f31e015ad640a207aca3b654577532ff"},"version":"0.1.4"}, - "th-lift": {"dependencies":["base","ghc-prim","template-haskell","th-abstraction"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/th-lift-0.8.3/th-lift-0.8.3.tar.gz"},"name":"th-lift","pinned":{"url":["https://hackage.haskell.org/package/th-lift-0.8.3/th-lift-0.8.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/th-lift-0.8.3.tar.gz"],"sha256":"25d57bf5f8e7deefeb4ace0539805ae1e90b1ba5a034ebcc36141846408c6b75","cabal-sha256":"3043e803a08c22676dcf71a4021d0fa276fcecc2ac3dbc4b230fee0b994ca7e9"},"version":"0.8.3"}, - "time": {"dependencies":[],"location":{"type":"core"},"name":"time","version":"1.11.1.1"}, - "transformers": {"dependencies":[],"location":{"type":"core"},"name":"transformers","version":"0.5.6.2"}, - "transformers-base": {"dependencies":["base","base-orphans","stm","transformers","transformers-compat"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/transformers-base-0.4.6/transformers-base-0.4.6.tar.gz"},"name":"transformers-base","pinned":{"url":["https://hackage.haskell.org/package/transformers-base-0.4.6/transformers-base-0.4.6.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/transformers-base-0.4.6.tar.gz"],"sha256":"323bf8689eb691b122661cffa41a25e00fea7a768433fe2dde35d3da7d32cf90","cabal-sha256":"6f18f320e371c8954c4b6b211e2fdd5d15a6d6310bd605b9d640f47ede408961"},"version":"0.4.6"}, - "transformers-compat": {"dependencies":["base","ghc-prim","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/transformers-compat-0.7.2/transformers-compat-0.7.2.tar.gz"},"name":"transformers-compat","pinned":{"url":["https://hackage.haskell.org/package/transformers-compat-0.7.2/transformers-compat-0.7.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/transformers-compat-0.7.2.tar.gz"],"sha256":"b62c7304c9f3cbc9463d0739aa85cb9489f217ea092b9d625d417514fbcc9d6a","cabal-sha256":"044fb9955f63ee138fcebedfdcbe54afe741f2d5892a2d0bdf3a8052bd342643"},"version":"0.7.2"}, - "type-errors": {"dependencies":["base","first-class-families","syb","template-haskell","th-abstraction"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/type-errors-0.2.0.2/type-errors-0.2.0.2.tar.gz"},"name":"type-errors","pinned":{"url":["https://hackage.haskell.org/package/type-errors-0.2.0.2/type-errors-0.2.0.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/type-errors-0.2.0.2.tar.gz"],"sha256":"697cffdd1ec573d6b8d1539976673f93bb562ee97b644077e2305bfefc897c83","cabal-sha256":"afd6b33bb582730a90ea58fd23d5b32a38b5b6c8b2f18e3250936bdc0487dfab"},"version":"0.2.0.2"}, - "typed-process": {"dependencies":["async","base","bytestring","process","stm","transformers","unliftio-core"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/typed-process-0.2.11.0/typed-process-0.2.11.0.tar.gz"},"name":"typed-process","pinned":{"url":["https://hackage.haskell.org/package/typed-process-0.2.11.0/typed-process-0.2.11.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/typed-process-0.2.11.0.tar.gz"],"sha256":"948c59540675d85f35c99e285cdb8686713ec1689f530d5d21813239ea91f625","cabal-sha256":"defde2c4dcd07750381d6e15ee7a517938c8d6353abcf27bba9f290e75a67d39"},"version":"0.2.11.0"}, - "unagi-chan": {"dependencies":["atomic-primops","base","ghc-prim","primitive"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/unagi-chan-0.4.1.4/unagi-chan-0.4.1.4.tar.gz"},"name":"unagi-chan","pinned":{"url":["https://hackage.haskell.org/package/unagi-chan-0.4.1.4/unagi-chan-0.4.1.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/unagi-chan-0.4.1.4.tar.gz"],"sha256":"d9d6f4ab07def8e84a942bb23791830a61faf89166cb7185a3b2f97cb45128b5","cabal-sha256":"e9a282689a65fc66260557222789d14dcb7d299be0ab2d4e8e414b0d9f2ef459"},"version":"0.4.1.4"}, - "unix": {"dependencies":[],"location":{"type":"core"},"name":"unix","version":"2.7.2.2"}, - "unliftio-core": {"dependencies":["base","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/unliftio-core-0.2.1.0/unliftio-core-0.2.1.0.tar.gz"},"name":"unliftio-core","pinned":{"url":["https://hackage.haskell.org/package/unliftio-core-0.2.1.0/unliftio-core-0.2.1.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/unliftio-core-0.2.1.0.tar.gz"],"sha256":"99384cba8d56d9d61b85e38a313a93ebcdb78be6566367f0930ef580597fe3e3","cabal-sha256":"cb78a95718f9cb2579a8a1208d4a148ea358f0774321c8cb905bfb0b96a2813c"},"version":"0.2.1.0"}, - "unordered-containers": {"dependencies":["base","deepseq","hashable","template-haskell"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/unordered-containers-0.2.19.1/unordered-containers-0.2.19.1.tar.gz"},"name":"unordered-containers","pinned":{"url":["https://hackage.haskell.org/package/unordered-containers-0.2.19.1/unordered-containers-0.2.19.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/unordered-containers-0.2.19.1.tar.gz"],"sha256":"1b27bec5e0d522b27a6029ebf4c4a6d40acbc083c787008e32fb55c4b1d128d2","cabal-sha256":"1c28ca429e3960de0330908579a427ccacddd700cb84ec1969e2bbe576152add"},"version":"0.2.19.1"}, - "vector": {"dependencies":["base","deepseq","ghc-prim","primitive"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/vector-0.12.3.1/vector-0.12.3.1.tar.gz"},"name":"vector","pinned":{"url":["https://hackage.haskell.org/package/vector-0.12.3.1/vector-0.12.3.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/vector-0.12.3.1.tar.gz"],"sha256":"fb4a53c02bd4d7fdf155c0604da9a5bb0f3b3bfce5d9960aea11c2ae235b9f35","cabal-sha256":"39141f312871b7c793a63be76635999e84d442aa3290aec59f30638ec0bf23a7"},"version":"0.12.3.1"}, - "vector-algorithms": {"dependencies":["base","bytestring","primitive","vector"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/vector-algorithms-0.8.0.4/vector-algorithms-0.8.0.4.tar.gz"},"name":"vector-algorithms","pinned":{"url":["https://hackage.haskell.org/package/vector-algorithms-0.8.0.4/vector-algorithms-0.8.0.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/vector-algorithms-0.8.0.4.tar.gz"],"sha256":"76176a56778bf30a275b1089ee6db24ec6c67d92525145f8dfe215b80137af3b","cabal-sha256":"e0656aa47388e5c80e4f5d4fd87c80fb8d473fdd41533ff7af5cbb292056a544"},"version":"0.8.0.4"}, - "void": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/void-0.7.3/void-0.7.3.tar.gz"},"name":"void","pinned":{"url":["https://hackage.haskell.org/package/void-0.7.3/void-0.7.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/void-0.7.3.tar.gz"],"sha256":"53af758ddc37dc63981671e503438d02c6f64a2d8744e9bec557a894431f7317","cabal-sha256":"13d30f62fcdf065e595d679d4ac8b4b0c1bb1a1b73db7b5b5a8f857cb5c8a546"},"version":"0.7.3"}, - "zlib": {"dependencies":["base","bytestring"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/zlib-0.6.3.0/zlib-0.6.3.0.tar.gz"},"name":"zlib","pinned":{"url":["https://hackage.haskell.org/package/zlib-0.6.3.0/zlib-0.6.3.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/zlib-0.6.3.0.tar.gz"],"sha256":"9eaa989ad4534438b5beb51c1d3a4c8f6a088fdff0b259a5394fbf39aaee04da","cabal-sha256":"cf2a8edc1f4086934638d11882423780dd096c4e77d9c6639ccc469c6c26f041"},"version":"0.6.3.0"} - } -} \ No newline at end of file diff --git a/rules_haskell_tests/stackage_snapshot.json b/rules_haskell_tests/stackage_snapshot.json new file mode 120000 index 000000000..3607384e5 --- /dev/null +++ b/rules_haskell_tests/stackage_snapshot.json @@ -0,0 +1 @@ +stackage_snapshot_9.4.6.json \ No newline at end of file diff --git a/rules_haskell_tests/stackage_snapshot.yaml b/rules_haskell_tests/stackage_snapshot.yaml index 1a3eb097f..3ac86a6f4 120000 --- a/rules_haskell_tests/stackage_snapshot.yaml +++ b/rules_haskell_tests/stackage_snapshot.yaml @@ -1 +1 @@ -../stackage_snapshot.yaml \ No newline at end of file +stackage_snapshot_9.4.6.yaml \ No newline at end of file diff --git a/rules_haskell_tests/stackage_snapshot_9.2.8.json b/rules_haskell_tests/stackage_snapshot_9.2.8.json deleted file mode 120000 index c81f31ff7..000000000 --- a/rules_haskell_tests/stackage_snapshot_9.2.8.json +++ /dev/null @@ -1 +0,0 @@ -stackage_snapshot.json \ No newline at end of file diff --git a/rules_haskell_tests/stackage_snapshot_9.2.8.json b/rules_haskell_tests/stackage_snapshot_9.2.8.json new file mode 100644 index 000000000..c6f85530e --- /dev/null +++ b/rules_haskell_tests/stackage_snapshot_9.2.8.json @@ -0,0 +1,116 @@ +{ + "__GENERATED_FILE_DO_NOT_MODIFY_MANUALLY": -716374996, + "all-cabal-hashes": "https://raw.githubusercontent.com/commercialhaskell/all-cabal-hashes/80fe3174b98134e50d4541c9c2a3803601f6fbb7", + "resolved": { + "Cabal": {"dependencies":["array","base","binary","bytestring","containers","deepseq","directory","filepath","mtl","parsec","pretty","process","text","time","transformers","unix"],"location":{"commit":"42f04c3f639f10dc3c7981a0c663bfe08ad833cb","subdir":"Cabal","type":"git","url":"https://github.com/tweag/cabal"},"name":"Cabal","version":"3.6.3.0"}, + "HUnit": {"dependencies":["base","call-stack","deepseq"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/HUnit-1.6.2.0/HUnit-1.6.2.0.tar.gz"},"name":"HUnit","pinned":{"cabal-sha256":"1a79174e8af616117ad39464cac9de205ca923da6582825e97c10786fda933a4","sha256":"b0b7538871ffc058486fc00740886d2f3172f8fa6869936bfe83a5e10bd744ab","url":["https://hackage.haskell.org/package/HUnit-1.6.2.0/HUnit-1.6.2.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/HUnit-1.6.2.0.tar.gz"]},"version":"1.6.2.0"}, + "QuickCheck": {"dependencies":["base","containers","deepseq","random","splitmix","template-haskell","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/QuickCheck-2.14.3/QuickCheck-2.14.3.tar.gz"},"name":"QuickCheck","pinned":{"cabal-sha256":"f03d2f404d5ba465453d0fbc1944832789a759fe7c4f9bf8616bc1378a02fde4","sha256":"5c0f22b36b28a1a8fa110b3819818d3f29494a3b0dedbae299f064123ca70501","url":["https://hackage.haskell.org/package/QuickCheck-2.14.3/QuickCheck-2.14.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/QuickCheck-2.14.3.tar.gz"]},"version":"2.14.3"}, + "StateVar": {"dependencies":["base","stm","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/StateVar-1.2.2/StateVar-1.2.2.tar.gz"},"name":"StateVar","pinned":{"cabal-sha256":"3c022c00485fe165e3080d5da6b3ca9c9b02f62c5deebc584d1b3d1309ce673e","sha256":"5e4b39da395656a59827b0280508aafdc70335798b50e5d6fd52596026251825","url":["https://hackage.haskell.org/package/StateVar-1.2.2/StateVar-1.2.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/StateVar-1.2.2.tar.gz"]},"version":"1.2.2"}, + "alex": {"dependencies":["array","base","containers","directory"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/alex-3.2.7.4/alex-3.2.7.4.tar.gz"},"name":"alex","pinned":{"cabal-sha256":"91f4b0bf2f0eca6966bab39975adc440a9d9929dc8729bf92c95c3296dcb25b9","sha256":"8a13fa01ea00883aa3d75d15ce848835b18631b8c9a4966961492d7c6095226f","url":["https://hackage.haskell.org/package/alex-3.2.7.4/alex-3.2.7.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/alex-3.2.7.4.tar.gz"]},"version":"3.2.7.4"}, + "ansi-terminal": {"dependencies":["base","colour"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/ansi-terminal-0.11.4/ansi-terminal-0.11.4.tar.gz"},"name":"ansi-terminal","pinned":{"cabal-sha256":"410737137c798e23339a08435a5511785ebf1db08700e37debbd7801cf73fc82","sha256":"7898e48f0a535c1857cde52c803f28096ba89759461fe4d157fd55dcdb420e25","url":["https://hackage.haskell.org/package/ansi-terminal-0.11.4/ansi-terminal-0.11.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/ansi-terminal-0.11.4.tar.gz"]},"version":"0.11.4"}, + "ansi-wl-pprint": {"dependencies":["ansi-terminal","base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/ansi-wl-pprint-0.6.9/ansi-wl-pprint-0.6.9.tar.gz"},"name":"ansi-wl-pprint","pinned":{"cabal-sha256":"fb737bc96e2aef34ad595d54ced7a73f648c521ebcb00fe0679aff45ccd49212","sha256":"a7b2e8e7cd3f02f2954e8b17dc60a0ccd889f49e2068ebb15abfa1d42f7a4eac","url":["https://hackage.haskell.org/package/ansi-wl-pprint-0.6.9/ansi-wl-pprint-0.6.9.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/ansi-wl-pprint-0.6.9.tar.gz"]},"version":"0.6.9"}, + "array": {"dependencies":[],"location":{"type":"core"},"name":"array","version":"0.5.4.0"}, + "async": {"dependencies":["base","hashable","stm"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/async-2.2.4/async-2.2.4.tar.gz"},"name":"async","pinned":{"cabal-sha256":"9b8ceefce014e490f9e1335fa5f511161309926c55d01cec795016f4363b5d2d","sha256":"484df85be0e76c4fed9376451e48e1d0c6e97952ce79735b72d54297e7e0a725","url":["https://hackage.haskell.org/package/async-2.2.4/async-2.2.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/async-2.2.4.tar.gz"]},"version":"2.2.4"}, + "atomic-primops": {"dependencies":["base","ghc-prim","primitive"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/atomic-primops-0.8.4/atomic-primops-0.8.4.tar.gz"},"name":"atomic-primops","pinned":{"cabal-sha256":"5218db0d8d4efe203a06c4643a0c6aeb3ab1abe159e92c122decc4f0dd1b5f38","sha256":"22a8617eb9e221b5daee1ae26ccce279ce3d7a53d76e82c767708f90a6c72d3e","url":["https://hackage.haskell.org/package/atomic-primops-0.8.4/atomic-primops-0.8.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/atomic-primops-0.8.4.tar.gz"]},"version":"0.8.4"}, + "attoparsec": {"dependencies":["array","base","bytestring","containers","deepseq","ghc-prim","scientific","text","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/attoparsec-0.14.4/attoparsec-0.14.4.tar.gz"},"name":"attoparsec","pinned":{"cabal-sha256":"ec709539b881d6431620bd7c40fbfa680aaf4a98c6f35b51536d8f455682b1ae","sha256":"3f337fe58624565de12426f607c23e60c7b09c86b4e3adfc827ca188c9979e6c","url":["https://hackage.haskell.org/package/attoparsec-0.14.4/attoparsec-0.14.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/attoparsec-0.14.4.tar.gz"]},"version":"0.14.4"}, + "base": {"dependencies":[],"location":{"type":"core"},"name":"base","version":"4.16.4.0"}, + "base-compat": {"dependencies":["base","ghc-prim","unix"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/base-compat-0.12.2/base-compat-0.12.2.tar.gz"},"name":"base-compat","pinned":{"cabal-sha256":"85d820a15e3f00f1781ac939cb9cdccdcc6f38c43e4c74a6e83e5d75f67b61a0","sha256":"a62adc883a5ac436f80e4ae02c3c56111cf1007492f267c291139a668d2150bd","url":["https://hackage.haskell.org/package/base-compat-0.12.2/base-compat-0.12.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/base-compat-0.12.2.tar.gz"]},"version":"0.12.2"}, + "base-compat-batteries": {"dependencies":["base","base-compat","ghc-prim"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/base-compat-batteries-0.12.2/base-compat-batteries-0.12.2.tar.gz"},"name":"base-compat-batteries","pinned":{"cabal-sha256":"ecf0bb2b39be54f1ffa185d37663702b0651d34d1cdcc32d32bb8f7279396afe","sha256":"ede9092e07f904e0759160bf1ecd3fb7eb043bae6dc89a37c3dc94829ec5eb99","url":["https://hackage.haskell.org/package/base-compat-batteries-0.12.2/base-compat-batteries-0.12.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/base-compat-batteries-0.12.2.tar.gz"]},"version":"0.12.2"}, + "base-orphans": {"dependencies":["base","ghc-prim"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/base-orphans-0.8.8.2/base-orphans-0.8.8.2.tar.gz"},"name":"base-orphans","pinned":{"cabal-sha256":"b62d60c8b7c507f0d0085925fad398e4fcda928c14b524be0148effd99cfb97d","sha256":"61cae7063884128dc98596ab7d8e6d896f6b0fa3da4e12310c850c8c08825092","url":["https://hackage.haskell.org/package/base-orphans-0.8.8.2/base-orphans-0.8.8.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/base-orphans-0.8.8.2.tar.gz"]},"version":"0.8.8.2"}, + "bifunctors": {"dependencies":["base","base-orphans","comonad","containers","tagged","template-haskell","th-abstraction","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/bifunctors-5.5.15/bifunctors-5.5.15.tar.gz"},"name":"bifunctors","pinned":{"cabal-sha256":"5ebaf9a1996de38ad9d77bec37a5585b6461b34f39446e8f1cadae7689a12bfd","sha256":"d6359d50d359dd6048dbf6d56c7628211a1785aab9174177faa6d2d8b0d9e3b7","url":["https://hackage.haskell.org/package/bifunctors-5.5.15/bifunctors-5.5.15.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/bifunctors-5.5.15.tar.gz"]},"version":"5.5.15"}, + "binary": {"dependencies":[],"location":{"type":"core"},"name":"binary","version":"0.8.9.0"}, + "bytestring": {"dependencies":[],"location":{"type":"core"},"name":"bytestring","version":"0.11.4.0"}, + "bytestring-builder": {"dependencies":["base","bytestring","deepseq"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/bytestring-builder-0.10.8.2.0/bytestring-builder-0.10.8.2.0.tar.gz"},"name":"bytestring-builder","pinned":{"cabal-sha256":"6b2b812cdac53f5a2c82376a416dde04adbb5ca3e1604c0d075368a0498f762b","sha256":"27faef6db27c5be5a3715fd68b93725853e0e668849eaf92ce7c33cef9cb2c3f","url":["https://hackage.haskell.org/package/bytestring-builder-0.10.8.2.0/bytestring-builder-0.10.8.2.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/bytestring-builder-0.10.8.2.0.tar.gz"]},"version":"0.10.8.2.0"}, + "c2hs": {"dependencies":["array","base","bytestring","containers","directory","dlist","filepath","language-c","pretty","process"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/c2hs-0.28.8/c2hs-0.28.8.tar.gz"},"name":"c2hs","pinned":{"cabal-sha256":"c399132e2273e70770be403fba4795d7d8c60d7bd147f0ef174342bebbd44392","sha256":"390632cffc561c32483af474aac50168a68f0fa382096552e37749923617884c","url":["https://hackage.haskell.org/package/c2hs-0.28.8/c2hs-0.28.8.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/c2hs-0.28.8.tar.gz"]},"version":"0.28.8"}, + "cabal-doctest": {"dependencies":["Cabal","base","directory","filepath"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/cabal-doctest-1.0.9/cabal-doctest-1.0.9.tar.gz"},"name":"cabal-doctest","pinned":{"cabal-sha256":"6dea0dbd1457f43d96ce1cfb1bab8b9f55d4fb82940e2bfa5aad78e6e2260656","sha256":"5556088496111d33810c4ae6c4a065bb37fa3315e9e8891e8000b1ab6707ba73","url":["https://hackage.haskell.org/package/cabal-doctest-1.0.9/cabal-doctest-1.0.9.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/cabal-doctest-1.0.9.tar.gz"]},"version":"1.0.9"}, + "call-stack": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/call-stack-0.4.0/call-stack-0.4.0.tar.gz"},"name":"call-stack","pinned":{"cabal-sha256":"ac44d2c00931dc20b01750da8c92ec443eb63a7231e8550188cb2ac2385f7feb","sha256":"430bcf8a3404f7e55319573c0b807b1356946f0c8f289bb3d9afb279c636b87b","url":["https://hackage.haskell.org/package/call-stack-0.4.0/call-stack-0.4.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/call-stack-0.4.0.tar.gz"]},"version":"0.4.0"}, + "clock": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/clock-0.8.3/clock-0.8.3.tar.gz"},"name":"clock","pinned":{"cabal-sha256":"a692159828c2cd278eaec317b3a7e9fb6d7b787c8a19f086004d15d9fa1fd72c","sha256":"845ce5db4c98cefd517323e005f87effceff886987305e421c4ef616dc0505d1","url":["https://hackage.haskell.org/package/clock-0.8.3/clock-0.8.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/clock-0.8.3.tar.gz"]},"version":"0.8.3"}, + "code-page": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/code-page-0.2.1/code-page-0.2.1.tar.gz"},"name":"code-page","pinned":{"cabal-sha256":"fe596b0f421abd2894fdb7049b3d76230eb1de6e04e9f635e2695dd55ded856e","sha256":"b2f90e19c61ed8a6ff7295f7f123d4a9913c790d4cf2c6029bc299293fdb2aaa","url":["https://hackage.haskell.org/package/code-page-0.2.1/code-page-0.2.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/code-page-0.2.1.tar.gz"]},"version":"0.2.1"}, + "colour": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/colour-2.3.6/colour-2.3.6.tar.gz"},"name":"colour","pinned":{"cabal-sha256":"ebdcbf15023958838a527e381ab3c3b1e99ed12d1b25efeb7feaa4ad8c37664a","sha256":"2cd35dcd6944a5abc9f108a5eb5ee564b6b1fa98a9ec79cefcc20b588991f871","url":["https://hackage.haskell.org/package/colour-2.3.6/colour-2.3.6.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/colour-2.3.6.tar.gz"]},"version":"2.3.6"}, + "comonad": {"dependencies":["base","containers","distributive","indexed-traversable","tagged","transformers","transformers-compat"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/comonad-5.0.8/comonad-5.0.8.tar.gz"},"name":"comonad","pinned":{"cabal-sha256":"4a4dbfbd03fb4963987710fca994e8b5624bd05a33e5f95b7581b26f8229c5e3","sha256":"ef6cdf2cc292cc43ee6aa96c581b235fdea8ab44a0bffb24dc79ae2b2ef33d13","url":["https://hackage.haskell.org/package/comonad-5.0.8/comonad-5.0.8.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/comonad-5.0.8.tar.gz"]},"version":"5.0.8"}, + "conduit": {"dependencies":["base","bytestring","directory","exceptions","filepath","mono-traversable","mtl","primitive","resourcet","text","transformers","unix","unliftio-core","vector"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/conduit-1.3.5/conduit-1.3.5.tar.gz"},"name":"conduit","pinned":{"cabal-sha256":"22665df25c9c158d5fcfb299e46b0b642868add42a6bb13b79d457dc7ff7be1a","sha256":"2bb0d3e0eecc43e3d1d8cfc2125914f9175cde752be2d5908a1e120f321c782d","url":["https://hackage.haskell.org/package/conduit-1.3.5/conduit-1.3.5.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/conduit-1.3.5.tar.gz"]},"version":"1.3.5"}, + "conduit-extra": {"dependencies":["async","attoparsec","base","bytestring","conduit","directory","filepath","network","primitive","process","resourcet","stm","streaming-commons","text","transformers","typed-process","unliftio-core"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/conduit-extra-1.3.6/conduit-extra-1.3.6.tar.gz"},"name":"conduit-extra","pinned":{"cabal-sha256":"83303e6fea78a683fdbb41682fc8dbc47b1d8830da1f09e88940f9a744a7f984","sha256":"8950c38049d892c38590d389bed49ecf880671f58ec63dd4709d9fe3d4b8f153","url":["https://hackage.haskell.org/package/conduit-extra-1.3.6/conduit-extra-1.3.6.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/conduit-extra-1.3.6.tar.gz"]},"version":"1.3.6"}, + "containers": {"dependencies":[],"location":{"type":"core"},"name":"containers","version":"0.6.5.1"}, + "contravariant": {"dependencies":["StateVar","base","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/contravariant-1.5.5/contravariant-1.5.5.tar.gz"},"name":"contravariant","pinned":{"cabal-sha256":"470ed0e040e879e2da4af1b2c8f94e199f6135852a8107858d5ae0a95365835f","sha256":"062fd66580d7aad0b5ba93e644ffa7feee69276ef50f20d4ed9f1deb7642dffa","url":["https://hackage.haskell.org/package/contravariant-1.5.5/contravariant-1.5.5.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/contravariant-1.5.5.tar.gz"]},"version":"1.5.5"}, + "data-array-byte": {"dependencies":["base","deepseq","template-haskell"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/data-array-byte-0.1.0.1/data-array-byte-0.1.0.1.tar.gz"},"name":"data-array-byte","pinned":{"cabal-sha256":"ad89e28b2b046175698fbf542af2ce43e5d2af50aae9f48d12566b1bb3de1d3c","sha256":"1bb6eca0b3e02d057fe7f4e14c81ef395216f421ab30fdaa1b18017c9c025600","url":["https://hackage.haskell.org/package/data-array-byte-0.1.0.1/data-array-byte-0.1.0.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/data-array-byte-0.1.0.1.tar.gz"]},"version":"0.1.0.1"}, + "data-default-class": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/data-default-class-0.1.2.0/data-default-class-0.1.2.0.tar.gz"},"name":"data-default-class","pinned":{"cabal-sha256":"63e62120b7efd733a5a17cf59ceb43268e9a929c748127172d7d42f4a336e327","sha256":"4f01b423f000c3e069aaf52a348564a6536797f31498bb85c3db4bd2d0973e56","url":["https://hackage.haskell.org/package/data-default-class-0.1.2.0/data-default-class-0.1.2.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/data-default-class-0.1.2.0.tar.gz"]},"version":"0.1.2.0"}, + "deepseq": {"dependencies":[],"location":{"type":"core"},"name":"deepseq","version":"1.4.6.1"}, + "directory": {"dependencies":[],"location":{"type":"core"},"name":"directory","version":"1.3.6.2"}, + "distributive": {"dependencies":["base","base-orphans","tagged","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/distributive-0.6.2.1/distributive-0.6.2.1.tar.gz"},"name":"distributive","pinned":{"cabal-sha256":"0f99f5541cca04acf89b64432b03422b6408e830a8dff30e6c4334ef1a48680c","sha256":"d7351392e078f58caa46630a4b9c643e1e2e9dddee45848c5c8358e7b1316b91","url":["https://hackage.haskell.org/package/distributive-0.6.2.1/distributive-0.6.2.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/distributive-0.6.2.1.tar.gz"]},"version":"0.6.2.1"}, + "dlist": {"dependencies":["base","deepseq"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/dlist-1.0/dlist-1.0.tar.gz"},"name":"dlist","pinned":{"cabal-sha256":"55ff69d20ce638fc7727342ee67f2f868da61d3dcf3763f790bf9aa0b145e568","sha256":"173d637328bb173fcc365f30d29ff4a94292a1e0e5558aeb3dfc11de81510115","url":["https://hackage.haskell.org/package/dlist-1.0/dlist-1.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/dlist-1.0.tar.gz"]},"version":"1.0"}, + "doctest": {"dependencies":["base","base-compat","code-page","deepseq","directory","exceptions","filepath","ghc","ghc-paths","process","syb","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/doctest-0.20.1/doctest-0.20.1.tar.gz"},"name":"doctest","pinned":{"cabal-sha256":"c0e08af88e034f41673477be0350ceae69faea2db03a4c10b289fa9c20d27cbb","sha256":"44a56fd4b70f22f314ad67dcff21e32e8e96da2129d2405cb5a177cc36be4b02","url":["https://hackage.haskell.org/package/doctest-0.20.1/doctest-0.20.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/doctest-0.20.1.tar.gz"]},"version":"0.20.1"}, + "exceptions": {"dependencies":[],"location":{"type":"core"},"name":"exceptions","version":"0.10.4"}, + "filepath": {"dependencies":[],"location":{"type":"core"},"name":"filepath","version":"1.4.2.2"}, + "first-class-families": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/first-class-families-0.8.0.1/first-class-families-0.8.0.1.tar.gz"},"name":"first-class-families","pinned":{"cabal-sha256":"d7a60485a2f392818808d4decbc6af7c20281713ec1d81948747f1c9c8c2b145","sha256":"4a1c8fbdbe01757ea8dc3190050d7a4a72c86e205d23676182292fe192c1da72","url":["https://hackage.haskell.org/package/first-class-families-0.8.0.1/first-class-families-0.8.0.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/first-class-families-0.8.0.1.tar.gz"]},"version":"0.8.0.1"}, + "generic-deriving": {"dependencies":["base","containers","ghc-prim","template-haskell","th-abstraction"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/generic-deriving-1.14.4/generic-deriving-1.14.4.tar.gz"},"name":"generic-deriving","pinned":{"cabal-sha256":"8395764ff8bef9e688b9681dff3bcd0dbb324a22192e5981bcba10afa75b9ac4","sha256":"372b87b2c91ed4ceff8602024a484944f4653456066755803b5cb268fed8195c","url":["https://hackage.haskell.org/package/generic-deriving-1.14.4/generic-deriving-1.14.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/generic-deriving-1.14.4.tar.gz"]},"version":"1.14.4"}, + "ghc": {"dependencies":[],"location":{"type":"core"},"name":"ghc","version":"9.2.8"}, + "ghc-bignum": {"dependencies":[],"location":{"type":"core"},"name":"ghc-bignum","version":"1.2"}, + "ghc-boot": {"dependencies":[],"location":{"type":"core"},"name":"ghc-boot","version":"9.2.8"}, + "ghc-boot-th": {"dependencies":[],"location":{"type":"core"},"name":"ghc-boot-th","version":"9.2.8"}, + "ghc-check": {"dependencies":["base","containers","directory","filepath","ghc","ghc-boot","ghc-paths","process","safe-exceptions","template-haskell","th-compat","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/ghc-check-0.5.0.8/ghc-check-0.5.0.8.tar.gz"},"name":"ghc-check","pinned":{"cabal-sha256":"4abee5e907b63c986ff4f130fa5a02a933a165af18bda98bff380763a9c1ad47","sha256":"1025a8353fb7c318b27b8dc6b268d22f1f64c271031ed0ce4defb0f9100d7cd4","url":["https://hackage.haskell.org/package/ghc-check-0.5.0.8/ghc-check-0.5.0.8.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/ghc-check-0.5.0.8.tar.gz"]},"version":"0.5.0.8"}, + "ghc-heap": {"dependencies":[],"location":{"type":"core"},"name":"ghc-heap","version":"9.2.8"}, + "ghc-paths": {"dependencies":["base"],"location":{"type":"vendored"},"name":"ghc-paths","version":"0.1.0.11"}, + "ghc-prim": {"dependencies":[],"location":{"type":"core"},"name":"ghc-prim","version":"0.8.0"}, + "ghc-source-gen": {"dependencies":["base","ghc"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/ghc-source-gen-0.4.3.0/ghc-source-gen-0.4.3.0.tar.gz"},"name":"ghc-source-gen","pinned":{"cabal-sha256":"9058ddc2e3201d7b2e5a91b79d76f952c5fb01fb34d742143e9c9b365589ad35","sha256":"0e88038ab714cbe420da8ea15f5cd78565828e9dd956a461283bbe15e9d418d2","url":["https://hackage.haskell.org/package/ghc-source-gen-0.4.3.0/ghc-source-gen-0.4.3.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/ghc-source-gen-0.4.3.0.tar.gz"]},"version":"0.4.3.0"}, + "happy": {"dependencies":["array","base","containers","mtl"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/happy-1.20.1.1/happy-1.20.1.1.tar.gz"},"name":"happy","pinned":{"cabal-sha256":"a381633c5e8f9e9e5a8e1900930ce13172397b4677fcfcc08cd38eb3f73b61b1","sha256":"8b4e7dc5a6c5fd666f8f7163232931ab28746d0d17da8fa1cbd68be9e878881b","url":["https://hackage.haskell.org/package/happy-1.20.1.1/happy-1.20.1.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/happy-1.20.1.1.tar.gz"]},"version":"1.20.1.1"}, + "hashable": {"dependencies":["base","bytestring","containers","data-array-byte","deepseq","filepath","ghc-bignum","ghc-prim","text"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/hashable-1.4.2.0/hashable-1.4.2.0.tar.gz"},"name":"hashable","pinned":{"cabal-sha256":"585792335d5541dba78fa8dfcb291a89cd5812a281825ff7a44afa296ab5d58a","sha256":"1b4000ea82b81f69d46d0af4152c10c6303873510738e24cfc4767760d30e3f8","url":["https://hackage.haskell.org/package/hashable-1.4.2.0/hashable-1.4.2.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/hashable-1.4.2.0.tar.gz"]},"version":"1.4.2.0"}, + "hspec": {"dependencies":["QuickCheck","base","hspec-core","hspec-discover","hspec-expectations"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/hspec-2.9.7/hspec-2.9.7.tar.gz"},"name":"hspec","pinned":{"cabal-sha256":"68732c76946f111db3ecf28fa1ab11f1468c287448b139e57d543bd25a382cf0","sha256":"81ddacf76445fb547010d3582ec9d81d7cd9285258ca74bfeefd653525765a24","url":["https://hackage.haskell.org/package/hspec-2.9.7/hspec-2.9.7.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/hspec-2.9.7.tar.gz"]},"version":"2.9.7"}, + "hspec-core": {"dependencies":["HUnit","QuickCheck","ansi-terminal","array","base","call-stack","clock","deepseq","directory","filepath","ghc","ghc-boot-th","hspec-expectations","quickcheck-io","random","setenv","stm","tf-random","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/hspec-core-2.9.7/hspec-core-2.9.7.tar.gz"},"name":"hspec-core","pinned":{"cabal-sha256":"2c79b0674fa522279eca1263e9aa2c1cf6ceaa5006fcf8956d8a04db46ce56f0","sha256":"16819b4b10fd22be4a72ec7f919417f722b0eba448c62be538e34e8e23fe1910","url":["https://hackage.haskell.org/package/hspec-core-2.9.7/hspec-core-2.9.7.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/hspec-core-2.9.7.tar.gz"]},"version":"2.9.7"}, + "hspec-discover": {"dependencies":["base","directory","filepath"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/hspec-discover-2.9.7/hspec-discover-2.9.7.tar.gz"},"name":"hspec-discover","pinned":{"cabal-sha256":"7b8e52d85c07e8cfed6723255f738fb69ae08d3c0edfd3e458837496897ee629","sha256":"65e933fe21a88a15409b0ec4d6d67fccacbaa410b96ece9e59e81a2e7b9b6614","url":["https://hackage.haskell.org/package/hspec-discover-2.9.7/hspec-discover-2.9.7.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/hspec-discover-2.9.7.tar.gz"]},"version":"2.9.7"}, + "hspec-expectations": {"dependencies":["HUnit","base","call-stack"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/hspec-expectations-0.8.2/hspec-expectations-0.8.2.tar.gz"},"name":"hspec-expectations","pinned":{"cabal-sha256":"e2db24881baadc2d9d23b03cb629e80dcbda89a6b04ace9adb5f4d02ef8b31aa","sha256":"819607ea1faf35ce5be34be61c6f50f3389ea43892d56fb28c57a9f5d54fb4ef","url":["https://hackage.haskell.org/package/hspec-expectations-0.8.2/hspec-expectations-0.8.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/hspec-expectations-0.8.2.tar.gz"]},"version":"0.8.2"}, + "indexed-traversable": {"dependencies":["array","base","containers","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/indexed-traversable-0.1.2.1/indexed-traversable-0.1.2.1.tar.gz"},"name":"indexed-traversable","pinned":{"cabal-sha256":"154b4649199a602dea948a93cb34a6c4be71576c4f78410733dd9f6bc79b6e0b","sha256":"fe854c10285debc7d6fe3e09da0928a740ebc091ad2911ae695bb007e6f746a4","url":["https://hackage.haskell.org/package/indexed-traversable-0.1.2.1/indexed-traversable-0.1.2.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/indexed-traversable-0.1.2.1.tar.gz"]},"version":"0.1.2.1"}, + "integer-logarithms": {"dependencies":["array","base","ghc-bignum","ghc-prim"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/integer-logarithms-1.0.3.1/integer-logarithms-1.0.3.1.tar.gz"},"name":"integer-logarithms","pinned":{"cabal-sha256":"4d0dfc334e64ff57bb1a08717afa4a4a7f28e4cdc46615dd287be31ef63ec00d","sha256":"9b0a9f9fab609b15cd015865721fb05f744a1bc77ae92fd133872de528bbea7f","url":["https://hackage.haskell.org/package/integer-logarithms-1.0.3.1/integer-logarithms-1.0.3.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/integer-logarithms-1.0.3.1.tar.gz"]},"version":"1.0.3.1"}, + "language-c": {"dependencies":["alex","array","base","bytestring","containers","deepseq","directory","filepath","happy","mtl","pretty","process"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/language-c-0.9.2/language-c-0.9.2.tar.gz"},"name":"language-c","pinned":{"cabal-sha256":"b4ec4cbab51a466463cf31c63e6e792f2ac9cfb563296deae02d7be26aba0e0f","sha256":"b2310d2fda16df72e9f8f63ef18bec2e09ae3aff5891dc948c3d9cb72cef6cb3","url":["https://hackage.haskell.org/package/language-c-0.9.2/language-c-0.9.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/language-c-0.9.2.tar.gz"]},"version":"0.9.2"}, + "lens-family": {"dependencies":["base","containers","lens-family-core","mtl","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/lens-family-2.1.2/lens-family-2.1.2.tar.gz"},"name":"lens-family","pinned":{"cabal-sha256":"c13af34889ed9637b2dbd4542122c01a6ec1351cc6dda673de0079f9b02747ef","sha256":"2b60afc3afc03b6e328fc96e291e21bb0a63b563657cabe7ba5febd471283648","url":["https://hackage.haskell.org/package/lens-family-2.1.2/lens-family-2.1.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/lens-family-2.1.2.tar.gz"]},"version":"2.1.2"}, + "lens-family-core": {"dependencies":["base","containers","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/lens-family-core-2.1.2/lens-family-core-2.1.2.tar.gz"},"name":"lens-family-core","pinned":{"cabal-sha256":"702013af981089f991c93598762b8804314266c2bd7d92fc35fb6a8b62af1883","sha256":"1b5a997276c8b77a96f99f48b95b204d34f3bb84fa3691747cd30bc8c76873b6","url":["https://hackage.haskell.org/package/lens-family-core-2.1.2/lens-family-core-2.1.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/lens-family-core-2.1.2.tar.gz"]},"version":"2.1.2"}, + "mmorph": {"dependencies":["base","mtl","transformers","transformers-compat"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/mmorph-1.2.0/mmorph-1.2.0.tar.gz"},"name":"mmorph","pinned":{"cabal-sha256":"df9b213ec18f811cb3137b478d148f3f1680ee43f841cb775835fa282fdb0295","sha256":"61338058eb676b466a462ca45d59f436a77a3bd6b816e4268c6d88522b6a4280","url":["https://hackage.haskell.org/package/mmorph-1.2.0/mmorph-1.2.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/mmorph-1.2.0.tar.gz"]},"version":"1.2.0"}, + "mono-traversable": {"dependencies":["base","bytestring","containers","hashable","split","text","transformers","unordered-containers","vector","vector-algorithms"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/mono-traversable-1.0.15.3/mono-traversable-1.0.15.3.tar.gz"},"name":"mono-traversable","pinned":{"cabal-sha256":"059bf3c05cdbef2d06b765333fe41c2168ced2503a23de674e2a59ceb2548c48","sha256":"98b220f3313d74227a4249210c8818e839678343e62b3ebb1b8c867cf2b974b7","url":["https://hackage.haskell.org/package/mono-traversable-1.0.15.3/mono-traversable-1.0.15.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/mono-traversable-1.0.15.3.tar.gz"]},"version":"1.0.15.3"}, + "mtl": {"dependencies":[],"location":{"type":"core"},"name":"mtl","version":"2.2.2"}, + "network": {"dependencies":["base","bytestring","deepseq","directory"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/network-3.1.4.0/network-3.1.4.0.tar.gz"},"name":"network","pinned":{"cabal-sha256":"e152cdb03243afb52bbc740cfbe96905ca298a6f6342f0c47b3f2e227ff19def","sha256":"b452a2afac95d9207357eb3820c719c7c7d27871ef4b6ed7bfcd03a036b9158e","url":["https://hackage.haskell.org/package/network-3.1.4.0/network-3.1.4.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/network-3.1.4.0.tar.gz"]},"version":"3.1.4.0"}, + "optparse-applicative": {"dependencies":["ansi-wl-pprint","base","process","transformers","transformers-compat"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/optparse-applicative-0.17.1.0/optparse-applicative-0.17.1.0.tar.gz"},"name":"optparse-applicative","pinned":{"cabal-sha256":"cb5f5f0dc9749846fc0e3df0041a8efee6368cc1cff07336acd4c3b02a951ed6","sha256":"d179cb740139c55e6dada3c00efaea45f6853a1974d374668323bbbd07e0a5ef","url":["https://hackage.haskell.org/package/optparse-applicative-0.17.1.0/optparse-applicative-0.17.1.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/optparse-applicative-0.17.1.0.tar.gz"]},"version":"0.17.1.0"}, + "parsec": {"dependencies":[],"location":{"type":"core"},"name":"parsec","version":"3.1.15.0"}, + "polysemy": {"dependencies":["Cabal","QuickCheck","async","base","cabal-doctest","containers","first-class-families","mtl","stm","syb","template-haskell","th-abstraction","transformers","type-errors","unagi-chan"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/polysemy-1.7.1.0/polysemy-1.7.1.0.tar.gz"},"name":"polysemy","pinned":{"cabal-sha256":"3ead7a332abd70b202920ed3bf2e36866de163f821e643adfdcc9d39867b8033","sha256":"4c9556c0c3f38f5fa655567106ecb53cd357e6ffaf8289753ba6dc26fd4bc224","url":["https://hackage.haskell.org/package/polysemy-1.7.1.0/polysemy-1.7.1.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/polysemy-1.7.1.0.tar.gz"]},"version":"1.7.1.0"}, + "pretty": {"dependencies":[],"location":{"type":"core"},"name":"pretty","version":"1.1.3.6"}, + "primitive": {"dependencies":["base","deepseq","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/primitive-0.7.3.0/primitive-0.7.3.0.tar.gz"},"name":"primitive","pinned":{"cabal-sha256":"ce9361b4d2ed296ef639380411b4cfc217a19e4b3cd4170e03e6fce52daa0176","sha256":"3c0cfda67f1ee6f7f65108ad6f973b5bbb35ddba34b3c87746a7448f787501dc","url":["https://hackage.haskell.org/package/primitive-0.7.3.0/primitive-0.7.3.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/primitive-0.7.3.0.tar.gz"]},"version":"0.7.3.0"}, + "process": {"dependencies":[],"location":{"type":"core"},"name":"process","version":"1.6.16.0"}, + "profunctors": {"dependencies":["base","base-orphans","bifunctors","comonad","contravariant","distributive","tagged","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/profunctors-5.6.2/profunctors-5.6.2.tar.gz"},"name":"profunctors","pinned":{"cabal-sha256":"e178ba4468982326656626e2089e296f64485e68fdddc9f4476dcd5d612b4f78","sha256":"65955d7b50525a4a3bccdab1d982d2ae342897fd38140d5a94b5ef3800d8c92a","url":["https://hackage.haskell.org/package/profunctors-5.6.2/profunctors-5.6.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/profunctors-5.6.2.tar.gz"]},"version":"5.6.2"}, + "proto-lens": {"dependencies":["base","bytestring","containers","deepseq","ghc-prim","lens-family","parsec","pretty","primitive","profunctors","tagged","text","transformers","vector"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/proto-lens-0.7.1.3/proto-lens-0.7.1.3.tar.gz"},"name":"proto-lens","pinned":{"cabal-sha256":"2d56bf8c37e21d741385e155d0dd327468ab1bc6897d10b0462b7e241d8e61a3","sha256":"aac4317671a31d5f76cb120b5c4f75e644c45b441b4a2b9cfa7015bd8bbae3ac","url":["https://hackage.haskell.org/package/proto-lens-0.7.1.3/proto-lens-0.7.1.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/proto-lens-0.7.1.3.tar.gz"]},"version":"0.7.1.3"}, + "proto-lens-protoc": {"dependencies":["base","bytestring","containers","filepath","ghc","ghc-paths","ghc-source-gen","lens-family","pretty","proto-lens","proto-lens-runtime","text"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/proto-lens-protoc-0.7.1.1/proto-lens-protoc-0.7.1.1.tar.gz"},"name":"proto-lens-protoc","pinned":{"cabal-sha256":"4b3b97d5caac9a9f8a85d426d5ad8a129f36e852dd05f42e614d9912030b9700","sha256":"0c412b47bce8a3898a61509b9a61c16e00ee947764bd22a07817ecc97a4080f2","url":["https://hackage.haskell.org/package/proto-lens-protoc-0.7.1.1/proto-lens-protoc-0.7.1.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/proto-lens-protoc-0.7.1.1.tar.gz"]},"version":"0.7.1.1"}, + "proto-lens-runtime": {"dependencies":["base","bytestring","containers","deepseq","filepath","lens-family","proto-lens","text","vector"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/proto-lens-runtime-0.7.0.4/proto-lens-runtime-0.7.0.4.tar.gz"},"name":"proto-lens-runtime","pinned":{"cabal-sha256":"1a64cb98b49541e53ea8a19270d7247960445083a2327a091ce0a1cafdef16f3","sha256":"5749cd01d97fd56bae5698830ba78adcc147e4b65b5e1b4b1cb6f9ee52587f47","url":["https://hackage.haskell.org/package/proto-lens-runtime-0.7.0.4/proto-lens-runtime-0.7.0.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/proto-lens-runtime-0.7.0.4.tar.gz"]},"version":"0.7.0.4"}, + "quickcheck-io": {"dependencies":["HUnit","QuickCheck","base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/quickcheck-io-0.2.0/quickcheck-io-0.2.0.tar.gz"},"name":"quickcheck-io","pinned":{"cabal-sha256":"7bf0b68fb90873825eb2e5e958c1b76126dcf984debb998e81673e6d837e0b2d","sha256":"fb779119d79fe08ff4d502fb6869a70c9a8d5fd8ae0959f605c3c937efd96422","url":["https://hackage.haskell.org/package/quickcheck-io-0.2.0/quickcheck-io-0.2.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/quickcheck-io-0.2.0.tar.gz"]},"version":"0.2.0"}, + "random": {"dependencies":["base","bytestring","deepseq","mtl","splitmix"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/random-1.2.1.1/random-1.2.1.1.tar.gz"},"name":"random","pinned":{"cabal-sha256":"e7c1f881159d5cc788619c9ee8b8f340ba2ff0db571cdf3d1a1968ebc5108789","sha256":"3e1272f7ed6a4d7bd1712b90143ec326fee9b225789222379fea20a9c90c9b76","url":["https://hackage.haskell.org/package/random-1.2.1.1/random-1.2.1.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/random-1.2.1.1.tar.gz"]},"version":"1.2.1.1"}, + "resourcet": {"dependencies":["base","containers","exceptions","mtl","primitive","transformers","unliftio-core"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/resourcet-1.2.6/resourcet-1.2.6.tar.gz"},"name":"resourcet","pinned":{"cabal-sha256":"0c55be13d24c1e9c1e6d82327ac039a0bf41469c456e3ae678efa8a9beda3a74","sha256":"f83b35b2106854750ef5f1c34695ea8b7bba6e0572cedf9f2993c5acfdb5fd34","url":["https://hackage.haskell.org/package/resourcet-1.2.6/resourcet-1.2.6.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/resourcet-1.2.6.tar.gz"]},"version":"1.2.6"}, + "safe-exceptions": {"dependencies":["base","deepseq","exceptions","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/safe-exceptions-0.1.7.3/safe-exceptions-0.1.7.3.tar.gz"},"name":"safe-exceptions","pinned":{"cabal-sha256":"6e9b1b233af80cc0aa17ea858d2641ba146fb11cbcc5970a52649e89d77282e2","sha256":"91ce28d8f8a6efd31788d4827ed5cdcb9a546ad4053a86c56f7947c66a30b5bf","url":["https://hackage.haskell.org/package/safe-exceptions-0.1.7.3/safe-exceptions-0.1.7.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/safe-exceptions-0.1.7.3.tar.gz"]},"version":"0.1.7.3"}, + "scientific": {"dependencies":["base","binary","bytestring","containers","deepseq","hashable","integer-logarithms","primitive","template-haskell","text"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/scientific-0.3.7.0/scientific-0.3.7.0.tar.gz"},"name":"scientific","pinned":{"cabal-sha256":"909755ab19b453169ff85281323da1488407776b2360bd9f7afdd219fd306ef2","sha256":"a3a121c4b3d68fb8b9f8c709ab012e48f090ed553609247a805ad070d6b343a9","url":["https://hackage.haskell.org/package/scientific-0.3.7.0/scientific-0.3.7.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/scientific-0.3.7.0.tar.gz"]},"version":"0.3.7.0"}, + "setenv": {"dependencies":["base","unix"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/setenv-0.1.1.3/setenv-0.1.1.3.tar.gz"},"name":"setenv","pinned":{"cabal-sha256":"c5916ac0d2a828473cd171261328a290afe0abd799db1ac8c310682fe778c45b","sha256":"e358df39afc03d5a39e2ec650652d845c85c80cc98fe331654deafb4767ecb32","url":["https://hackage.haskell.org/package/setenv-0.1.1.3/setenv-0.1.1.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/setenv-0.1.1.3.tar.gz"]},"version":"0.1.1.3"}, + "split": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/split-0.2.3.5/split-0.2.3.5.tar.gz"},"name":"split","pinned":{"cabal-sha256":"f472fa7019647cacac3267742a6f7ac0a5c816f9890e80e4b826cd937436de87","sha256":"bf8aa8d610354a2b576946a6c838251ec5988c8374100638e6b2604513b93159","url":["https://hackage.haskell.org/package/split-0.2.3.5/split-0.2.3.5.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/split-0.2.3.5.tar.gz"]},"version":"0.2.3.5"}, + "splitmix": {"dependencies":["base","deepseq"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/splitmix-0.1.0.4/splitmix-0.1.0.4.tar.gz"},"name":"splitmix","pinned":{"cabal-sha256":"db25c2e17967aa6b6046ab8b1b96ba3f344ca59a62b60fb6113d51ea305a3d8e","sha256":"6d065402394e7a9117093dbb4530a21342c9b1e2ec509516c8a8d0ffed98ecaa","url":["https://hackage.haskell.org/package/splitmix-0.1.0.4/splitmix-0.1.0.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/splitmix-0.1.0.4.tar.gz"]},"version":"0.1.0.4"}, + "stm": {"dependencies":[],"location":{"type":"core"},"name":"stm","version":"2.5.0.2"}, + "streaming": {"dependencies":["base","containers","ghc-prim","mmorph","mtl","transformers","transformers-base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/streaming-0.2.3.1/streaming-0.2.3.1.tar.gz"},"name":"streaming","pinned":{"cabal-sha256":"1f8866432934fe00d317576ddff3bba70a671b16073339c8f5e37fce42827518","sha256":"fc5efae393750b9729ce5c5e979edcd3b9a5bf41ab927636174b01f999ffea88","url":["https://hackage.haskell.org/package/streaming-0.2.3.1/streaming-0.2.3.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/streaming-0.2.3.1.tar.gz"]},"version":"0.2.3.1"}, + "streaming-commons": {"dependencies":["array","async","base","bytestring","directory","network","process","random","stm","text","transformers","unix","zlib"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/streaming-commons-0.2.2.6/streaming-commons-0.2.2.6.tar.gz"},"name":"streaming-commons","pinned":{"cabal-sha256":"d5c6fb99efd4e71bdb0351d55f2d87e16c11880f42998e39363eb63f057ae24b","sha256":"0180958a882eb0f6262b812fe886c2b1b8285474b5b958f814ae4f05409fbf79","url":["https://hackage.haskell.org/package/streaming-commons-0.2.2.6/streaming-commons-0.2.2.6.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/streaming-commons-0.2.2.6.tar.gz"]},"version":"0.2.2.6"}, + "syb": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/syb-0.7.2.3/syb-0.7.2.3.tar.gz"},"name":"syb","pinned":{"cabal-sha256":"d71f6747016466b0766491eae36be842ba98ba25e2aec26eaedbeea965c0586a","sha256":"d0b72daf16a947c4d9cb2d5774072f2153433224a04fd60fad60be9ffac8d91a","url":["https://hackage.haskell.org/package/syb-0.7.2.3/syb-0.7.2.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/syb-0.7.2.3.tar.gz"]},"version":"0.7.2.3"}, + "tagged": {"dependencies":["base","deepseq","template-haskell","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/tagged-0.8.6.1/tagged-0.8.6.1.tar.gz"},"name":"tagged","pinned":{"cabal-sha256":"8a24aef29b8e35447ccc56658ea07c2aded30bfa8130ea057e382936e17c74a6","sha256":"f5e0fcf95f0bb4aa63f428f2c01955a41ea1a42cfcf39145ed631f59a9616c02","url":["https://hackage.haskell.org/package/tagged-0.8.6.1/tagged-0.8.6.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/tagged-0.8.6.1.tar.gz"]},"version":"0.8.6.1"}, + "template-haskell": {"dependencies":[],"location":{"type":"core"},"name":"template-haskell","version":"2.18.0.0"}, + "temporary": {"dependencies":["base","directory","exceptions","filepath","random","transformers","unix"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/temporary-1.3/temporary-1.3.tar.gz"},"name":"temporary","pinned":{"cabal-sha256":"3a66c136f700dbf42f3c5000ca93e80b26dead51e54322c83272b236c1ec8ef1","sha256":"8c442993694b5ffca823ce864af95bd2841fb5264ee511c61cf48cc71d879890","url":["https://hackage.haskell.org/package/temporary-1.3/temporary-1.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/temporary-1.3.tar.gz"]},"version":"1.3"}, + "text": {"dependencies":[],"location":{"type":"core"},"name":"text","version":"1.2.5.0"}, + "text-show": {"dependencies":["array","base","base-compat-batteries","bifunctors","bytestring","bytestring-builder","containers","generic-deriving","ghc-boot-th","ghc-prim","template-haskell","text","th-abstraction","th-lift","transformers","transformers-compat"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/text-show-3.10.3/text-show-3.10.3.tar.gz"},"name":"text-show","pinned":{"cabal-sha256":"86b426acef96087f85565028ca7558f3ba1fd0a211deec7673fdb17ee0e3a747","sha256":"1e6afb6e36ae9580829c2806778cf75a55e3a8412afcde1b5c5378bc4266a938","url":["https://hackage.haskell.org/package/text-show-3.10.3/text-show-3.10.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/text-show-3.10.3.tar.gz"]},"version":"3.10.3"}, + "tf-random": {"dependencies":["base","primitive","random","time"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/tf-random-0.5/tf-random-0.5.tar.gz"},"name":"tf-random","pinned":{"cabal-sha256":"14012837d0f0e18fdbbe3d56e67da8622ee5e20b180abce952dd50bd9f36b326","sha256":"2e30cec027b313c9e1794d326635d8fc5f79b6bf6e7580ab4b00186dadc88510","url":["https://hackage.haskell.org/package/tf-random-0.5/tf-random-0.5.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/tf-random-0.5.tar.gz"]},"version":"0.5"}, + "th-abstraction": {"dependencies":["base","containers","ghc-prim","template-haskell"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/th-abstraction-0.4.5.0/th-abstraction-0.4.5.0.tar.gz"},"name":"th-abstraction","pinned":{"cabal-sha256":"c28f186ae9817a059e54f63689f8985194b7f58d8fbd79e157d12374b6f9d2c3","sha256":"00d5e24f247e328bd9898d5af5915c1e86b134b4d40baa680258635f95031526","url":["https://hackage.haskell.org/package/th-abstraction-0.4.5.0/th-abstraction-0.4.5.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/th-abstraction-0.4.5.0.tar.gz"]},"version":"0.4.5.0"}, + "th-compat": {"dependencies":["base","directory","filepath","template-haskell"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/th-compat-0.1.4/th-compat-0.1.4.tar.gz"},"name":"th-compat","pinned":{"cabal-sha256":"f5f2c679ecc1c1b83d2d68db6cc564e5c78d53425e69e1b9e36784820e122d37","sha256":"d8f97ac14ab47b6b8a7b0fdb4ff95426322ec56badd01652ac15da4a44d4bab8","url":["https://hackage.haskell.org/package/th-compat-0.1.4/th-compat-0.1.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/th-compat-0.1.4.tar.gz"]},"version":"0.1.4"}, + "th-lift": {"dependencies":["base","ghc-prim","template-haskell","th-abstraction"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/th-lift-0.8.3/th-lift-0.8.3.tar.gz"},"name":"th-lift","pinned":{"cabal-sha256":"3043e803a08c22676dcf71a4021d0fa276fcecc2ac3dbc4b230fee0b994ca7e9","sha256":"25d57bf5f8e7deefeb4ace0539805ae1e90b1ba5a034ebcc36141846408c6b75","url":["https://hackage.haskell.org/package/th-lift-0.8.3/th-lift-0.8.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/th-lift-0.8.3.tar.gz"]},"version":"0.8.3"}, + "time": {"dependencies":[],"location":{"type":"core"},"name":"time","version":"1.11.1.1"}, + "transformers": {"dependencies":[],"location":{"type":"core"},"name":"transformers","version":"0.5.6.2"}, + "transformers-base": {"dependencies":["base","base-orphans","stm","transformers","transformers-compat"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/transformers-base-0.4.6/transformers-base-0.4.6.tar.gz"},"name":"transformers-base","pinned":{"cabal-sha256":"6f18f320e371c8954c4b6b211e2fdd5d15a6d6310bd605b9d640f47ede408961","sha256":"323bf8689eb691b122661cffa41a25e00fea7a768433fe2dde35d3da7d32cf90","url":["https://hackage.haskell.org/package/transformers-base-0.4.6/transformers-base-0.4.6.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/transformers-base-0.4.6.tar.gz"]},"version":"0.4.6"}, + "transformers-compat": {"dependencies":["base","ghc-prim","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/transformers-compat-0.7.2/transformers-compat-0.7.2.tar.gz"},"name":"transformers-compat","pinned":{"cabal-sha256":"044fb9955f63ee138fcebedfdcbe54afe741f2d5892a2d0bdf3a8052bd342643","sha256":"b62c7304c9f3cbc9463d0739aa85cb9489f217ea092b9d625d417514fbcc9d6a","url":["https://hackage.haskell.org/package/transformers-compat-0.7.2/transformers-compat-0.7.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/transformers-compat-0.7.2.tar.gz"]},"version":"0.7.2"}, + "type-errors": {"dependencies":["base","first-class-families","syb","template-haskell","th-abstraction"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/type-errors-0.2.0.2/type-errors-0.2.0.2.tar.gz"},"name":"type-errors","pinned":{"cabal-sha256":"afd6b33bb582730a90ea58fd23d5b32a38b5b6c8b2f18e3250936bdc0487dfab","sha256":"697cffdd1ec573d6b8d1539976673f93bb562ee97b644077e2305bfefc897c83","url":["https://hackage.haskell.org/package/type-errors-0.2.0.2/type-errors-0.2.0.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/type-errors-0.2.0.2.tar.gz"]},"version":"0.2.0.2"}, + "typed-process": {"dependencies":["async","base","bytestring","process","stm","transformers","unliftio-core"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/typed-process-0.2.11.0/typed-process-0.2.11.0.tar.gz"},"name":"typed-process","pinned":{"cabal-sha256":"defde2c4dcd07750381d6e15ee7a517938c8d6353abcf27bba9f290e75a67d39","sha256":"948c59540675d85f35c99e285cdb8686713ec1689f530d5d21813239ea91f625","url":["https://hackage.haskell.org/package/typed-process-0.2.11.0/typed-process-0.2.11.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/typed-process-0.2.11.0.tar.gz"]},"version":"0.2.11.0"}, + "unagi-chan": {"dependencies":["atomic-primops","base","ghc-prim","primitive"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/unagi-chan-0.4.1.4/unagi-chan-0.4.1.4.tar.gz"},"name":"unagi-chan","pinned":{"cabal-sha256":"e9a282689a65fc66260557222789d14dcb7d299be0ab2d4e8e414b0d9f2ef459","sha256":"d9d6f4ab07def8e84a942bb23791830a61faf89166cb7185a3b2f97cb45128b5","url":["https://hackage.haskell.org/package/unagi-chan-0.4.1.4/unagi-chan-0.4.1.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/unagi-chan-0.4.1.4.tar.gz"]},"version":"0.4.1.4"}, + "unix": {"dependencies":[],"location":{"type":"core"},"name":"unix","version":"2.7.2.2"}, + "unliftio-core": {"dependencies":["base","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/unliftio-core-0.2.1.0/unliftio-core-0.2.1.0.tar.gz"},"name":"unliftio-core","pinned":{"cabal-sha256":"28800633b20e0f7bfbdda1248c28022749aa0935aea10b1e3fc9c88cbebb06de","sha256":"99384cba8d56d9d61b85e38a313a93ebcdb78be6566367f0930ef580597fe3e3","url":["https://hackage.haskell.org/package/unliftio-core-0.2.1.0/unliftio-core-0.2.1.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/unliftio-core-0.2.1.0.tar.gz"]},"version":"0.2.1.0"}, + "unordered-containers": {"dependencies":["base","deepseq","hashable","template-haskell"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/unordered-containers-0.2.19.1/unordered-containers-0.2.19.1.tar.gz"},"name":"unordered-containers","pinned":{"cabal-sha256":"1c28ca429e3960de0330908579a427ccacddd700cb84ec1969e2bbe576152add","sha256":"1b27bec5e0d522b27a6029ebf4c4a6d40acbc083c787008e32fb55c4b1d128d2","url":["https://hackage.haskell.org/package/unordered-containers-0.2.19.1/unordered-containers-0.2.19.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/unordered-containers-0.2.19.1.tar.gz"]},"version":"0.2.19.1"}, + "vector": {"dependencies":["base","deepseq","ghc-prim","primitive"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/vector-0.12.3.1/vector-0.12.3.1.tar.gz"},"name":"vector","pinned":{"cabal-sha256":"39141f312871b7c793a63be76635999e84d442aa3290aec59f30638ec0bf23a7","sha256":"fb4a53c02bd4d7fdf155c0604da9a5bb0f3b3bfce5d9960aea11c2ae235b9f35","url":["https://hackage.haskell.org/package/vector-0.12.3.1/vector-0.12.3.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/vector-0.12.3.1.tar.gz"]},"version":"0.12.3.1"}, + "vector-algorithms": {"dependencies":["base","bytestring","primitive","vector"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/vector-algorithms-0.8.0.4/vector-algorithms-0.8.0.4.tar.gz"},"name":"vector-algorithms","pinned":{"cabal-sha256":"e0656aa47388e5c80e4f5d4fd87c80fb8d473fdd41533ff7af5cbb292056a544","sha256":"76176a56778bf30a275b1089ee6db24ec6c67d92525145f8dfe215b80137af3b","url":["https://hackage.haskell.org/package/vector-algorithms-0.8.0.4/vector-algorithms-0.8.0.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/vector-algorithms-0.8.0.4.tar.gz"]},"version":"0.8.0.4"}, + "void": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/void-0.7.3/void-0.7.3.tar.gz"},"name":"void","pinned":{"cabal-sha256":"13d30f62fcdf065e595d679d4ac8b4b0c1bb1a1b73db7b5b5a8f857cb5c8a546","sha256":"53af758ddc37dc63981671e503438d02c6f64a2d8744e9bec557a894431f7317","url":["https://hackage.haskell.org/package/void-0.7.3/void-0.7.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/void-0.7.3.tar.gz"]},"version":"0.7.3"}, + "zlib": {"dependencies":["base","bytestring"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/zlib-0.6.3.0/zlib-0.6.3.0.tar.gz"},"name":"zlib","pinned":{"cabal-sha256":"19eb7759af71957811d5ec10ddb1e2f4c98700ddb9c0da6860c0441d811f0e6d","sha256":"9eaa989ad4534438b5beb51c1d3a4c8f6a088fdff0b259a5394fbf39aaee04da","url":["https://hackage.haskell.org/package/zlib-0.6.3.0/zlib-0.6.3.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/zlib-0.6.3.0.tar.gz"]},"version":"0.6.3.0"} + } +} \ No newline at end of file diff --git a/rules_haskell_tests/stackage_snapshot_9.4.6.yaml b/rules_haskell_tests/stackage_snapshot_9.4.6.yaml deleted file mode 100644 index 40d980cfa..000000000 --- a/rules_haskell_tests/stackage_snapshot_9.4.6.yaml +++ /dev/null @@ -1,30 +0,0 @@ -# We drop the Win32 package from the stack snapshot so that stack considers it a toolchain library. -# In this case we will use the Win32 provided by the compiler instead of recompiling it. -# -# Recompiling it should be fine for future versions of Win32, -# but with versions <= 2.13.2.0 we encounter the following issue: -# https://github.com/haskell/win32/issues/193 - -resolver: lts-21.11 - -drop-packages: - - Win32 - -packages: -- git: https://github.com/tweag/cabal - commit: 4f8c4ab8274320c1a00992c9aa7c6559ff190fa9 - subdirs: - - Cabal - -# See https://github.com/avdv/proto-lens#readme -- git: https://github.com/avdv/proto-lens - commit: 2ab0a8d1ec1f54f3d1a0ecd1a257311389126490 - -# support GHC 9.4 (see https://github.com/google/ghc-source-gen/pull/102) -- git: https://github.com/circuithub/ghc-source-gen - commit: 7a6aac047b706508e85ba2054b5bedbecfd7eb7a - -# stackage lts-21.11/ghc 9.4.6 only contain Win32-2.12.0.1 -flags: - ansi-terminal: - Win32-2-13-1: false diff --git a/rules_haskell_tests/stackage_snapshot_9.4.6.yaml b/rules_haskell_tests/stackage_snapshot_9.4.6.yaml new file mode 120000 index 000000000..5db769861 --- /dev/null +++ b/rules_haskell_tests/stackage_snapshot_9.4.6.yaml @@ -0,0 +1 @@ +../stackage_snapshot_9.4.6.yaml \ No newline at end of file diff --git a/rules_haskell_tests/tests/haskell_module/repl/haskell_module_repl_cross_library_deps_test/WORKSPACE b/rules_haskell_tests/tests/haskell_module/repl/haskell_module_repl_cross_library_deps_test/WORKSPACE index f16c4ffd0..830b2c771 100644 --- a/rules_haskell_tests/tests/haskell_module/repl/haskell_module_repl_cross_library_deps_test/WORKSPACE +++ b/rules_haskell_tests/tests/haskell_module/repl/haskell_module_repl_cross_library_deps_test/WORKSPACE @@ -15,14 +15,14 @@ rules_haskell_dependencies() load("@rules_haskell//haskell:nixpkgs.bzl", "haskell_register_ghc_nixpkgs") haskell_register_ghc_nixpkgs( - attribute_path = "haskell.compiler.ghc928", + attribute_path = "haskell.compiler.ghc946", repository = "@rules_haskell//nixpkgs:default.nix", - version = "9.2.8", + version = "9.4.6", ) load("@rules_haskell//haskell:toolchain.bzl", "rules_haskell_toolchains") -rules_haskell_toolchains(version = "9.2.8") +rules_haskell_toolchains(version = "9.4.6") load( "@rules_nixpkgs_core//:nixpkgs.bzl", diff --git a/rules_haskell_tests/tests/haskell_module/repl/haskell_module_repl_test/WORKSPACE b/rules_haskell_tests/tests/haskell_module/repl/haskell_module_repl_test/WORKSPACE index 95abb3260..2732ad060 100644 --- a/rules_haskell_tests/tests/haskell_module/repl/haskell_module_repl_test/WORKSPACE +++ b/rules_haskell_tests/tests/haskell_module/repl/haskell_module_repl_test/WORKSPACE @@ -15,14 +15,14 @@ rules_haskell_dependencies() load("@rules_haskell//haskell:nixpkgs.bzl", "haskell_register_ghc_nixpkgs") haskell_register_ghc_nixpkgs( - attribute_path = "haskell.compiler.ghc928", + attribute_path = "haskell.compiler.ghc946", repository = "@rules_haskell//nixpkgs:default.nix", - version = "9.2.8", + version = "9.4.6", ) load("@rules_haskell//haskell:toolchain.bzl", "rules_haskell_toolchains") -rules_haskell_toolchains(version = "9.2.8") +rules_haskell_toolchains(version = "9.4.6") load( "@io_tweag_rules_nixpkgs//nixpkgs:nixpkgs.bzl", diff --git a/rules_haskell_tests/tests/repl-targets/hs_bin_repl_test/WORKSPACE b/rules_haskell_tests/tests/repl-targets/hs_bin_repl_test/WORKSPACE index 924a00a94..f1e11041e 100644 --- a/rules_haskell_tests/tests/repl-targets/hs_bin_repl_test/WORKSPACE +++ b/rules_haskell_tests/tests/repl-targets/hs_bin_repl_test/WORKSPACE @@ -10,14 +10,14 @@ rules_haskell_dependencies() load("@rules_haskell//haskell:nixpkgs.bzl", "haskell_register_ghc_nixpkgs") haskell_register_ghc_nixpkgs( - attribute_path = "haskell.compiler.ghc928", + attribute_path = "haskell.compiler.ghc946", repository = "@rules_haskell//nixpkgs:default.nix", - version = "9.2.8", + version = "9.4.6", ) load("@rules_haskell//haskell:toolchain.bzl", "rules_haskell_toolchains") -rules_haskell_toolchains(version = "9.2.8") +rules_haskell_toolchains(version = "9.4.6") load( "@io_tweag_rules_nixpkgs//nixpkgs:nixpkgs.bzl", diff --git a/rules_haskell_tests/tests/repl-targets/hs_lib_repl_test/WORKSPACE b/rules_haskell_tests/tests/repl-targets/hs_lib_repl_test/WORKSPACE index bad4394a9..f5f5e7f9a 100644 --- a/rules_haskell_tests/tests/repl-targets/hs_lib_repl_test/WORKSPACE +++ b/rules_haskell_tests/tests/repl-targets/hs_lib_repl_test/WORKSPACE @@ -17,14 +17,14 @@ rules_haskell_dependencies() load("@rules_haskell//haskell:nixpkgs.bzl", "haskell_register_ghc_nixpkgs") haskell_register_ghc_nixpkgs( - attribute_path = "haskell.compiler.ghc928", + attribute_path = "haskell.compiler.ghc946", repository = "@rules_haskell//nixpkgs:default.nix", - version = "9.2.8", + version = "9.4.6", ) load("@rules_haskell//haskell:toolchain.bzl", "rules_haskell_toolchains") -rules_haskell_toolchains(version = "9.2.8") +rules_haskell_toolchains(version = "9.4.6") load( "@io_tweag_rules_nixpkgs//nixpkgs:nixpkgs.bzl", diff --git a/rules_haskell_tests/tests/stack-snapshot-deps/hs_override_stack_test/WORKSPACE b/rules_haskell_tests/tests/stack-snapshot-deps/hs_override_stack_test/WORKSPACE index a56182bd2..88c98d20f 100644 --- a/rules_haskell_tests/tests/stack-snapshot-deps/hs_override_stack_test/WORKSPACE +++ b/rules_haskell_tests/tests/stack-snapshot-deps/hs_override_stack_test/WORKSPACE @@ -10,14 +10,14 @@ rules_haskell_dependencies() load("@rules_haskell//haskell:nixpkgs.bzl", "haskell_register_ghc_nixpkgs") haskell_register_ghc_nixpkgs( - attribute_path = "haskell.compiler.ghc928", + attribute_path = "haskell.compiler.ghc946", repository = "@rules_haskell//nixpkgs:default.nix", - version = "9.2.8", + version = "9.4.6", ) load("@rules_haskell//haskell:toolchain.bzl", "rules_haskell_toolchains") -rules_haskell_toolchains(version = "9.2.8") +rules_haskell_toolchains(version = "9.4.6") load( "@io_tweag_rules_nixpkgs//nixpkgs:nixpkgs.bzl", diff --git a/shell.nix b/shell.nix index 641b1c416..38a21a923 100644 --- a/shell.nix +++ b/shell.nix @@ -1,4 +1,4 @@ -{ pkgs ? import ./nixpkgs { }, docTools ? true, ghcVersion ? "9.2.8" }: +{ pkgs ? import ./nixpkgs { }, docTools ? true, ghcVersion ? "9.4.6" }: with pkgs; diff --git a/stackage_snapshot.json b/stackage_snapshot.json index fbde24725..fecbccdfd 100644 --- a/stackage_snapshot.json +++ b/stackage_snapshot.json @@ -1,53 +1,54 @@ { - "__GENERATED_FILE_DO_NOT_MODIFY_MANUALLY": -1865563250, - "all-cabal-hashes": "https://raw.githubusercontent.com/commercialhaskell/all-cabal-hashes/7928d142bd2765e83d8e4e2420da6cffb8d86c80", + "__GENERATED_FILE_DO_NOT_MODIFY_MANUALLY": -1103382728, + "all-cabal-hashes": "https://raw.githubusercontent.com/commercialhaskell/all-cabal-hashes/f9852bf631dd415e0fd690bc50f17abb12c618a6", "resolved": { - "Cabal": {"dependencies":["array","base","binary","bytestring","containers","deepseq","directory","filepath","mtl","parsec","pretty","process","text","time","transformers","unix"],"location":{"type":"git","url":"https://github.com/tweag/cabal","commit":"42f04c3f639f10dc3c7981a0c663bfe08ad833cb","subdir":"Cabal"},"name":"Cabal","version":"3.6.3.0"}, + "Cabal": {"dependencies":["Cabal-syntax","array","base","bytestring","containers","deepseq","directory","filepath","mtl","parsec","pretty","process","text","time","transformers","unix"],"location":{"type":"git","url":"https://github.com/tweag/cabal","commit":"4f8c4ab8274320c1a00992c9aa7c6559ff190fa9","subdir":"Cabal"},"name":"Cabal","version":"3.8.1.0"}, + "Cabal-syntax": {"dependencies":[],"location":{"type":"core"},"name":"Cabal-syntax","version":"3.8.1.0"}, "StateVar": {"dependencies":["base","stm","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/StateVar-1.2.2/StateVar-1.2.2.tar.gz"},"name":"StateVar","pinned":{"url":["https://hackage.haskell.org/package/StateVar-1.2.2/StateVar-1.2.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/StateVar-1.2.2.tar.gz"],"sha256":"5e4b39da395656a59827b0280508aafdc70335798b50e5d6fd52596026251825","cabal-sha256":"3c022c00485fe165e3080d5da6b3ca9c9b02f62c5deebc584d1b3d1309ce673e"},"version":"1.2.2"}, - "alex": {"dependencies":["array","base","containers","directory"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/alex-3.2.7.4/alex-3.2.7.4.tar.gz"},"name":"alex","pinned":{"url":["https://hackage.haskell.org/package/alex-3.2.7.4/alex-3.2.7.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/alex-3.2.7.4.tar.gz"],"sha256":"8a13fa01ea00883aa3d75d15ce848835b18631b8c9a4966961492d7c6095226f","cabal-sha256":"91f4b0bf2f0eca6966bab39975adc440a9d9929dc8729bf92c95c3296dcb25b9"},"version":"3.2.7.4"}, + "alex": {"dependencies":["array","base","containers","directory"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/alex-3.3.0.0/alex-3.3.0.0.tar.gz"},"name":"alex","pinned":{"url":["https://hackage.haskell.org/package/alex-3.3.0.0/alex-3.3.0.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/alex-3.3.0.0.tar.gz"],"sha256":"810f8e85ea6b87c37cba10f7660d7f1aa0ba251c1275e3a18c312964bb329a63","cabal-sha256":"0ab9095e18bcace5adf1d07fcaa489ae4d5c141e9c0fcfeb5343362d04b9dc5b"},"version":"3.3.0.0"}, "array": {"dependencies":[],"location":{"type":"core"},"name":"array","version":"0.5.4.0"}, - "base": {"dependencies":[],"location":{"type":"core"},"name":"base","version":"4.16.4.0"}, - "base-orphans": {"dependencies":["base","ghc-prim"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/base-orphans-0.8.8.2/base-orphans-0.8.8.2.tar.gz"},"name":"base-orphans","pinned":{"url":["https://hackage.haskell.org/package/base-orphans-0.8.8.2/base-orphans-0.8.8.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/base-orphans-0.8.8.2.tar.gz"],"sha256":"61cae7063884128dc98596ab7d8e6d896f6b0fa3da4e12310c850c8c08825092","cabal-sha256":"b62d60c8b7c507f0d0085925fad398e4fcda928c14b524be0148effd99cfb97d"},"version":"0.8.8.2"}, + "base": {"dependencies":[],"location":{"type":"core"},"name":"base","version":"4.17.2.0"}, + "base-orphans": {"dependencies":["base","ghc-prim"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/base-orphans-0.9.0/base-orphans-0.9.0.tar.gz"},"name":"base-orphans","pinned":{"url":["https://hackage.haskell.org/package/base-orphans-0.9.0/base-orphans-0.9.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/base-orphans-0.9.0.tar.gz"],"sha256":"613ed4d8241ed5a648a59ae6569a6962990bb545711d020d49fb83fa12d16e62","cabal-sha256":"0bdd3486d3a1bcbed0513b46af4a13ca74b395313fa5b6e0068d6b7413b76a04"},"version":"0.9.0"}, "bifunctors": {"dependencies":["base","base-orphans","comonad","containers","tagged","template-haskell","th-abstraction","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/bifunctors-5.5.15/bifunctors-5.5.15.tar.gz"},"name":"bifunctors","pinned":{"url":["https://hackage.haskell.org/package/bifunctors-5.5.15/bifunctors-5.5.15.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/bifunctors-5.5.15.tar.gz"],"sha256":"d6359d50d359dd6048dbf6d56c7628211a1785aab9174177faa6d2d8b0d9e3b7","cabal-sha256":"5ebaf9a1996de38ad9d77bec37a5585b6461b34f39446e8f1cadae7689a12bfd"},"version":"5.5.15"}, - "binary": {"dependencies":[],"location":{"type":"core"},"name":"binary","version":"0.8.9.0"}, - "bytestring": {"dependencies":[],"location":{"type":"core"},"name":"bytestring","version":"0.11.4.0"}, + "bytestring": {"dependencies":[],"location":{"type":"core"},"name":"bytestring","version":"0.11.5.1"}, "c2hs": {"dependencies":["array","base","bytestring","containers","directory","dlist","filepath","language-c","pretty","process"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/c2hs-0.28.8/c2hs-0.28.8.tar.gz"},"name":"c2hs","pinned":{"url":["https://hackage.haskell.org/package/c2hs-0.28.8/c2hs-0.28.8.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/c2hs-0.28.8.tar.gz"],"sha256":"390632cffc561c32483af474aac50168a68f0fa382096552e37749923617884c","cabal-sha256":"c399132e2273e70770be403fba4795d7d8c60d7bd147f0ef174342bebbd44392"},"version":"0.28.8"}, "comonad": {"dependencies":["base","containers","distributive","indexed-traversable","tagged","transformers","transformers-compat"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/comonad-5.0.8/comonad-5.0.8.tar.gz"},"name":"comonad","pinned":{"url":["https://hackage.haskell.org/package/comonad-5.0.8/comonad-5.0.8.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/comonad-5.0.8.tar.gz"],"sha256":"ef6cdf2cc292cc43ee6aa96c581b235fdea8ab44a0bffb24dc79ae2b2ef33d13","cabal-sha256":"4a4dbfbd03fb4963987710fca994e8b5624bd05a33e5f95b7581b26f8229c5e3"},"version":"5.0.8"}, - "containers": {"dependencies":[],"location":{"type":"core"},"name":"containers","version":"0.6.5.1"}, + "containers": {"dependencies":[],"location":{"type":"core"},"name":"containers","version":"0.6.7"}, "contravariant": {"dependencies":["StateVar","base","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/contravariant-1.5.5/contravariant-1.5.5.tar.gz"},"name":"contravariant","pinned":{"url":["https://hackage.haskell.org/package/contravariant-1.5.5/contravariant-1.5.5.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/contravariant-1.5.5.tar.gz"],"sha256":"062fd66580d7aad0b5ba93e644ffa7feee69276ef50f20d4ed9f1deb7642dffa","cabal-sha256":"470ed0e040e879e2da4af1b2c8f94e199f6135852a8107858d5ae0a95365835f"},"version":"1.5.5"}, "data-default-class": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/data-default-class-0.1.2.0/data-default-class-0.1.2.0.tar.gz"},"name":"data-default-class","pinned":{"url":["https://hackage.haskell.org/package/data-default-class-0.1.2.0/data-default-class-0.1.2.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/data-default-class-0.1.2.0.tar.gz"],"sha256":"4f01b423f000c3e069aaf52a348564a6536797f31498bb85c3db4bd2d0973e56","cabal-sha256":"63e62120b7efd733a5a17cf59ceb43268e9a929c748127172d7d42f4a336e327"},"version":"0.1.2.0"}, - "deepseq": {"dependencies":[],"location":{"type":"core"},"name":"deepseq","version":"1.4.6.1"}, - "directory": {"dependencies":[],"location":{"type":"core"},"name":"directory","version":"1.3.6.2"}, + "deepseq": {"dependencies":[],"location":{"type":"core"},"name":"deepseq","version":"1.4.8.0"}, + "directory": {"dependencies":[],"location":{"type":"core"},"name":"directory","version":"1.3.7.1"}, "distributive": {"dependencies":["base","base-orphans","tagged","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/distributive-0.6.2.1/distributive-0.6.2.1.tar.gz"},"name":"distributive","pinned":{"url":["https://hackage.haskell.org/package/distributive-0.6.2.1/distributive-0.6.2.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/distributive-0.6.2.1.tar.gz"],"sha256":"d7351392e078f58caa46630a4b9c643e1e2e9dddee45848c5c8358e7b1316b91","cabal-sha256":"0f99f5541cca04acf89b64432b03422b6408e830a8dff30e6c4334ef1a48680c"},"version":"0.6.2.1"}, "dlist": {"dependencies":["base","deepseq"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/dlist-1.0/dlist-1.0.tar.gz"},"name":"dlist","pinned":{"url":["https://hackage.haskell.org/package/dlist-1.0/dlist-1.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/dlist-1.0.tar.gz"],"sha256":"173d637328bb173fcc365f30d29ff4a94292a1e0e5558aeb3dfc11de81510115","cabal-sha256":"55ff69d20ce638fc7727342ee67f2f868da61d3dcf3763f790bf9aa0b145e568"},"version":"1.0"}, "filepath": {"dependencies":[],"location":{"type":"core"},"name":"filepath","version":"1.4.2.2"}, - "ghc": {"dependencies":[],"location":{"type":"core"},"name":"ghc","version":"9.2.8"}, + "ghc": {"dependencies":[],"location":{"type":"core"},"name":"ghc","version":"9.4.6"}, "ghc-paths": {"dependencies":["base"],"location":{"type":"vendored"},"name":"ghc-paths","version":"0.1.0.11"}, - "ghc-prim": {"dependencies":[],"location":{"type":"core"},"name":"ghc-prim","version":"0.8.0"}, - "ghc-source-gen": {"dependencies":["base","ghc"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/ghc-source-gen-0.4.3.0/ghc-source-gen-0.4.3.0.tar.gz"},"name":"ghc-source-gen","pinned":{"url":["https://hackage.haskell.org/package/ghc-source-gen-0.4.3.0/ghc-source-gen-0.4.3.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/ghc-source-gen-0.4.3.0.tar.gz"],"sha256":"0e88038ab714cbe420da8ea15f5cd78565828e9dd956a461283bbe15e9d418d2","cabal-sha256":"9058ddc2e3201d7b2e5a91b79d76f952c5fb01fb34d742143e9c9b365589ad35"},"version":"0.4.3.0"}, + "ghc-prim": {"dependencies":[],"location":{"type":"core"},"name":"ghc-prim","version":"0.9.1"}, + "ghc-source-gen": {"dependencies":["base","ghc"],"location":{"type":"git","url":"https://github.com/circuithub/ghc-source-gen","commit":"7a6aac047b706508e85ba2054b5bedbecfd7eb7a","subdir":""},"name":"ghc-source-gen","version":"0.4.3.0"}, "happy": {"dependencies":["array","base","containers","mtl"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/happy-1.20.1.1/happy-1.20.1.1.tar.gz"},"name":"happy","pinned":{"url":["https://hackage.haskell.org/package/happy-1.20.1.1/happy-1.20.1.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/happy-1.20.1.1.tar.gz"],"sha256":"8b4e7dc5a6c5fd666f8f7163232931ab28746d0d17da8fa1cbd68be9e878881b","cabal-sha256":"a381633c5e8f9e9e5a8e1900930ce13172397b4677fcfcc08cd38eb3f73b61b1"},"version":"1.20.1.1"}, "indexed-traversable": {"dependencies":["array","base","containers","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/indexed-traversable-0.1.2.1/indexed-traversable-0.1.2.1.tar.gz"},"name":"indexed-traversable","pinned":{"url":["https://hackage.haskell.org/package/indexed-traversable-0.1.2.1/indexed-traversable-0.1.2.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/indexed-traversable-0.1.2.1.tar.gz"],"sha256":"fe854c10285debc7d6fe3e09da0928a740ebc091ad2911ae695bb007e6f746a4","cabal-sha256":"154b4649199a602dea948a93cb34a6c4be71576c4f78410733dd9f6bc79b6e0b"},"version":"0.1.2.1"}, "language-c": {"dependencies":["alex","array","base","bytestring","containers","deepseq","directory","filepath","happy","mtl","pretty","process"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/language-c-0.9.2/language-c-0.9.2.tar.gz"},"name":"language-c","pinned":{"url":["https://hackage.haskell.org/package/language-c-0.9.2/language-c-0.9.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/language-c-0.9.2.tar.gz"],"sha256":"b2310d2fda16df72e9f8f63ef18bec2e09ae3aff5891dc948c3d9cb72cef6cb3","cabal-sha256":"a4b77129d7d30d777e0f203ba9c18b88f4791f95c079fef573b554f915dcf57d"},"version":"0.9.2"}, "lens-family": {"dependencies":["base","containers","lens-family-core","mtl","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/lens-family-2.1.2/lens-family-2.1.2.tar.gz"},"name":"lens-family","pinned":{"url":["https://hackage.haskell.org/package/lens-family-2.1.2/lens-family-2.1.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/lens-family-2.1.2.tar.gz"],"sha256":"2b60afc3afc03b6e328fc96e291e21bb0a63b563657cabe7ba5febd471283648","cabal-sha256":"c13af34889ed9637b2dbd4542122c01a6ec1351cc6dda673de0079f9b02747ef"},"version":"2.1.2"}, "lens-family-core": {"dependencies":["base","containers","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/lens-family-core-2.1.2/lens-family-core-2.1.2.tar.gz"},"name":"lens-family-core","pinned":{"url":["https://hackage.haskell.org/package/lens-family-core-2.1.2/lens-family-core-2.1.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/lens-family-core-2.1.2.tar.gz"],"sha256":"1b5a997276c8b77a96f99f48b95b204d34f3bb84fa3691747cd30bc8c76873b6","cabal-sha256":"702013af981089f991c93598762b8804314266c2bd7d92fc35fb6a8b62af1883"},"version":"2.1.2"}, "mtl": {"dependencies":[],"location":{"type":"core"},"name":"mtl","version":"2.2.2"}, - "parsec": {"dependencies":[],"location":{"type":"core"},"name":"parsec","version":"3.1.15.0"}, + "parsec": {"dependencies":[],"location":{"type":"core"},"name":"parsec","version":"3.1.16.1"}, "pretty": {"dependencies":[],"location":{"type":"core"},"name":"pretty","version":"1.1.3.6"}, - "primitive": {"dependencies":["base","deepseq","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/primitive-0.7.3.0/primitive-0.7.3.0.tar.gz"},"name":"primitive","pinned":{"url":["https://hackage.haskell.org/package/primitive-0.7.3.0/primitive-0.7.3.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/primitive-0.7.3.0.tar.gz"],"sha256":"3c0cfda67f1ee6f7f65108ad6f973b5bbb35ddba34b3c87746a7448f787501dc","cabal-sha256":"ce9361b4d2ed296ef639380411b4cfc217a19e4b3cd4170e03e6fce52daa0176"},"version":"0.7.3.0"}, - "process": {"dependencies":[],"location":{"type":"core"},"name":"process","version":"1.6.16.0"}, + "primitive": {"dependencies":["base","deepseq","template-haskell","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/primitive-0.8.0.0/primitive-0.8.0.0.tar.gz"},"name":"primitive","pinned":{"url":["https://hackage.haskell.org/package/primitive-0.8.0.0/primitive-0.8.0.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/primitive-0.8.0.0.tar.gz"],"sha256":"5553c21b4a789f9b591eed69e598cc58484c274af29250e517b5a8bcc62b995f","cabal-sha256":"d0ff45fa6e61f92af23611ceb8b9a6a04c236b50fb70c60e2ed3bfa532703670"},"version":"0.8.0.0"}, + "process": {"dependencies":[],"location":{"type":"core"},"name":"process","version":"1.6.17.0"}, "profunctors": {"dependencies":["base","base-orphans","bifunctors","comonad","contravariant","distributive","tagged","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/profunctors-5.6.2/profunctors-5.6.2.tar.gz"},"name":"profunctors","pinned":{"url":["https://hackage.haskell.org/package/profunctors-5.6.2/profunctors-5.6.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/profunctors-5.6.2.tar.gz"],"sha256":"65955d7b50525a4a3bccdab1d982d2ae342897fd38140d5a94b5ef3800d8c92a","cabal-sha256":"e178ba4468982326656626e2089e296f64485e68fdddc9f4476dcd5d612b4f78"},"version":"5.6.2"}, "proto-lens": {"dependencies":["base","bytestring","containers","deepseq","ghc-prim","lens-family","parsec","pretty","primitive","profunctors","tagged","text","transformers","vector"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/proto-lens-0.7.1.3/proto-lens-0.7.1.3.tar.gz"},"name":"proto-lens","pinned":{"url":["https://hackage.haskell.org/package/proto-lens-0.7.1.3/proto-lens-0.7.1.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/proto-lens-0.7.1.3.tar.gz"],"sha256":"aac4317671a31d5f76cb120b5c4f75e644c45b441b4a2b9cfa7015bd8bbae3ac","cabal-sha256":"2d56bf8c37e21d741385e155d0dd327468ab1bc6897d10b0462b7e241d8e61a3"},"version":"0.7.1.3"}, - "proto-lens-protoc": {"dependencies":["base","bytestring","containers","filepath","ghc","ghc-paths","ghc-source-gen","lens-family","pretty","proto-lens","proto-lens-runtime","text"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/proto-lens-protoc-0.7.1.1/proto-lens-protoc-0.7.1.1.tar.gz"},"name":"proto-lens-protoc","pinned":{"url":["https://hackage.haskell.org/package/proto-lens-protoc-0.7.1.1/proto-lens-protoc-0.7.1.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/proto-lens-protoc-0.7.1.1.tar.gz"],"sha256":"0c412b47bce8a3898a61509b9a61c16e00ee947764bd22a07817ecc97a4080f2","cabal-sha256":"4b3b97d5caac9a9f8a85d426d5ad8a129f36e852dd05f42e614d9912030b9700"},"version":"0.7.1.1"}, + "proto-lens-protoc": {"dependencies":["base","bytestring","containers","filepath","ghc","ghc-paths","ghc-source-gen","lens-family","pretty","proto-lens","proto-lens-runtime","text"],"location":{"type":"git","url":"https://github.com/avdv/proto-lens","commit":"2ab0a8d1ec1f54f3d1a0ecd1a257311389126490","subdir":""},"name":"proto-lens-protoc","version":"0.7.1.1"}, "proto-lens-runtime": {"dependencies":["base","bytestring","containers","deepseq","filepath","lens-family","proto-lens","text","vector"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/proto-lens-runtime-0.7.0.4/proto-lens-runtime-0.7.0.4.tar.gz"},"name":"proto-lens-runtime","pinned":{"url":["https://hackage.haskell.org/package/proto-lens-runtime-0.7.0.4/proto-lens-runtime-0.7.0.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/proto-lens-runtime-0.7.0.4.tar.gz"],"sha256":"5749cd01d97fd56bae5698830ba78adcc147e4b65b5e1b4b1cb6f9ee52587f47","cabal-sha256":"1a64cb98b49541e53ea8a19270d7247960445083a2327a091ce0a1cafdef16f3"},"version":"0.7.0.4"}, - "stm": {"dependencies":[],"location":{"type":"core"},"name":"stm","version":"2.5.0.2"}, - "tagged": {"dependencies":["base","deepseq","template-haskell","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/tagged-0.8.6.1/tagged-0.8.6.1.tar.gz"},"name":"tagged","pinned":{"url":["https://hackage.haskell.org/package/tagged-0.8.6.1/tagged-0.8.6.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/tagged-0.8.6.1.tar.gz"],"sha256":"f5e0fcf95f0bb4aa63f428f2c01955a41ea1a42cfcf39145ed631f59a9616c02","cabal-sha256":"8a24aef29b8e35447ccc56658ea07c2aded30bfa8130ea057e382936e17c74a6"},"version":"0.8.6.1"}, - "template-haskell": {"dependencies":[],"location":{"type":"core"},"name":"template-haskell","version":"2.18.0.0"}, - "text": {"dependencies":[],"location":{"type":"core"},"name":"text","version":"1.2.5.0"}, + "stm": {"dependencies":[],"location":{"type":"core"},"name":"stm","version":"2.5.1.0"}, + "tagged": {"dependencies":["base","deepseq","template-haskell","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/tagged-0.8.7/tagged-0.8.7.tar.gz"},"name":"tagged","pinned":{"url":["https://hackage.haskell.org/package/tagged-0.8.7/tagged-0.8.7.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/tagged-0.8.7.tar.gz"],"sha256":"6414eeac27a1633f49e2f78199ced99ce8ce3d70b658cf6d55b1d81ff60cb961","cabal-sha256":"9013e1491dc0d291cb37c2845973293a03c230374f44792bfc96e14fdfb426dc"},"version":"0.8.7"}, + "template-haskell": {"dependencies":[],"location":{"type":"core"},"name":"template-haskell","version":"2.19.0.0"}, + "text": {"dependencies":[],"location":{"type":"core"},"name":"text","version":"2.0.2"}, "th-abstraction": {"dependencies":["base","containers","ghc-prim","template-haskell"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/th-abstraction-0.4.5.0/th-abstraction-0.4.5.0.tar.gz"},"name":"th-abstraction","pinned":{"url":["https://hackage.haskell.org/package/th-abstraction-0.4.5.0/th-abstraction-0.4.5.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/th-abstraction-0.4.5.0.tar.gz"],"sha256":"00d5e24f247e328bd9898d5af5915c1e86b134b4d40baa680258635f95031526","cabal-sha256":"c28f186ae9817a059e54f63689f8985194b7f58d8fbd79e157d12374b6f9d2c3"},"version":"0.4.5.0"}, - "time": {"dependencies":[],"location":{"type":"core"},"name":"time","version":"1.11.1.1"}, + "time": {"dependencies":[],"location":{"type":"core"},"name":"time","version":"1.12.2"}, "transformers": {"dependencies":[],"location":{"type":"core"},"name":"transformers","version":"0.5.6.2"}, "transformers-compat": {"dependencies":["base","ghc-prim","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/transformers-compat-0.7.2/transformers-compat-0.7.2.tar.gz"},"name":"transformers-compat","pinned":{"url":["https://hackage.haskell.org/package/transformers-compat-0.7.2/transformers-compat-0.7.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/transformers-compat-0.7.2.tar.gz"],"sha256":"b62c7304c9f3cbc9463d0739aa85cb9489f217ea092b9d625d417514fbcc9d6a","cabal-sha256":"044fb9955f63ee138fcebedfdcbe54afe741f2d5892a2d0bdf3a8052bd342643"},"version":"0.7.2"}, - "unix": {"dependencies":[],"location":{"type":"core"},"name":"unix","version":"2.7.2.2"}, - "vector": {"dependencies":["base","deepseq","ghc-prim","primitive"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/vector-0.12.3.1/vector-0.12.3.1.tar.gz"},"name":"vector","pinned":{"url":["https://hackage.haskell.org/package/vector-0.12.3.1/vector-0.12.3.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/vector-0.12.3.1.tar.gz"],"sha256":"fb4a53c02bd4d7fdf155c0604da9a5bb0f3b3bfce5d9960aea11c2ae235b9f35","cabal-sha256":"39141f312871b7c793a63be76635999e84d442aa3290aec59f30638ec0bf23a7"},"version":"0.12.3.1"} + "unix": {"dependencies":[],"location":{"type":"core"},"name":"unix","version":"2.7.3"}, + "vector": {"dependencies":["base","deepseq","primitive","vector-stream"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/vector-0.13.0.0/vector-0.13.0.0.tar.gz"},"name":"vector","pinned":{"url":["https://hackage.haskell.org/package/vector-0.13.0.0/vector-0.13.0.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/vector-0.13.0.0.tar.gz"],"sha256":"c5d3167d15e12f52e00879ddf304a591672a74e369cc47bc5c7fa1d5a8d15b4f","cabal-sha256":"1d0b2128c7151e06c2417616afedcb1a4d54087afeba623c55dd4b29094d4348"},"version":"0.13.0.0"}, + "vector-stream": {"dependencies":["base","ghc-prim"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/vector-stream-0.1.0.0/vector-stream-0.1.0.0.tar.gz"},"name":"vector-stream","pinned":{"url":["https://hackage.haskell.org/package/vector-stream-0.1.0.0/vector-stream-0.1.0.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/vector-stream-0.1.0.0.tar.gz"],"sha256":"a888210f6467f155090653734be5cc920406a07227e0d3adb59096716fdb806c","cabal-sha256":"8977959d4bec54d9f2c5e9d4baa2cac7ab26e804a72591df8db887e0692ae8ae"},"version":"0.1.0.0"} } } \ No newline at end of file diff --git a/stackage_snapshot.yaml b/stackage_snapshot.yaml index 7202f801b..70b173692 100644 --- a/stackage_snapshot.yaml +++ b/stackage_snapshot.yaml @@ -5,18 +5,26 @@ # but with versions <= 2.13.2.0 we encounter the following issue: # https://github.com/haskell/win32/issues/193 -resolver: lts-20.26 +resolver: lts-21.11 drop-packages: - Win32 packages: - git: https://github.com/tweag/cabal - commit: 42f04c3f639f10dc3c7981a0c663bfe08ad833cb + commit: 4f8c4ab8274320c1a00992c9aa7c6559ff190fa9 subdirs: - Cabal -# stackage lts-20.26/ghc 9.2.8 only contain Win32-2.12.0.1 +# See https://github.com/avdv/proto-lens#readme +- git: https://github.com/avdv/proto-lens + commit: 2ab0a8d1ec1f54f3d1a0ecd1a257311389126490 + +# support GHC 9.4 (see https://github.com/google/ghc-source-gen/pull/102) +- git: https://github.com/google/ghc-source-gen + commit: 7527305ed59a47140053cf7bc87432fe1f8804d0 + +# stackage lts-21.11/ghc 9.4.6 only contain Win32-2.12.0.1 flags: ansi-terminal: Win32-2-13-1: false diff --git a/stackage_snapshot_9.2.8.json b/stackage_snapshot_9.2.8.json deleted file mode 120000 index c81f31ff7..000000000 --- a/stackage_snapshot_9.2.8.json +++ /dev/null @@ -1 +0,0 @@ -stackage_snapshot.json \ No newline at end of file diff --git a/stackage_snapshot_9.2.8.json b/stackage_snapshot_9.2.8.json new file mode 100644 index 000000000..fbde24725 --- /dev/null +++ b/stackage_snapshot_9.2.8.json @@ -0,0 +1,53 @@ +{ + "__GENERATED_FILE_DO_NOT_MODIFY_MANUALLY": -1865563250, + "all-cabal-hashes": "https://raw.githubusercontent.com/commercialhaskell/all-cabal-hashes/7928d142bd2765e83d8e4e2420da6cffb8d86c80", + "resolved": { + "Cabal": {"dependencies":["array","base","binary","bytestring","containers","deepseq","directory","filepath","mtl","parsec","pretty","process","text","time","transformers","unix"],"location":{"type":"git","url":"https://github.com/tweag/cabal","commit":"42f04c3f639f10dc3c7981a0c663bfe08ad833cb","subdir":"Cabal"},"name":"Cabal","version":"3.6.3.0"}, + "StateVar": {"dependencies":["base","stm","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/StateVar-1.2.2/StateVar-1.2.2.tar.gz"},"name":"StateVar","pinned":{"url":["https://hackage.haskell.org/package/StateVar-1.2.2/StateVar-1.2.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/StateVar-1.2.2.tar.gz"],"sha256":"5e4b39da395656a59827b0280508aafdc70335798b50e5d6fd52596026251825","cabal-sha256":"3c022c00485fe165e3080d5da6b3ca9c9b02f62c5deebc584d1b3d1309ce673e"},"version":"1.2.2"}, + "alex": {"dependencies":["array","base","containers","directory"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/alex-3.2.7.4/alex-3.2.7.4.tar.gz"},"name":"alex","pinned":{"url":["https://hackage.haskell.org/package/alex-3.2.7.4/alex-3.2.7.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/alex-3.2.7.4.tar.gz"],"sha256":"8a13fa01ea00883aa3d75d15ce848835b18631b8c9a4966961492d7c6095226f","cabal-sha256":"91f4b0bf2f0eca6966bab39975adc440a9d9929dc8729bf92c95c3296dcb25b9"},"version":"3.2.7.4"}, + "array": {"dependencies":[],"location":{"type":"core"},"name":"array","version":"0.5.4.0"}, + "base": {"dependencies":[],"location":{"type":"core"},"name":"base","version":"4.16.4.0"}, + "base-orphans": {"dependencies":["base","ghc-prim"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/base-orphans-0.8.8.2/base-orphans-0.8.8.2.tar.gz"},"name":"base-orphans","pinned":{"url":["https://hackage.haskell.org/package/base-orphans-0.8.8.2/base-orphans-0.8.8.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/base-orphans-0.8.8.2.tar.gz"],"sha256":"61cae7063884128dc98596ab7d8e6d896f6b0fa3da4e12310c850c8c08825092","cabal-sha256":"b62d60c8b7c507f0d0085925fad398e4fcda928c14b524be0148effd99cfb97d"},"version":"0.8.8.2"}, + "bifunctors": {"dependencies":["base","base-orphans","comonad","containers","tagged","template-haskell","th-abstraction","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/bifunctors-5.5.15/bifunctors-5.5.15.tar.gz"},"name":"bifunctors","pinned":{"url":["https://hackage.haskell.org/package/bifunctors-5.5.15/bifunctors-5.5.15.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/bifunctors-5.5.15.tar.gz"],"sha256":"d6359d50d359dd6048dbf6d56c7628211a1785aab9174177faa6d2d8b0d9e3b7","cabal-sha256":"5ebaf9a1996de38ad9d77bec37a5585b6461b34f39446e8f1cadae7689a12bfd"},"version":"5.5.15"}, + "binary": {"dependencies":[],"location":{"type":"core"},"name":"binary","version":"0.8.9.0"}, + "bytestring": {"dependencies":[],"location":{"type":"core"},"name":"bytestring","version":"0.11.4.0"}, + "c2hs": {"dependencies":["array","base","bytestring","containers","directory","dlist","filepath","language-c","pretty","process"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/c2hs-0.28.8/c2hs-0.28.8.tar.gz"},"name":"c2hs","pinned":{"url":["https://hackage.haskell.org/package/c2hs-0.28.8/c2hs-0.28.8.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/c2hs-0.28.8.tar.gz"],"sha256":"390632cffc561c32483af474aac50168a68f0fa382096552e37749923617884c","cabal-sha256":"c399132e2273e70770be403fba4795d7d8c60d7bd147f0ef174342bebbd44392"},"version":"0.28.8"}, + "comonad": {"dependencies":["base","containers","distributive","indexed-traversable","tagged","transformers","transformers-compat"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/comonad-5.0.8/comonad-5.0.8.tar.gz"},"name":"comonad","pinned":{"url":["https://hackage.haskell.org/package/comonad-5.0.8/comonad-5.0.8.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/comonad-5.0.8.tar.gz"],"sha256":"ef6cdf2cc292cc43ee6aa96c581b235fdea8ab44a0bffb24dc79ae2b2ef33d13","cabal-sha256":"4a4dbfbd03fb4963987710fca994e8b5624bd05a33e5f95b7581b26f8229c5e3"},"version":"5.0.8"}, + "containers": {"dependencies":[],"location":{"type":"core"},"name":"containers","version":"0.6.5.1"}, + "contravariant": {"dependencies":["StateVar","base","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/contravariant-1.5.5/contravariant-1.5.5.tar.gz"},"name":"contravariant","pinned":{"url":["https://hackage.haskell.org/package/contravariant-1.5.5/contravariant-1.5.5.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/contravariant-1.5.5.tar.gz"],"sha256":"062fd66580d7aad0b5ba93e644ffa7feee69276ef50f20d4ed9f1deb7642dffa","cabal-sha256":"470ed0e040e879e2da4af1b2c8f94e199f6135852a8107858d5ae0a95365835f"},"version":"1.5.5"}, + "data-default-class": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/data-default-class-0.1.2.0/data-default-class-0.1.2.0.tar.gz"},"name":"data-default-class","pinned":{"url":["https://hackage.haskell.org/package/data-default-class-0.1.2.0/data-default-class-0.1.2.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/data-default-class-0.1.2.0.tar.gz"],"sha256":"4f01b423f000c3e069aaf52a348564a6536797f31498bb85c3db4bd2d0973e56","cabal-sha256":"63e62120b7efd733a5a17cf59ceb43268e9a929c748127172d7d42f4a336e327"},"version":"0.1.2.0"}, + "deepseq": {"dependencies":[],"location":{"type":"core"},"name":"deepseq","version":"1.4.6.1"}, + "directory": {"dependencies":[],"location":{"type":"core"},"name":"directory","version":"1.3.6.2"}, + "distributive": {"dependencies":["base","base-orphans","tagged","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/distributive-0.6.2.1/distributive-0.6.2.1.tar.gz"},"name":"distributive","pinned":{"url":["https://hackage.haskell.org/package/distributive-0.6.2.1/distributive-0.6.2.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/distributive-0.6.2.1.tar.gz"],"sha256":"d7351392e078f58caa46630a4b9c643e1e2e9dddee45848c5c8358e7b1316b91","cabal-sha256":"0f99f5541cca04acf89b64432b03422b6408e830a8dff30e6c4334ef1a48680c"},"version":"0.6.2.1"}, + "dlist": {"dependencies":["base","deepseq"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/dlist-1.0/dlist-1.0.tar.gz"},"name":"dlist","pinned":{"url":["https://hackage.haskell.org/package/dlist-1.0/dlist-1.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/dlist-1.0.tar.gz"],"sha256":"173d637328bb173fcc365f30d29ff4a94292a1e0e5558aeb3dfc11de81510115","cabal-sha256":"55ff69d20ce638fc7727342ee67f2f868da61d3dcf3763f790bf9aa0b145e568"},"version":"1.0"}, + "filepath": {"dependencies":[],"location":{"type":"core"},"name":"filepath","version":"1.4.2.2"}, + "ghc": {"dependencies":[],"location":{"type":"core"},"name":"ghc","version":"9.2.8"}, + "ghc-paths": {"dependencies":["base"],"location":{"type":"vendored"},"name":"ghc-paths","version":"0.1.0.11"}, + "ghc-prim": {"dependencies":[],"location":{"type":"core"},"name":"ghc-prim","version":"0.8.0"}, + "ghc-source-gen": {"dependencies":["base","ghc"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/ghc-source-gen-0.4.3.0/ghc-source-gen-0.4.3.0.tar.gz"},"name":"ghc-source-gen","pinned":{"url":["https://hackage.haskell.org/package/ghc-source-gen-0.4.3.0/ghc-source-gen-0.4.3.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/ghc-source-gen-0.4.3.0.tar.gz"],"sha256":"0e88038ab714cbe420da8ea15f5cd78565828e9dd956a461283bbe15e9d418d2","cabal-sha256":"9058ddc2e3201d7b2e5a91b79d76f952c5fb01fb34d742143e9c9b365589ad35"},"version":"0.4.3.0"}, + "happy": {"dependencies":["array","base","containers","mtl"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/happy-1.20.1.1/happy-1.20.1.1.tar.gz"},"name":"happy","pinned":{"url":["https://hackage.haskell.org/package/happy-1.20.1.1/happy-1.20.1.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/happy-1.20.1.1.tar.gz"],"sha256":"8b4e7dc5a6c5fd666f8f7163232931ab28746d0d17da8fa1cbd68be9e878881b","cabal-sha256":"a381633c5e8f9e9e5a8e1900930ce13172397b4677fcfcc08cd38eb3f73b61b1"},"version":"1.20.1.1"}, + "indexed-traversable": {"dependencies":["array","base","containers","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/indexed-traversable-0.1.2.1/indexed-traversable-0.1.2.1.tar.gz"},"name":"indexed-traversable","pinned":{"url":["https://hackage.haskell.org/package/indexed-traversable-0.1.2.1/indexed-traversable-0.1.2.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/indexed-traversable-0.1.2.1.tar.gz"],"sha256":"fe854c10285debc7d6fe3e09da0928a740ebc091ad2911ae695bb007e6f746a4","cabal-sha256":"154b4649199a602dea948a93cb34a6c4be71576c4f78410733dd9f6bc79b6e0b"},"version":"0.1.2.1"}, + "language-c": {"dependencies":["alex","array","base","bytestring","containers","deepseq","directory","filepath","happy","mtl","pretty","process"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/language-c-0.9.2/language-c-0.9.2.tar.gz"},"name":"language-c","pinned":{"url":["https://hackage.haskell.org/package/language-c-0.9.2/language-c-0.9.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/language-c-0.9.2.tar.gz"],"sha256":"b2310d2fda16df72e9f8f63ef18bec2e09ae3aff5891dc948c3d9cb72cef6cb3","cabal-sha256":"a4b77129d7d30d777e0f203ba9c18b88f4791f95c079fef573b554f915dcf57d"},"version":"0.9.2"}, + "lens-family": {"dependencies":["base","containers","lens-family-core","mtl","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/lens-family-2.1.2/lens-family-2.1.2.tar.gz"},"name":"lens-family","pinned":{"url":["https://hackage.haskell.org/package/lens-family-2.1.2/lens-family-2.1.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/lens-family-2.1.2.tar.gz"],"sha256":"2b60afc3afc03b6e328fc96e291e21bb0a63b563657cabe7ba5febd471283648","cabal-sha256":"c13af34889ed9637b2dbd4542122c01a6ec1351cc6dda673de0079f9b02747ef"},"version":"2.1.2"}, + "lens-family-core": {"dependencies":["base","containers","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/lens-family-core-2.1.2/lens-family-core-2.1.2.tar.gz"},"name":"lens-family-core","pinned":{"url":["https://hackage.haskell.org/package/lens-family-core-2.1.2/lens-family-core-2.1.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/lens-family-core-2.1.2.tar.gz"],"sha256":"1b5a997276c8b77a96f99f48b95b204d34f3bb84fa3691747cd30bc8c76873b6","cabal-sha256":"702013af981089f991c93598762b8804314266c2bd7d92fc35fb6a8b62af1883"},"version":"2.1.2"}, + "mtl": {"dependencies":[],"location":{"type":"core"},"name":"mtl","version":"2.2.2"}, + "parsec": {"dependencies":[],"location":{"type":"core"},"name":"parsec","version":"3.1.15.0"}, + "pretty": {"dependencies":[],"location":{"type":"core"},"name":"pretty","version":"1.1.3.6"}, + "primitive": {"dependencies":["base","deepseq","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/primitive-0.7.3.0/primitive-0.7.3.0.tar.gz"},"name":"primitive","pinned":{"url":["https://hackage.haskell.org/package/primitive-0.7.3.0/primitive-0.7.3.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/primitive-0.7.3.0.tar.gz"],"sha256":"3c0cfda67f1ee6f7f65108ad6f973b5bbb35ddba34b3c87746a7448f787501dc","cabal-sha256":"ce9361b4d2ed296ef639380411b4cfc217a19e4b3cd4170e03e6fce52daa0176"},"version":"0.7.3.0"}, + "process": {"dependencies":[],"location":{"type":"core"},"name":"process","version":"1.6.16.0"}, + "profunctors": {"dependencies":["base","base-orphans","bifunctors","comonad","contravariant","distributive","tagged","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/profunctors-5.6.2/profunctors-5.6.2.tar.gz"},"name":"profunctors","pinned":{"url":["https://hackage.haskell.org/package/profunctors-5.6.2/profunctors-5.6.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/profunctors-5.6.2.tar.gz"],"sha256":"65955d7b50525a4a3bccdab1d982d2ae342897fd38140d5a94b5ef3800d8c92a","cabal-sha256":"e178ba4468982326656626e2089e296f64485e68fdddc9f4476dcd5d612b4f78"},"version":"5.6.2"}, + "proto-lens": {"dependencies":["base","bytestring","containers","deepseq","ghc-prim","lens-family","parsec","pretty","primitive","profunctors","tagged","text","transformers","vector"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/proto-lens-0.7.1.3/proto-lens-0.7.1.3.tar.gz"},"name":"proto-lens","pinned":{"url":["https://hackage.haskell.org/package/proto-lens-0.7.1.3/proto-lens-0.7.1.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/proto-lens-0.7.1.3.tar.gz"],"sha256":"aac4317671a31d5f76cb120b5c4f75e644c45b441b4a2b9cfa7015bd8bbae3ac","cabal-sha256":"2d56bf8c37e21d741385e155d0dd327468ab1bc6897d10b0462b7e241d8e61a3"},"version":"0.7.1.3"}, + "proto-lens-protoc": {"dependencies":["base","bytestring","containers","filepath","ghc","ghc-paths","ghc-source-gen","lens-family","pretty","proto-lens","proto-lens-runtime","text"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/proto-lens-protoc-0.7.1.1/proto-lens-protoc-0.7.1.1.tar.gz"},"name":"proto-lens-protoc","pinned":{"url":["https://hackage.haskell.org/package/proto-lens-protoc-0.7.1.1/proto-lens-protoc-0.7.1.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/proto-lens-protoc-0.7.1.1.tar.gz"],"sha256":"0c412b47bce8a3898a61509b9a61c16e00ee947764bd22a07817ecc97a4080f2","cabal-sha256":"4b3b97d5caac9a9f8a85d426d5ad8a129f36e852dd05f42e614d9912030b9700"},"version":"0.7.1.1"}, + "proto-lens-runtime": {"dependencies":["base","bytestring","containers","deepseq","filepath","lens-family","proto-lens","text","vector"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/proto-lens-runtime-0.7.0.4/proto-lens-runtime-0.7.0.4.tar.gz"},"name":"proto-lens-runtime","pinned":{"url":["https://hackage.haskell.org/package/proto-lens-runtime-0.7.0.4/proto-lens-runtime-0.7.0.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/proto-lens-runtime-0.7.0.4.tar.gz"],"sha256":"5749cd01d97fd56bae5698830ba78adcc147e4b65b5e1b4b1cb6f9ee52587f47","cabal-sha256":"1a64cb98b49541e53ea8a19270d7247960445083a2327a091ce0a1cafdef16f3"},"version":"0.7.0.4"}, + "stm": {"dependencies":[],"location":{"type":"core"},"name":"stm","version":"2.5.0.2"}, + "tagged": {"dependencies":["base","deepseq","template-haskell","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/tagged-0.8.6.1/tagged-0.8.6.1.tar.gz"},"name":"tagged","pinned":{"url":["https://hackage.haskell.org/package/tagged-0.8.6.1/tagged-0.8.6.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/tagged-0.8.6.1.tar.gz"],"sha256":"f5e0fcf95f0bb4aa63f428f2c01955a41ea1a42cfcf39145ed631f59a9616c02","cabal-sha256":"8a24aef29b8e35447ccc56658ea07c2aded30bfa8130ea057e382936e17c74a6"},"version":"0.8.6.1"}, + "template-haskell": {"dependencies":[],"location":{"type":"core"},"name":"template-haskell","version":"2.18.0.0"}, + "text": {"dependencies":[],"location":{"type":"core"},"name":"text","version":"1.2.5.0"}, + "th-abstraction": {"dependencies":["base","containers","ghc-prim","template-haskell"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/th-abstraction-0.4.5.0/th-abstraction-0.4.5.0.tar.gz"},"name":"th-abstraction","pinned":{"url":["https://hackage.haskell.org/package/th-abstraction-0.4.5.0/th-abstraction-0.4.5.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/th-abstraction-0.4.5.0.tar.gz"],"sha256":"00d5e24f247e328bd9898d5af5915c1e86b134b4d40baa680258635f95031526","cabal-sha256":"c28f186ae9817a059e54f63689f8985194b7f58d8fbd79e157d12374b6f9d2c3"},"version":"0.4.5.0"}, + "time": {"dependencies":[],"location":{"type":"core"},"name":"time","version":"1.11.1.1"}, + "transformers": {"dependencies":[],"location":{"type":"core"},"name":"transformers","version":"0.5.6.2"}, + "transformers-compat": {"dependencies":["base","ghc-prim","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/transformers-compat-0.7.2/transformers-compat-0.7.2.tar.gz"},"name":"transformers-compat","pinned":{"url":["https://hackage.haskell.org/package/transformers-compat-0.7.2/transformers-compat-0.7.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/transformers-compat-0.7.2.tar.gz"],"sha256":"b62c7304c9f3cbc9463d0739aa85cb9489f217ea092b9d625d417514fbcc9d6a","cabal-sha256":"044fb9955f63ee138fcebedfdcbe54afe741f2d5892a2d0bdf3a8052bd342643"},"version":"0.7.2"}, + "unix": {"dependencies":[],"location":{"type":"core"},"name":"unix","version":"2.7.2.2"}, + "vector": {"dependencies":["base","deepseq","ghc-prim","primitive"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/vector-0.12.3.1/vector-0.12.3.1.tar.gz"},"name":"vector","pinned":{"url":["https://hackage.haskell.org/package/vector-0.12.3.1/vector-0.12.3.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/vector-0.12.3.1.tar.gz"],"sha256":"fb4a53c02bd4d7fdf155c0604da9a5bb0f3b3bfce5d9960aea11c2ae235b9f35","cabal-sha256":"39141f312871b7c793a63be76635999e84d442aa3290aec59f30638ec0bf23a7"},"version":"0.12.3.1"} + } +} \ No newline at end of file diff --git a/stackage_snapshot_9.2.8.yaml b/stackage_snapshot_9.2.8.yaml deleted file mode 120000 index da61c356a..000000000 --- a/stackage_snapshot_9.2.8.yaml +++ /dev/null @@ -1 +0,0 @@ -stackage_snapshot.yaml \ No newline at end of file diff --git a/stackage_snapshot_9.2.8.yaml b/stackage_snapshot_9.2.8.yaml new file mode 100644 index 000000000..7202f801b --- /dev/null +++ b/stackage_snapshot_9.2.8.yaml @@ -0,0 +1,22 @@ +# We drop the Win32 package from the stack snapshot so that stack considers it a toolchain library. +# In this case we will use the Win32 provided by the compiler instead of recompiling it. +# +# Recompiling it should be fine for future versions of Win32, +# but with versions <= 2.13.2.0 we encounter the following issue: +# https://github.com/haskell/win32/issues/193 + +resolver: lts-20.26 + +drop-packages: + - Win32 + +packages: +- git: https://github.com/tweag/cabal + commit: 42f04c3f639f10dc3c7981a0c663bfe08ad833cb + subdirs: + - Cabal + +# stackage lts-20.26/ghc 9.2.8 only contain Win32-2.12.0.1 +flags: + ansi-terminal: + Win32-2-13-1: false diff --git a/stackage_snapshot_9.4.6.json b/stackage_snapshot_9.4.6.json deleted file mode 100644 index fecbccdfd..000000000 --- a/stackage_snapshot_9.4.6.json +++ /dev/null @@ -1,54 +0,0 @@ -{ - "__GENERATED_FILE_DO_NOT_MODIFY_MANUALLY": -1103382728, - "all-cabal-hashes": "https://raw.githubusercontent.com/commercialhaskell/all-cabal-hashes/f9852bf631dd415e0fd690bc50f17abb12c618a6", - "resolved": { - "Cabal": {"dependencies":["Cabal-syntax","array","base","bytestring","containers","deepseq","directory","filepath","mtl","parsec","pretty","process","text","time","transformers","unix"],"location":{"type":"git","url":"https://github.com/tweag/cabal","commit":"4f8c4ab8274320c1a00992c9aa7c6559ff190fa9","subdir":"Cabal"},"name":"Cabal","version":"3.8.1.0"}, - "Cabal-syntax": {"dependencies":[],"location":{"type":"core"},"name":"Cabal-syntax","version":"3.8.1.0"}, - "StateVar": {"dependencies":["base","stm","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/StateVar-1.2.2/StateVar-1.2.2.tar.gz"},"name":"StateVar","pinned":{"url":["https://hackage.haskell.org/package/StateVar-1.2.2/StateVar-1.2.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/StateVar-1.2.2.tar.gz"],"sha256":"5e4b39da395656a59827b0280508aafdc70335798b50e5d6fd52596026251825","cabal-sha256":"3c022c00485fe165e3080d5da6b3ca9c9b02f62c5deebc584d1b3d1309ce673e"},"version":"1.2.2"}, - "alex": {"dependencies":["array","base","containers","directory"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/alex-3.3.0.0/alex-3.3.0.0.tar.gz"},"name":"alex","pinned":{"url":["https://hackage.haskell.org/package/alex-3.3.0.0/alex-3.3.0.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/alex-3.3.0.0.tar.gz"],"sha256":"810f8e85ea6b87c37cba10f7660d7f1aa0ba251c1275e3a18c312964bb329a63","cabal-sha256":"0ab9095e18bcace5adf1d07fcaa489ae4d5c141e9c0fcfeb5343362d04b9dc5b"},"version":"3.3.0.0"}, - "array": {"dependencies":[],"location":{"type":"core"},"name":"array","version":"0.5.4.0"}, - "base": {"dependencies":[],"location":{"type":"core"},"name":"base","version":"4.17.2.0"}, - "base-orphans": {"dependencies":["base","ghc-prim"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/base-orphans-0.9.0/base-orphans-0.9.0.tar.gz"},"name":"base-orphans","pinned":{"url":["https://hackage.haskell.org/package/base-orphans-0.9.0/base-orphans-0.9.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/base-orphans-0.9.0.tar.gz"],"sha256":"613ed4d8241ed5a648a59ae6569a6962990bb545711d020d49fb83fa12d16e62","cabal-sha256":"0bdd3486d3a1bcbed0513b46af4a13ca74b395313fa5b6e0068d6b7413b76a04"},"version":"0.9.0"}, - "bifunctors": {"dependencies":["base","base-orphans","comonad","containers","tagged","template-haskell","th-abstraction","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/bifunctors-5.5.15/bifunctors-5.5.15.tar.gz"},"name":"bifunctors","pinned":{"url":["https://hackage.haskell.org/package/bifunctors-5.5.15/bifunctors-5.5.15.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/bifunctors-5.5.15.tar.gz"],"sha256":"d6359d50d359dd6048dbf6d56c7628211a1785aab9174177faa6d2d8b0d9e3b7","cabal-sha256":"5ebaf9a1996de38ad9d77bec37a5585b6461b34f39446e8f1cadae7689a12bfd"},"version":"5.5.15"}, - "bytestring": {"dependencies":[],"location":{"type":"core"},"name":"bytestring","version":"0.11.5.1"}, - "c2hs": {"dependencies":["array","base","bytestring","containers","directory","dlist","filepath","language-c","pretty","process"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/c2hs-0.28.8/c2hs-0.28.8.tar.gz"},"name":"c2hs","pinned":{"url":["https://hackage.haskell.org/package/c2hs-0.28.8/c2hs-0.28.8.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/c2hs-0.28.8.tar.gz"],"sha256":"390632cffc561c32483af474aac50168a68f0fa382096552e37749923617884c","cabal-sha256":"c399132e2273e70770be403fba4795d7d8c60d7bd147f0ef174342bebbd44392"},"version":"0.28.8"}, - "comonad": {"dependencies":["base","containers","distributive","indexed-traversable","tagged","transformers","transformers-compat"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/comonad-5.0.8/comonad-5.0.8.tar.gz"},"name":"comonad","pinned":{"url":["https://hackage.haskell.org/package/comonad-5.0.8/comonad-5.0.8.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/comonad-5.0.8.tar.gz"],"sha256":"ef6cdf2cc292cc43ee6aa96c581b235fdea8ab44a0bffb24dc79ae2b2ef33d13","cabal-sha256":"4a4dbfbd03fb4963987710fca994e8b5624bd05a33e5f95b7581b26f8229c5e3"},"version":"5.0.8"}, - "containers": {"dependencies":[],"location":{"type":"core"},"name":"containers","version":"0.6.7"}, - "contravariant": {"dependencies":["StateVar","base","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/contravariant-1.5.5/contravariant-1.5.5.tar.gz"},"name":"contravariant","pinned":{"url":["https://hackage.haskell.org/package/contravariant-1.5.5/contravariant-1.5.5.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/contravariant-1.5.5.tar.gz"],"sha256":"062fd66580d7aad0b5ba93e644ffa7feee69276ef50f20d4ed9f1deb7642dffa","cabal-sha256":"470ed0e040e879e2da4af1b2c8f94e199f6135852a8107858d5ae0a95365835f"},"version":"1.5.5"}, - "data-default-class": {"dependencies":["base"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/data-default-class-0.1.2.0/data-default-class-0.1.2.0.tar.gz"},"name":"data-default-class","pinned":{"url":["https://hackage.haskell.org/package/data-default-class-0.1.2.0/data-default-class-0.1.2.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/data-default-class-0.1.2.0.tar.gz"],"sha256":"4f01b423f000c3e069aaf52a348564a6536797f31498bb85c3db4bd2d0973e56","cabal-sha256":"63e62120b7efd733a5a17cf59ceb43268e9a929c748127172d7d42f4a336e327"},"version":"0.1.2.0"}, - "deepseq": {"dependencies":[],"location":{"type":"core"},"name":"deepseq","version":"1.4.8.0"}, - "directory": {"dependencies":[],"location":{"type":"core"},"name":"directory","version":"1.3.7.1"}, - "distributive": {"dependencies":["base","base-orphans","tagged","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/distributive-0.6.2.1/distributive-0.6.2.1.tar.gz"},"name":"distributive","pinned":{"url":["https://hackage.haskell.org/package/distributive-0.6.2.1/distributive-0.6.2.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/distributive-0.6.2.1.tar.gz"],"sha256":"d7351392e078f58caa46630a4b9c643e1e2e9dddee45848c5c8358e7b1316b91","cabal-sha256":"0f99f5541cca04acf89b64432b03422b6408e830a8dff30e6c4334ef1a48680c"},"version":"0.6.2.1"}, - "dlist": {"dependencies":["base","deepseq"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/dlist-1.0/dlist-1.0.tar.gz"},"name":"dlist","pinned":{"url":["https://hackage.haskell.org/package/dlist-1.0/dlist-1.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/dlist-1.0.tar.gz"],"sha256":"173d637328bb173fcc365f30d29ff4a94292a1e0e5558aeb3dfc11de81510115","cabal-sha256":"55ff69d20ce638fc7727342ee67f2f868da61d3dcf3763f790bf9aa0b145e568"},"version":"1.0"}, - "filepath": {"dependencies":[],"location":{"type":"core"},"name":"filepath","version":"1.4.2.2"}, - "ghc": {"dependencies":[],"location":{"type":"core"},"name":"ghc","version":"9.4.6"}, - "ghc-paths": {"dependencies":["base"],"location":{"type":"vendored"},"name":"ghc-paths","version":"0.1.0.11"}, - "ghc-prim": {"dependencies":[],"location":{"type":"core"},"name":"ghc-prim","version":"0.9.1"}, - "ghc-source-gen": {"dependencies":["base","ghc"],"location":{"type":"git","url":"https://github.com/circuithub/ghc-source-gen","commit":"7a6aac047b706508e85ba2054b5bedbecfd7eb7a","subdir":""},"name":"ghc-source-gen","version":"0.4.3.0"}, - "happy": {"dependencies":["array","base","containers","mtl"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/happy-1.20.1.1/happy-1.20.1.1.tar.gz"},"name":"happy","pinned":{"url":["https://hackage.haskell.org/package/happy-1.20.1.1/happy-1.20.1.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/happy-1.20.1.1.tar.gz"],"sha256":"8b4e7dc5a6c5fd666f8f7163232931ab28746d0d17da8fa1cbd68be9e878881b","cabal-sha256":"a381633c5e8f9e9e5a8e1900930ce13172397b4677fcfcc08cd38eb3f73b61b1"},"version":"1.20.1.1"}, - "indexed-traversable": {"dependencies":["array","base","containers","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/indexed-traversable-0.1.2.1/indexed-traversable-0.1.2.1.tar.gz"},"name":"indexed-traversable","pinned":{"url":["https://hackage.haskell.org/package/indexed-traversable-0.1.2.1/indexed-traversable-0.1.2.1.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/indexed-traversable-0.1.2.1.tar.gz"],"sha256":"fe854c10285debc7d6fe3e09da0928a740ebc091ad2911ae695bb007e6f746a4","cabal-sha256":"154b4649199a602dea948a93cb34a6c4be71576c4f78410733dd9f6bc79b6e0b"},"version":"0.1.2.1"}, - "language-c": {"dependencies":["alex","array","base","bytestring","containers","deepseq","directory","filepath","happy","mtl","pretty","process"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/language-c-0.9.2/language-c-0.9.2.tar.gz"},"name":"language-c","pinned":{"url":["https://hackage.haskell.org/package/language-c-0.9.2/language-c-0.9.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/language-c-0.9.2.tar.gz"],"sha256":"b2310d2fda16df72e9f8f63ef18bec2e09ae3aff5891dc948c3d9cb72cef6cb3","cabal-sha256":"a4b77129d7d30d777e0f203ba9c18b88f4791f95c079fef573b554f915dcf57d"},"version":"0.9.2"}, - "lens-family": {"dependencies":["base","containers","lens-family-core","mtl","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/lens-family-2.1.2/lens-family-2.1.2.tar.gz"},"name":"lens-family","pinned":{"url":["https://hackage.haskell.org/package/lens-family-2.1.2/lens-family-2.1.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/lens-family-2.1.2.tar.gz"],"sha256":"2b60afc3afc03b6e328fc96e291e21bb0a63b563657cabe7ba5febd471283648","cabal-sha256":"c13af34889ed9637b2dbd4542122c01a6ec1351cc6dda673de0079f9b02747ef"},"version":"2.1.2"}, - "lens-family-core": {"dependencies":["base","containers","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/lens-family-core-2.1.2/lens-family-core-2.1.2.tar.gz"},"name":"lens-family-core","pinned":{"url":["https://hackage.haskell.org/package/lens-family-core-2.1.2/lens-family-core-2.1.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/lens-family-core-2.1.2.tar.gz"],"sha256":"1b5a997276c8b77a96f99f48b95b204d34f3bb84fa3691747cd30bc8c76873b6","cabal-sha256":"702013af981089f991c93598762b8804314266c2bd7d92fc35fb6a8b62af1883"},"version":"2.1.2"}, - "mtl": {"dependencies":[],"location":{"type":"core"},"name":"mtl","version":"2.2.2"}, - "parsec": {"dependencies":[],"location":{"type":"core"},"name":"parsec","version":"3.1.16.1"}, - "pretty": {"dependencies":[],"location":{"type":"core"},"name":"pretty","version":"1.1.3.6"}, - "primitive": {"dependencies":["base","deepseq","template-haskell","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/primitive-0.8.0.0/primitive-0.8.0.0.tar.gz"},"name":"primitive","pinned":{"url":["https://hackage.haskell.org/package/primitive-0.8.0.0/primitive-0.8.0.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/primitive-0.8.0.0.tar.gz"],"sha256":"5553c21b4a789f9b591eed69e598cc58484c274af29250e517b5a8bcc62b995f","cabal-sha256":"d0ff45fa6e61f92af23611ceb8b9a6a04c236b50fb70c60e2ed3bfa532703670"},"version":"0.8.0.0"}, - "process": {"dependencies":[],"location":{"type":"core"},"name":"process","version":"1.6.17.0"}, - "profunctors": {"dependencies":["base","base-orphans","bifunctors","comonad","contravariant","distributive","tagged","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/profunctors-5.6.2/profunctors-5.6.2.tar.gz"},"name":"profunctors","pinned":{"url":["https://hackage.haskell.org/package/profunctors-5.6.2/profunctors-5.6.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/profunctors-5.6.2.tar.gz"],"sha256":"65955d7b50525a4a3bccdab1d982d2ae342897fd38140d5a94b5ef3800d8c92a","cabal-sha256":"e178ba4468982326656626e2089e296f64485e68fdddc9f4476dcd5d612b4f78"},"version":"5.6.2"}, - "proto-lens": {"dependencies":["base","bytestring","containers","deepseq","ghc-prim","lens-family","parsec","pretty","primitive","profunctors","tagged","text","transformers","vector"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/proto-lens-0.7.1.3/proto-lens-0.7.1.3.tar.gz"},"name":"proto-lens","pinned":{"url":["https://hackage.haskell.org/package/proto-lens-0.7.1.3/proto-lens-0.7.1.3.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/proto-lens-0.7.1.3.tar.gz"],"sha256":"aac4317671a31d5f76cb120b5c4f75e644c45b441b4a2b9cfa7015bd8bbae3ac","cabal-sha256":"2d56bf8c37e21d741385e155d0dd327468ab1bc6897d10b0462b7e241d8e61a3"},"version":"0.7.1.3"}, - "proto-lens-protoc": {"dependencies":["base","bytestring","containers","filepath","ghc","ghc-paths","ghc-source-gen","lens-family","pretty","proto-lens","proto-lens-runtime","text"],"location":{"type":"git","url":"https://github.com/avdv/proto-lens","commit":"2ab0a8d1ec1f54f3d1a0ecd1a257311389126490","subdir":""},"name":"proto-lens-protoc","version":"0.7.1.1"}, - "proto-lens-runtime": {"dependencies":["base","bytestring","containers","deepseq","filepath","lens-family","proto-lens","text","vector"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/proto-lens-runtime-0.7.0.4/proto-lens-runtime-0.7.0.4.tar.gz"},"name":"proto-lens-runtime","pinned":{"url":["https://hackage.haskell.org/package/proto-lens-runtime-0.7.0.4/proto-lens-runtime-0.7.0.4.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/proto-lens-runtime-0.7.0.4.tar.gz"],"sha256":"5749cd01d97fd56bae5698830ba78adcc147e4b65b5e1b4b1cb6f9ee52587f47","cabal-sha256":"1a64cb98b49541e53ea8a19270d7247960445083a2327a091ce0a1cafdef16f3"},"version":"0.7.0.4"}, - "stm": {"dependencies":[],"location":{"type":"core"},"name":"stm","version":"2.5.1.0"}, - "tagged": {"dependencies":["base","deepseq","template-haskell","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/tagged-0.8.7/tagged-0.8.7.tar.gz"},"name":"tagged","pinned":{"url":["https://hackage.haskell.org/package/tagged-0.8.7/tagged-0.8.7.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/tagged-0.8.7.tar.gz"],"sha256":"6414eeac27a1633f49e2f78199ced99ce8ce3d70b658cf6d55b1d81ff60cb961","cabal-sha256":"9013e1491dc0d291cb37c2845973293a03c230374f44792bfc96e14fdfb426dc"},"version":"0.8.7"}, - "template-haskell": {"dependencies":[],"location":{"type":"core"},"name":"template-haskell","version":"2.19.0.0"}, - "text": {"dependencies":[],"location":{"type":"core"},"name":"text","version":"2.0.2"}, - "th-abstraction": {"dependencies":["base","containers","ghc-prim","template-haskell"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/th-abstraction-0.4.5.0/th-abstraction-0.4.5.0.tar.gz"},"name":"th-abstraction","pinned":{"url":["https://hackage.haskell.org/package/th-abstraction-0.4.5.0/th-abstraction-0.4.5.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/th-abstraction-0.4.5.0.tar.gz"],"sha256":"00d5e24f247e328bd9898d5af5915c1e86b134b4d40baa680258635f95031526","cabal-sha256":"c28f186ae9817a059e54f63689f8985194b7f58d8fbd79e157d12374b6f9d2c3"},"version":"0.4.5.0"}, - "time": {"dependencies":[],"location":{"type":"core"},"name":"time","version":"1.12.2"}, - "transformers": {"dependencies":[],"location":{"type":"core"},"name":"transformers","version":"0.5.6.2"}, - "transformers-compat": {"dependencies":["base","ghc-prim","transformers"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/transformers-compat-0.7.2/transformers-compat-0.7.2.tar.gz"},"name":"transformers-compat","pinned":{"url":["https://hackage.haskell.org/package/transformers-compat-0.7.2/transformers-compat-0.7.2.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/transformers-compat-0.7.2.tar.gz"],"sha256":"b62c7304c9f3cbc9463d0739aa85cb9489f217ea092b9d625d417514fbcc9d6a","cabal-sha256":"044fb9955f63ee138fcebedfdcbe54afe741f2d5892a2d0bdf3a8052bd342643"},"version":"0.7.2"}, - "unix": {"dependencies":[],"location":{"type":"core"},"name":"unix","version":"2.7.3"}, - "vector": {"dependencies":["base","deepseq","primitive","vector-stream"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/vector-0.13.0.0/vector-0.13.0.0.tar.gz"},"name":"vector","pinned":{"url":["https://hackage.haskell.org/package/vector-0.13.0.0/vector-0.13.0.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/vector-0.13.0.0.tar.gz"],"sha256":"c5d3167d15e12f52e00879ddf304a591672a74e369cc47bc5c7fa1d5a8d15b4f","cabal-sha256":"1d0b2128c7151e06c2417616afedcb1a4d54087afeba623c55dd4b29094d4348"},"version":"0.13.0.0"}, - "vector-stream": {"dependencies":["base","ghc-prim"],"location":{"type":"hackage","url":"https://hackage.haskell.org/package/vector-stream-0.1.0.0/vector-stream-0.1.0.0.tar.gz"},"name":"vector-stream","pinned":{"url":["https://hackage.haskell.org/package/vector-stream-0.1.0.0/vector-stream-0.1.0.0.tar.gz","https://s3.amazonaws.com/hackage.fpcomplete.com/package/vector-stream-0.1.0.0.tar.gz"],"sha256":"a888210f6467f155090653734be5cc920406a07227e0d3adb59096716fdb806c","cabal-sha256":"8977959d4bec54d9f2c5e9d4baa2cac7ab26e804a72591df8db887e0692ae8ae"},"version":"0.1.0.0"} - } -} \ No newline at end of file diff --git a/stackage_snapshot_9.4.6.json b/stackage_snapshot_9.4.6.json new file mode 120000 index 000000000..c81f31ff7 --- /dev/null +++ b/stackage_snapshot_9.4.6.json @@ -0,0 +1 @@ +stackage_snapshot.json \ No newline at end of file diff --git a/stackage_snapshot_9.4.6.yaml b/stackage_snapshot_9.4.6.yaml deleted file mode 100644 index 70b173692..000000000 --- a/stackage_snapshot_9.4.6.yaml +++ /dev/null @@ -1,30 +0,0 @@ -# We drop the Win32 package from the stack snapshot so that stack considers it a toolchain library. -# In this case we will use the Win32 provided by the compiler instead of recompiling it. -# -# Recompiling it should be fine for future versions of Win32, -# but with versions <= 2.13.2.0 we encounter the following issue: -# https://github.com/haskell/win32/issues/193 - -resolver: lts-21.11 - -drop-packages: - - Win32 - -packages: -- git: https://github.com/tweag/cabal - commit: 4f8c4ab8274320c1a00992c9aa7c6559ff190fa9 - subdirs: - - Cabal - -# See https://github.com/avdv/proto-lens#readme -- git: https://github.com/avdv/proto-lens - commit: 2ab0a8d1ec1f54f3d1a0ecd1a257311389126490 - -# support GHC 9.4 (see https://github.com/google/ghc-source-gen/pull/102) -- git: https://github.com/google/ghc-source-gen - commit: 7527305ed59a47140053cf7bc87432fe1f8804d0 - -# stackage lts-21.11/ghc 9.4.6 only contain Win32-2.12.0.1 -flags: - ansi-terminal: - Win32-2-13-1: false diff --git a/stackage_snapshot_9.4.6.yaml b/stackage_snapshot_9.4.6.yaml new file mode 120000 index 000000000..da61c356a --- /dev/null +++ b/stackage_snapshot_9.4.6.yaml @@ -0,0 +1 @@ +stackage_snapshot.yaml \ No newline at end of file diff --git a/start b/start index 169b9c7ea..ae99b990b 100755 --- a/start +++ b/start @@ -6,8 +6,8 @@ set -eu # If the environment variable `GHC_VERSION` is not set yet, -# we use the default version (currently "9.2.8"). -GHC_VERSION=${GHC_VERSION:="9.2.8"} +# we use the default version (currently "9.4.6"). +GHC_VERSION=${GHC_VERSION:="9.4.6"} readonly MIN_BAZEL_MAJOR=6 readonly MIN_BAZEL_MINOR=0 @@ -314,7 +314,7 @@ EOF # https://github.com/tweag/rules_nixpkgs/blob/master/README.md nixpkgs_git_repository( name = "nixpkgs", - revision = "nixos-23.05", + revision = "nixos-23.11", ) nixpkgs_cc_configure( diff --git a/tutorial/WORKSPACE b/tutorial/WORKSPACE index 05e96dc47..52789c30d 100644 --- a/tutorial/WORKSPACE +++ b/tutorial/WORKSPACE @@ -12,14 +12,14 @@ rules_haskell_dependencies() load("@rules_haskell//haskell:nixpkgs.bzl", "haskell_register_ghc_nixpkgs") haskell_register_ghc_nixpkgs( - attribute_path = "haskell.compiler.ghc928", + attribute_path = "haskell.compiler.ghc946", repository = "@rules_haskell//nixpkgs:default.nix", - version = "9.2.8", + version = "9.4.6", ) load("@rules_haskell//haskell:toolchain.bzl", "rules_haskell_toolchains") -rules_haskell_toolchains(version = "9.2.8") +rules_haskell_toolchains(version = "9.4.6") load( "@io_tweag_rules_nixpkgs//nixpkgs:nixpkgs.bzl",