summaryrefslogtreecommitdiff
path: root/libraries/base/GHC/Generics.hs
diff options
context:
space:
mode:
Diffstat (limited to 'libraries/base/GHC/Generics.hs')
-rw-r--r--libraries/base/GHC/Generics.hs108
1 files changed, 107 insertions, 1 deletions
diff --git a/libraries/base/GHC/Generics.hs b/libraries/base/GHC/Generics.hs
index d98533b5b2..3e38930261 100644
--- a/libraries/base/GHC/Generics.hs
+++ b/libraries/base/GHC/Generics.hs
@@ -8,6 +8,7 @@
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE MagicHash #-}
-----------------------------------------------------------------------------
-- |
@@ -532,6 +533,65 @@ module GHC.Generics (
-- @
-- newtype (':.:') f g p = 'Comp1' { 'unComp1' :: f (g p) }
-- @
+
+-- *** Representation of unlifted types
+--
+-- |
+--
+-- If one were to attempt to derive a Generic instance for a datatype with an
+-- unlifted argument (for example, 'Int#'), one might expect the occurrence of
+-- the 'Int#' argument to be marked with @'Rec0' 'Int#'@. This won't work,
+-- though, since 'Int#' is of kind @#@ and 'Rec0' expects a type of kind @*@.
+-- In fact, polymorphism over unlifted types is disallowed completely.
+--
+-- One solution would be to represent an occurrence of 'Int#' with 'Rec0 Int'
+-- instead. With this approach, however, the programmer has no way of knowing
+-- whether the 'Int' is actually an 'Int#' in disguise.
+--
+-- Instead of reusing 'Rec0', a separate data family 'URec' is used to mark
+-- occurrences of common unlifted types:
+--
+-- @
+-- data family URec a p
+--
+-- data instance 'URec' ('Ptr' ()) p = 'UAddr' { 'uAddr#' :: 'Addr#' }
+-- data instance 'URec' 'Char' p = 'UChar' { 'uChar#' :: 'Char#' }
+-- data instance 'URec' 'Double' p = 'UDouble' { 'uDouble#' :: 'Double#' }
+-- data instance 'URec' 'Int' p = 'UFloat' { 'uFloat#' :: 'Float#' }
+-- data instance 'URec' 'Float' p = 'UInt' { 'uInt#' :: 'Int#' }
+-- data instance 'URec' 'Word' p = 'UWord' { 'uWord#' :: 'Word#' }
+-- @
+--
+-- Several type synonyms are provided for convenience:
+--
+-- @
+-- type 'UAddr' = 'URec' ('Ptr' ())
+-- type 'UChar' = 'URec' 'Char'
+-- type 'UDouble' = 'URec' 'Double'
+-- type 'UFloat' = 'URec' 'Float'
+-- type 'UInt' = 'URec' 'Int'
+-- type 'UWord' = 'URec' 'Word'
+-- @
+--
+-- The declaration
+--
+-- @
+-- data IntHash = IntHash Int#
+-- deriving 'Generic'
+-- @
+--
+-- yields
+--
+-- @
+-- instance 'Generic' IntHash where
+-- type 'Rep' IntHash =
+-- 'D1' D1IntHash
+-- ('C1' C1_0IntHash
+-- ('S1' 'NoSelector' 'UInt'))
+-- @
+--
+-- Currently, only the six unlifted types listed above are generated, but this
+-- may be extended to encompass more unlifted types in the future.
#if 0
-- *** Limitations
--
@@ -548,6 +608,11 @@ module GHC.Generics (
V1, U1(..), Par1(..), Rec1(..), K1(..), M1(..)
, (:+:)(..), (:*:)(..), (:.:)(..)
+ -- ** Unboxed representation types
+ , URec(..)
+ , type UAddr, type UChar, type UDouble
+ , type UFloat, type UInt, type UWord
+
-- ** Synonyms for convenience
, Rec0, Par0, R, P
, D1, C1, S1, D, C, S
@@ -562,6 +627,8 @@ module GHC.Generics (
) where
-- We use some base types
+import GHC.Prim ( Addr#, Char#, Double#, Float#, Int#, Word# )
+import GHC.Ptr ( Ptr )
import GHC.Types
import Data.Maybe ( Maybe(..) )
import Data.Either ( Either(..) )
@@ -614,6 +681,46 @@ infixr 7 :.:
newtype (:.:) f (g :: * -> *) (p :: *) = Comp1 { unComp1 :: f (g p) }
deriving (Eq, Ord, Read, Show, Generic)
+-- | Constants of kind @#@
+data family URec (a :: *) (p :: *)
+
+-- | Used for marking occurrences of 'Addr#'
+data instance URec (Ptr ()) p = UAddr { uAddr# :: Addr# }
+ deriving (Eq, Ord, Generic)
+
+-- | Used for marking occurrences of 'Char#'
+data instance URec Char p = UChar { uChar# :: Char# }
+ deriving (Eq, Ord, Show, Generic)
+
+-- | Used for marking occurrences of 'Double#'
+data instance URec Double p = UDouble { uDouble# :: Double# }
+ deriving (Eq, Ord, Show, Generic)
+
+-- | Used for marking occurrences of 'Float#'
+data instance URec Float p = UFloat { uFloat# :: Float# }
+ deriving (Eq, Ord, Show, Generic)
+
+-- | Used for marking occurrences of 'Int#'
+data instance URec Int p = UInt { uInt# :: Int# }
+ deriving (Eq, Ord, Show, Generic)
+
+-- | Used for marking occurrences of 'Word#'
+data instance URec Word p = UWord { uWord# :: Word# }
+ deriving (Eq, Ord, Show, Generic)
+
+-- | Type synonym for 'URec': 'Addr#'
+type UAddr = URec (Ptr ())
+-- | Type synonym for 'URec': 'Char#'
+type UChar = URec Char
+-- | Type synonym for 'URec': 'Double#'
+type UDouble = URec Double
+-- | Type synonym for 'URec': 'Float#'
+type UFloat = URec Float
+-- | Type synonym for 'URec': 'Int#'
+type UInt = URec Int
+-- | Type synonym for 'URec': 'Word#'
+type UWord = URec Word
+
-- | Tag for K1: recursion (of kind *)
data R
-- | Tag for K1: parameters (other than the last)
@@ -642,7 +749,6 @@ type C1 = M1 C
-- | Type synonym for encoding meta-information for record selectors
type S1 = M1 S
-
-- | Class for datatypes that represent datatypes
class Datatype (d :: *) where
-- | The name of the datatype (unqualified)