[GHC] #15812: add System.Mem.Address to base

#15812: add System.Mem.Address to base -------------------------------------+------------------------------------- Reporter: carter | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: | Version: 8.7 libraries/base | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): D5268 | Wiki Page: -------------------------------------+------------------------------------- per libraries in progress discussion and https://phabricator.haskell.org/D5268 current state is this {{{ {-# LANGUAGE MagicHash #-} Module System.Mem.Address ( -- * Types Addr(..), -- * Address arithmetic nullAddr, plusAddr, minusAddr, remAddr, -- * Conversion addrToInt, addrToPtr, ptrToAddr ) where import GHC.Base ( Int(..) ) import GHC.Prim import GHC.Exts (isTrue#) import GHC.Ptr import Foreign.Marshal.Utils import Data.Typeable ( Typeable ) import Data.Data ( Data(..), mkNoRepType ) -- | A machine address data Addr = Addr Addr# deriving ( Typeable ) instance Show Addr where showsPrec _ (Addr a) = showString "0x" . showHex (fromIntegral (I# (addr2Int# a)) :: Word) instance Eq Addr where Addr a# == Addr b# = isTrue# (eqAddr# a# b#) Addr a# /= Addr b# = isTrue# (neAddr# a# b#) instance Ord Addr where Addr a# > Addr b# = isTrue# (gtAddr# a# b#) Addr a# >= Addr b# = isTrue# (geAddr# a# b#) Addr a# < Addr b# = isTrue# (ltAddr# a# b#) Addr a# <= Addr b# = isTrue# (leAddr# a# b#) instance Data Addr where toConstr _ = error "toConstr" gunfold _ _ = error "gunfold" dataTypeOf _ = mkNoRepType "Data.Primitive.Types.Addr" -- | The null address nullAddr :: Addr nullAddr = Addr nullAddr# infixl 6 `plusAddr`, `minusAddr` infixl 7 `remAddr` -- | Offset an address by the given number of bytes plusAddr :: Addr -> Int -> Addr plusAddr (Addr a#) (I# i#) = Addr (plusAddr# a# i#) -- | Distance in bytes between two addresses. The result is only valid if the -- difference fits in an 'Int'. minusAddr :: Addr -> Addr -> Int minusAddr (Addr a#) (Addr b#) = I# (minusAddr# a# b#) -- | The remainder of the address and the integer. remAddr :: Addr -> Int -> Int remAddr (Addr a#) (I# i#) = I# (remAddr# a# i#) -- | Convert an 'Addr' to an 'Int'. addrToInt :: Addr -> Int {-# INLINE addrToInt #-} addrToInt (Addr addr#) = I# (addr2Int# addr#) -- | convert `Addr` to `Ptr a` addrToPtr :: Addr -> Ptr a addrToPtr (Addr addr#) = Ptr addr# -- | convert `Ptr a` to `Addr` ptrToAddr :: Ptr a -> Addr ptrToAddr (Ptr p) = Addr p }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15812 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15812: add System.Mem.Address to base -------------------------------------+------------------------------------- Reporter: carter | Owner: (none) Type: feature request | Status: patch Priority: normal | Milestone: 8.8.1 Component: libraries/base | Version: 8.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): D5268 Wiki Page: | -------------------------------------+------------------------------------- Changes (by carter): * status: new => patch * type: bug => feature request -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15812#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15812: add System.Mem.Address to base -------------------------------------+------------------------------------- Reporter: carter | Owner: (none) Type: feature request | Status: patch Priority: normal | Milestone: 8.8.1 Component: libraries/base | Version: 8.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5268 Wiki Page: | -------------------------------------+------------------------------------- Changes (by trommler): * differential: D5268 => Phab:D5268 Comment: Fixed Phabricator link. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15812#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15812: add System.Mem.Address to base -------------------------------------+------------------------------------- Reporter: carter | Owner: (none) Type: feature request | Status: patch Priority: normal | Milestone: 8.10.1 Component: libraries/base | Version: 8.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5268 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.8.1 => 8.10.1 Comment: carter, where is the discussion for this? Regardless, this won't happen for 8.8. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15812#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15812: add System.Mem.Address to base -------------------------------------+------------------------------------- Reporter: carter | Owner: (none) Type: feature request | Status: patch Priority: normal | Milestone: 8.10.1 Component: libraries/base | Version: 8.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5268 Wiki Page: | -------------------------------------+------------------------------------- Comment (by carter): the discussion started in https://mail.haskell.org/pipermail/libraries/2018-October/028997.html (https://mail.haskell.org/pipermail/libraries/2018-October/thread.html) and continued through november https://mail.haskell.org/pipermail/libraries/2018-November/thread.html i'll write up more notes later, but ultimately the conclusion seems to be : 1. theres not really any examples where the code becomes simpler/safer/more performant with Address in base and usage thereof 2. there are valid/ real issues with some Ptr based interfaces and they could be improved. (and some confusion about why/best/practicies, and in one case the mistaken belief that all `Ptr a` values will conform to the Storable type class representation) there were ~ 3 people arguing for inclusion in base, but in my own opinion there wasn't a case substantiating their utility. (and some of the exemplar changes they suggested would needless break existing code without fixing any underlying issue, as best i could tell) Punchline: theres definitely a genuine need for better tooling around pointers to make its way into the ecosystem and perhaps eventually base, but this Adddress work doesn't accomplish that -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15812#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15812: add System.Mem.Address to base -------------------------------------+------------------------------------- Reporter: carter | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: 8.10.1 Component: libraries/base | Version: 8.7 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5268 Wiki Page: | -------------------------------------+------------------------------------- Changes (by carter): * status: patch => closed * resolution: => wontfix -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15812#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC