[Git][ghc/ghc][wip/andreask/ghc-primops] ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps
Andreas Klebinger (@AndreasK)
gitlab at gitlab.haskell.org
Tue Sep 10 15:07:47 UTC 2024
Andreas Klebinger pushed to branch wip/andreask/ghc-primops at Glasgow Haskell Compiler / GHC
Commits:
ac9b303d by Andreas Klebinger at 2024-09-10T16:48:53+02:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps
This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.
Addresses #25242
- - - - -
2 changed files:
- libraries/ghc-experimental/ghc-experimental.cabal.in
- + libraries/ghc-experimental/src/GHC/PrimOps.hs
Changes:
=====================================
libraries/ghc-experimental/ghc-experimental.cabal.in
=====================================
@@ -29,6 +29,7 @@ library
exposed-modules:
Data.Sum.Experimental
Data.Tuple.Experimental
+ GHC.PrimOps
GHC.Profiling.Eras
GHC.TypeLits.Experimental
GHC.TypeNats.Experimental
=====================================
libraries/ghc-experimental/src/GHC/PrimOps.hs
=====================================
@@ -0,0 +1,31 @@
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE Unsafe #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# OPTIONS_HADDOCK print-explicit-runtime-reps #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module : GHC.PrimOps
+-- Copyright : Andreas Klebinger 2024
+-- License : see libraries/ghc-experimental/LICENSE
+--
+-- Maintainer : ghc-devs at haskell.org
+-- Stability : internal
+-- Portability : non-portable (GHC Extensions)
+--
+-- GHC Extensions: This is the Approved Way to get at GHC-specific extensions
+-- without relying on the ghc-internal package.
+-----------------------------------------------------------------------------
+
+module GHC.PrimOps
+ (
+ module GHC.Internal.Exts,
+ ) where
+
+import GHC.Internal.Exts
+
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ac9b303dda899ca82b5671375aac1dfcc485a62f
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ac9b303dda899ca82b5671375aac1dfcc485a62f
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240910/f02b36c2/attachment-0001.html>
More information about the ghc-commits
mailing list