File: Generics.hs

package info (click to toggle)
haskell-deepseq-generics 0.2.0.0-9
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 92 kB
  • sloc: haskell: 144; makefile: 3
file content (164 lines) | stat: -rw-r--r-- 5,049 bytes parent folder | download | duplicates (5)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
{-# LANGUAGE BangPatterns, TypeOperators, FlexibleContexts #-}

-- |
-- Module:  Control.DeepSeq.Generics
-- Copyright:   (c) 2012, Herbert Valerio Riedel
-- License:     BSD-style (see the LICENSE file)
--
-- Maintainer:  Herbert Valerio Riedel <hvr@gnu.org>
-- Stability:   stable
-- Portability: GHC
--
-- __NOTE__: Starting with @deepseq-1.4.0.0@, 'NFData' gained support
-- for generic derivation via @DefaultSignatures@. The new default
-- 'rnf' method implementation is then equivalent to
--
-- @
-- instance NFData MyType where
--   'rnf' = 'genericRnfV1'
-- @
--
-- See documentation of 'rnf' for more details on how to use the new
-- built-in 'Generic' support.

module Control.DeepSeq.Generics
    ( genericRnf
    , genericRnfV1
    ) where

import Control.DeepSeq
import GHC.Generics

-- | "GHC.Generics"-based 'rnf' implementation
--
-- This provides a generic `rnf` implementation for one type at a
-- time. If the type of the value 'genericRnf' is asked to reduce to
-- NF contains values of other types, those types have to provide
-- 'NFData' instances. This also means that recursive types can only
-- be used with 'genericRnf' if a 'NFData' instance has been defined
-- as well (see examples below).
--
-- The typical usage for 'genericRnf' is for reducing boilerplate code
-- when defining 'NFData' instances for ordinary algebraic
-- datatypes. See the code below for some simple usage examples:
--
-- > {-# LANGUAGE DeriveGeneric #-}
-- >
-- > import Control.DeepSeq
-- > import Control.DeepSeq.Generics (genericRnf)
-- > import GHC.Generics
-- >
-- > -- simple record
-- > data Foo = Foo AccountId Name Address
-- >          deriving Generic
-- >
-- > type Address      = [String]
-- > type Name         = String
-- > newtype AccountId = AccountId Int
-- >
-- > instance NFData AccountId
-- > instance NFData Foo where rnf = genericRnf
-- >
-- > -- recursive list-like type
-- > data N = Z | S N deriving Generic
-- >
-- > instance NFData N where rnf = genericRnf
-- >
-- > -- parametric & recursive type
-- > data Bar a = Bar0 | Bar1 a | Bar2 (Bar a)
-- >            deriving Generic
-- >
-- > instance NFData a => NFData (Bar a) where rnf = genericRnf
--
-- __NOTE__: The 'GNFData' type-class showing up in the type-signature is
--           used internally and not exported.

genericRnf :: (Generic a, GNFData (Rep a)) => a -> ()
genericRnf = grnf_ . from
{-# INLINE genericRnf #-}

-- | Hidden internal type-class
--
-- __NOTE__: the 'V1' instance is not provided for 'GNFData' in order to
-- trigger a compile-time error; see 'GNFDataV1' which defers this to
-- a runtime error.
class GNFData f where
    grnf_ :: f a -> ()

instance GNFData U1 where
    grnf_ U1 = ()

instance NFData a => GNFData (K1 i a) where
    grnf_ = rnf . unK1
    {-# INLINEABLE grnf_ #-}

instance GNFData a => GNFData (M1 i c a) where
    grnf_ = grnf_ . unM1
    {-# INLINEABLE grnf_ #-}

instance (GNFData a, GNFData b) => GNFData (a :*: b) where
    grnf_ (x :*: y) = grnf_ x `seq` grnf_ y
    {-# INLINEABLE grnf_ #-}

instance (GNFData a, GNFData b) => GNFData (a :+: b) where
    grnf_ (L1 x) = grnf_ x
    grnf_ (R1 x) = grnf_ x
    {-# INLINEABLE grnf_ #-}

-- | Variant of 'genericRnf' which supports derivation for uninhabited types.
--
-- For instance, the type
--
-- > data TagFoo deriving Generic
--
-- would cause a compile-time error with 'genericRnf', but with
-- 'genericRnfV1' the error is deferred to run-time:
--
-- > Prelude> genericRnf (undefined :: TagFoo)
-- >
-- > <interactive>:1:1:
-- >     No instance for (GNFData V1) arising from a use of `genericRnf'
-- >     Possible fix: add an instance declaration for (GNFData V1)
-- >     In the expression: genericRnf (undefined :: TagFoo)
-- >     In an equation for `it': it = genericRnf (undefined :: TagFoo)
-- >
-- > Prelude> genericRnfV1 (undefined :: TagFoo)
-- > *** Exception: Control.DeepSeq.Generics.genericRnfV1: uninhabited type
--
-- 'genericRnfV1' corresponds to @deepseq-1.4.0.0@'s default @rnf@
-- method implementation.
--
-- __NOTE__: The 'GNFDataV1' type-class showing up in the type-signature is
--           used internally and not exported.
--
-- @since 0.1.1.0
genericRnfV1 :: (Generic a, GNFDataV1 (Rep a)) => a -> ()
genericRnfV1 = grnfV1_ . from
{-# INLINE genericRnfV1 #-}

-- | Variant of 'GNFData' supporting 'V1'
class GNFDataV1 f where
    grnfV1_ :: f a -> ()

instance GNFDataV1 V1 where
    grnfV1_ = error "Control.DeepSeq.Generics.genericRnfV1: uninhabited type"

instance GNFDataV1 U1 where
    grnfV1_ U1 = ()

instance NFData a => GNFDataV1 (K1 i a) where
    grnfV1_ = rnf . unK1
    {-# INLINEABLE grnfV1_ #-}

instance GNFDataV1 a => GNFDataV1 (M1 i c a) where
    grnfV1_ = grnfV1_ . unM1
    {-# INLINEABLE grnfV1_ #-}

instance (GNFDataV1 a, GNFDataV1 b) => GNFDataV1 (a :*: b) where
    grnfV1_ (x :*: y) = grnfV1_ x `seq` grnfV1_ y
    {-# INLINEABLE grnfV1_ #-}

instance (GNFDataV1 a, GNFDataV1 b) => GNFDataV1 (a :+: b) where
    grnfV1_ (L1 x) = grnfV1_ x
    grnfV1_ (R1 x) = grnfV1_ x
    {-# INLINEABLE grnfV1_ #-}