{-# LANGUAGE CPP #-}{-# LANGUAGE DataKinds #-}{-# LANGUAGE DeriveFunctor #-}{-# LANGUAGE DeriveGeneric #-}{-# LANGUAGE EmptyDataDeriving #-}{-# LANGUAGE FlexibleContexts #-}{-# LANGUAGE FlexibleInstances #-}{-# LANGUAGE GADTs #-}{-# LANGUAGE GeneralizedNewtypeDeriving #-}{-# LANGUAGE KindSignatures #-}{-# LANGUAGE MagicHash #-}{-# LANGUAGE NoImplicitPrelude #-}{-# LANGUAGE PolyKinds #-}{-# LANGUAGE ScopedTypeVariables #-}{-# LANGUAGE StandaloneDeriving #-}{-# LANGUAGE Trustworthy #-}{-# LANGUAGE TypeFamilies #-}{-# LANGUAGE TypeOperators #-}{-# LANGUAGE TypeSynonymInstances #-}{-# LANGUAGE UndecidableInstances #-}------------------------------------------------------------------------------- |-- Module : GHC.Generics-- Copyright : (c) Universiteit Utrecht 2010-2011, University of Oxford 2012-2014-- License : see libraries/base/LICENSE---- Maintainer : libraries@haskell.org-- Stability : internal-- Portability : non-portable---- @since 4.6.0.0---- If you're using @GHC.Generics@, you should consider using the-- <http://hackage.haskell.org/package/generic-deriving> package, which-- contains many useful generic functions.moduleGHC.Generics(-- * Introduction---- |---- Datatype-generic functions are based on the idea of converting values of-- a datatype @T@ into corresponding values of a (nearly) isomorphic type @'Rep' T@.-- The type @'Rep' T@ is-- built from a limited set of type constructors, all provided by this module. A-- datatype-generic function is then an overloaded function with instances-- for most of these type constructors, together with a wrapper that performs-- the mapping between @T@ and @'Rep' T@. By using this technique, we merely need-- a few generic instances in order to implement functionality that works for any-- representable type.---- Representable types are collected in the 'Generic' class, which defines the-- associated type 'Rep' as well as conversion functions 'from' and 'to'.-- Typically, you will not define 'Generic' instances by hand, but have the compiler-- derive them for you.-- ** Representing datatypes---- |---- The key to defining your own datatype-generic functions is to understand how to-- represent datatypes using the given set of type constructors.---- Let us look at an example first:---- @-- data Tree a = Leaf a | Node (Tree a) (Tree a)-- deriving 'Generic'-- @---- The above declaration (which requires the language pragma @DeriveGeneric@)-- causes the following representation to be generated:---- @-- instance 'Generic' (Tree a) where-- type 'Rep' (Tree a) =-- 'D1' ('MetaData \"Tree\" \"Main\" \"package-name\" 'False)-- ('C1' ('MetaCons \"Leaf\" 'PrefixI 'False)-- ('S1' ('MetaSel 'Nothing-- 'NoSourceUnpackedness-- 'NoSourceStrictness-- 'DecidedLazy)-- ('Rec0' a))-- ':+:'-- 'C1' ('MetaCons \"Node\" 'PrefixI 'False)-- ('S1' ('MetaSel 'Nothing-- 'NoSourceUnpackedness-- 'NoSourceStrictness-- 'DecidedLazy)-- ('Rec0' (Tree a))-- ':*:'-- 'S1' ('MetaSel 'Nothing-- 'NoSourceUnpackedness-- 'NoSourceStrictness-- 'DecidedLazy)-- ('Rec0' (Tree a))))-- ...-- @---- /Hint:/ You can obtain information about the code being generated from GHC by passing-- the @-ddump-deriv@ flag. In GHCi, you can expand a type family such as 'Rep' using-- the @:kind!@ command.---- This is a lot of information! However, most of it is actually merely meta-information-- that makes names of datatypes and constructors and more available on the type level.---- Here is a reduced representation for @Tree@ with nearly all meta-information removed,-- for now keeping only the most essential aspects:---- @-- instance 'Generic' (Tree a) where-- type 'Rep' (Tree a) =-- 'Rec0' a-- ':+:'-- ('Rec0' (Tree a) ':*:' 'Rec0' (Tree a))-- @---- The @Tree@ datatype has two constructors. The representation of individual constructors-- is combined using the binary type constructor ':+:'.---- The first constructor consists of a single field, which is the parameter @a@. This is-- represented as @'Rec0' a@.---- The second constructor consists of two fields. Each is a recursive field of type @Tree a@,-- represented as @'Rec0' (Tree a)@. Representations of individual fields are combined using-- the binary type constructor ':*:'.---- Now let us explain the additional tags being used in the complete representation:---- * The @'S1' ('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness-- 'DecidedLazy)@ tag indicates several things. The @'Nothing@ indicates-- that there is no record field selector associated with this field of-- the constructor (if there were, it would have been marked @'Just-- \"recordName\"@ instead). The other types contain meta-information on-- the field's strictness:---- * There is no @{\-\# UNPACK \#-\}@ or @{\-\# NOUNPACK \#-\}@ annotation-- in the source, so it is tagged with @'NoSourceUnpackedness@.---- * There is no strictness (@!@) or laziness (@~@) annotation in the-- source, so it is tagged with @'NoSourceStrictness@.---- * The compiler infers that the field is lazy, so it is tagged with-- @'DecidedLazy@. Bear in mind that what the compiler decides may be-- quite different from what is written in the source. See-- 'DecidedStrictness' for a more detailed explanation.---- The @'MetaSel@ type is also an instance of the type class 'Selector',-- which can be used to obtain information about the field at the value-- level.---- * The @'C1' ('MetaCons \"Leaf\" 'PrefixI 'False)@ and-- @'C1' ('MetaCons \"Node\" 'PrefixI 'False)@ invocations indicate that the enclosed part is-- the representation of the first and second constructor of datatype @Tree@, respectively.-- Here, the meta-information regarding constructor names, fixity and whether-- it has named fields or not is encoded at the type level. The @'MetaCons@-- type is also an instance of the type class 'Constructor'. This type class can be used-- to obtain information about the constructor at the value level.---- * The @'D1' ('MetaData \"Tree\" \"Main\" \"package-name\" 'False)@ tag-- indicates that the enclosed part is the representation of the-- datatype @Tree@. Again, the meta-information is encoded at the type level.-- The @'MetaData@ type is an instance of class 'Datatype', which-- can be used to obtain the name of a datatype, the module it has been-- defined in, the package it is located under, and whether it has been-- defined using @data@ or @newtype@ at the value level.-- ** Derived and fundamental representation types---- |---- There are many datatype-generic functions that do not distinguish between positions that-- are parameters or positions that are recursive calls. There are also many datatype-generic-- functions that do not care about the names of datatypes and constructors at all. To keep-- the number of cases to consider in generic functions in such a situation to a minimum,-- it turns out that many of the type constructors introduced above are actually synonyms,-- defining them to be variants of a smaller set of constructors.-- *** Individual fields of constructors: 'K1'---- |---- The type constructor 'Rec0' is a variant of 'K1':---- @-- type 'Rec0' = 'K1' 'R'-- @---- Here, 'R' is a type-level proxy that does not have any associated values.---- There used to be another variant of 'K1' (namely @Par0@), but it has since-- been deprecated.-- *** Meta information: 'M1'---- |---- The type constructors 'S1', 'C1' and 'D1' are all variants of 'M1':---- @-- type 'S1' = 'M1' 'S'-- type 'C1' = 'M1' 'C'-- type 'D1' = 'M1' 'D'-- @---- The types 'S', 'C' and 'D' are once again type-level proxies, just used to create-- several variants of 'M1'.-- *** Additional generic representation type constructors---- |---- Next to 'K1', 'M1', ':+:' and ':*:' there are a few more type constructors that occur-- in the representations of other datatypes.-- **** Empty datatypes: 'V1'---- |---- For empty datatypes, 'V1' is used as a representation. For example,---- @-- data Empty deriving 'Generic'-- @---- yields---- @-- instance 'Generic' Empty where-- type 'Rep' Empty =-- 'D1' ('MetaData \"Empty\" \"Main\" \"package-name\" 'False) 'V1'-- @-- **** Constructors without fields: 'U1'---- |---- If a constructor has no arguments, then 'U1' is used as its representation. For example-- the representation of 'Bool' is---- @-- instance 'Generic' Bool where-- type 'Rep' Bool =-- 'D1' ('MetaData \"Bool\" \"Data.Bool\" \"package-name\" 'False)-- ('C1' ('MetaCons \"False\" 'PrefixI 'False) 'U1' ':+:' 'C1' ('MetaCons \"True\" 'PrefixI 'False) 'U1')-- @-- *** Representation of types with many constructors or many fields---- |---- As ':+:' and ':*:' are just binary operators, one might ask what happens if the-- datatype has more than two constructors, or a constructor with more than two-- fields. The answer is simple: the operators are used several times, to combine-- all the constructors and fields as needed. However, users /should not rely on-- a specific nesting strategy/ for ':+:' and ':*:' being used. The compiler is-- free to choose any nesting it prefers. (In practice, the current implementation-- tries to produce a more-or-less balanced nesting, so that the traversal of-- the structure of the datatype from the root to a particular component can be-- performed in logarithmic rather than linear time.)-- ** Defining datatype-generic functions---- |---- A datatype-generic function comprises two parts:---- 1. /Generic instances/ for the function, implementing it for most of the representation-- type constructors introduced above.---- 2. A /wrapper/ that for any datatype that is in `Generic`, performs the conversion-- between the original value and its `Rep`-based representation and then invokes the-- generic instances.---- As an example, let us look at a function @encode@ that produces a naive, but lossless-- bit encoding of values of various datatypes. So we are aiming to define a function---- @-- encode :: 'Generic' a => a -> [Bool]-- @---- where we use 'Bool' as our datatype for bits.---- For part 1, we define a class @Encode'@. Perhaps surprisingly, this class is parameterized-- over a type constructor @f@ of kind @* -> *@. This is a technicality: all the representation-- type constructors operate with kind @* -> *@ as base kind. But the type argument is never-- being used. This may be changed at some point in the future. The class has a single method,-- and we use the type we want our final function to have, but we replace the occurrences of-- the generic type argument @a@ with @f p@ (where the @p@ is any argument; it will not be used).---- > class Encode' f where-- > encode' :: f p -> [Bool]---- With the goal in mind to make @encode@ work on @Tree@ and other datatypes, we now define-- instances for the representation type constructors 'V1', 'U1', ':+:', ':*:', 'K1', and 'M1'.-- *** Definition of the generic representation types---- |---- In order to be able to do this, we need to know the actual definitions of these types:---- @-- data 'V1' p -- lifted version of Empty-- data 'U1' p = 'U1' -- lifted version of ()-- data (':+:') f g p = 'L1' (f p) | 'R1' (g p) -- lifted version of 'Either'-- data (':*:') f g p = (f p) ':*:' (g p) -- lifted version of (,)-- newtype 'K1' i c p = 'K1' { 'unK1' :: c } -- a container for a c-- newtype 'M1' i t f p = 'M1' { 'unM1' :: f p } -- a wrapper-- @---- So, 'U1' is just the unit type, ':+:' is just a binary choice like 'Either',-- ':*:' is a binary pair like the pair constructor @(,)@, and 'K1' is a value-- of a specific type @c@, and 'M1' wraps a value of the generic type argument,-- which in the lifted world is an @f p@ (where we do not care about @p@).-- *** Generic instances---- |---- The instance for 'V1' is slightly awkward (but also rarely used):---- @-- instance Encode' 'V1' where-- encode' x = undefined-- @---- There are no values of type @V1 p@ to pass (except undefined), so this is-- actually impossible. One can ask why it is useful to define an instance for-- 'V1' at all in this case? Well, an empty type can be used as an argument to-- a non-empty type, and you might still want to encode the resulting type.-- As a somewhat contrived example, consider @[Empty]@, which is not an empty-- type, but contains just the empty list. The 'V1' instance ensures that we-- can call the generic function on such types.---- There is exactly one value of type 'U1', so encoding it requires no-- knowledge, and we can use zero bits:---- @-- instance Encode' 'U1' where-- encode' 'U1' = []-- @---- In the case for ':+:', we produce 'False' or 'True' depending on whether-- the constructor of the value provided is located on the left or on the right:---- @-- instance (Encode' f, Encode' g) => Encode' (f ':+:' g) where-- encode' ('L1' x) = False : encode' x-- encode' ('R1' x) = True : encode' x-- @---- (Note that this encoding strategy may not be reliable across different-- versions of GHC. Recall that the compiler is free to choose any nesting-- of ':+:' it chooses, so if GHC chooses @(a ':+:' b) ':+:' c@, then the-- encoding for @a@ would be @[False, False]@, @b@ would be @[False, True]@,-- and @c@ would be @[True]@. However, if GHC chooses @a ':+:' (b ':+:' c)@,-- then the encoding for @a@ would be @[False]@, @b@ would be @[True, False]@,-- and @c@ would be @[True, True]@.)---- In the case for ':*:', we append the encodings of the two subcomponents:---- @-- instance (Encode' f, Encode' g) => Encode' (f ':*:' g) where-- encode' (x ':*:' y) = encode' x ++ encode' y-- @---- The case for 'K1' is rather interesting. Here, we call the final function-- @encode@ that we yet have to define, recursively. We will use another type-- class @Encode@ for that function:---- @-- instance (Encode c) => Encode' ('K1' i c) where-- encode' ('K1' x) = encode x-- @---- Note how we can define a uniform instance for 'M1', because we completely-- disregard all meta-information:---- @-- instance (Encode' f) => Encode' ('M1' i t f) where-- encode' ('M1' x) = encode' x-- @---- Unlike in 'K1', the instance for 'M1' refers to @encode'@, not @encode@.-- *** The wrapper and generic default---- |---- We now define class @Encode@ for the actual @encode@ function:---- @-- class Encode a where-- encode :: a -> [Bool]-- default encode :: (Generic a, Encode' (Rep a)) => a -> [Bool]-- encode x = encode' ('from' x)-- @---- The incoming @x@ is converted using 'from', then we dispatch to the-- generic instances using @encode'@. We use this as a default definition-- for @encode@. We need the @default encode@ signature because ordinary-- Haskell default methods must not introduce additional class constraints,-- but our generic default does.---- Defining a particular instance is now as simple as saying---- @-- instance (Encode a) => Encode (Tree a)-- @--
#if 0
-- /TODO:/ Add usage example?--
#endif
-- The generic default is being used. In the future, it will hopefully be-- possible to use @deriving Encode@ as well, but GHC does not yet support-- that syntax for this situation.---- Having @Encode@ as a class has the advantage that we can define-- non-generic special cases, which is particularly useful for abstract-- datatypes that have no structural representation. For example, given-- a suitable integer encoding function @encodeInt@, we can define---- @-- instance Encode Int where-- encode = encodeInt-- @-- *** Omitting generic instances---- |---- It is not always required to provide instances for all the generic-- representation types, but omitting instances restricts the set of-- datatypes the functions will work for:---- * If no ':+:' instance is given, the function may still work for-- empty datatypes or datatypes that have a single constructor,-- but will fail on datatypes with more than one constructor.---- * If no ':*:' instance is given, the function may still work for-- datatypes where each constructor has just zero or one field,-- in particular for enumeration types.---- * If no 'K1' instance is given, the function may still work for-- enumeration types, where no constructor has any fields.---- * If no 'V1' instance is given, the function may still work for-- any datatype that is not empty.---- * If no 'U1' instance is given, the function may still work for-- any datatype where each constructor has at least one field.---- An 'M1' instance is always required (but it can just ignore the-- meta-information, as is the case for @encode@ above).
#if 0
-- *** Using meta-information---- |---- TODO
#endif
-- ** Generic constructor classes---- |---- Datatype-generic functions as defined above work for a large class-- of datatypes, including parameterized datatypes. (We have used @Tree@-- as our example above, which is of kind @* -> *@.) However, the-- 'Generic' class ranges over types of kind @*@, and therefore, the-- resulting generic functions (such as @encode@) must be parameterized-- by a generic type argument of kind @*@.---- What if we want to define generic classes that range over type-- constructors (such as 'Data.Functor.Functor',-- 'Data.Traversable.Traversable', or 'Data.Foldable.Foldable')?-- *** The 'Generic1' class---- |---- Like 'Generic', there is a class 'Generic1' that defines a-- representation 'Rep1' and conversion functions 'from1' and 'to1',-- only that 'Generic1' ranges over types of kind @* -> *@. (More generally,-- it can range over types of kind @k -> *@, for any kind @k@, if the-- @PolyKinds@ extension is enabled. More on this later.)-- The 'Generic1' class is also derivable.---- The representation 'Rep1' is ever so slightly different from 'Rep'.-- Let us look at @Tree@ as an example again:---- @-- data Tree a = Leaf a | Node (Tree a) (Tree a)-- deriving 'Generic1'-- @---- The above declaration causes the following representation to be generated:---- @-- instance 'Generic1' Tree where-- type 'Rep1' Tree =-- 'D1' ('MetaData \"Tree\" \"Main\" \"package-name\" 'False)-- ('C1' ('MetaCons \"Leaf\" 'PrefixI 'False)-- ('S1' ('MetaSel 'Nothing-- 'NoSourceUnpackedness-- 'NoSourceStrictness-- 'DecidedLazy)-- 'Par1')-- ':+:'-- 'C1' ('MetaCons \"Node\" 'PrefixI 'False)-- ('S1' ('MetaSel 'Nothing-- 'NoSourceUnpackedness-- 'NoSourceStrictness-- 'DecidedLazy)-- ('Rec1' Tree)-- ':*:'-- 'S1' ('MetaSel 'Nothing-- 'NoSourceUnpackedness-- 'NoSourceStrictness-- 'DecidedLazy)-- ('Rec1' Tree)))-- ...-- @---- The representation reuses 'D1', 'C1', 'S1' (and thereby 'M1') as well-- as ':+:' and ':*:' from 'Rep'. (This reusability is the reason that we-- carry around the dummy type argument for kind-@*@-types, but there are-- already enough different names involved without duplicating each of-- these.)---- What's different is that we now use 'Par1' to refer to the parameter-- (and that parameter, which used to be @a@), is not mentioned explicitly-- by name anywhere; and we use 'Rec1' to refer to a recursive use of @Tree a@.-- *** Representation of @* -> *@ types---- |---- Unlike 'Rec0', the 'Par1' and 'Rec1' type constructors do not-- map to 'K1'. They are defined directly, as follows:---- @-- newtype 'Par1' p = 'Par1' { 'unPar1' :: p } -- gives access to parameter p-- newtype 'Rec1' f p = 'Rec1' { 'unRec1' :: f p } -- a wrapper-- @---- In 'Par1', the parameter @p@ is used for the first time, whereas 'Rec1' simply-- wraps an application of @f@ to @p@.---- Note that 'K1' (in the guise of 'Rec0') can still occur in a 'Rep1' representation,-- namely when the datatype has a field that does not mention the parameter.---- The declaration---- @-- data WithInt a = WithInt Int a-- deriving 'Generic1'-- @---- yields---- @-- instance 'Generic1' WithInt where-- type 'Rep1' WithInt =-- 'D1' ('MetaData \"WithInt\" \"Main\" \"package-name\" 'False)-- ('C1' ('MetaCons \"WithInt\" 'PrefixI 'False)-- ('S1' ('MetaSel 'Nothing-- 'NoSourceUnpackedness-- 'NoSourceStrictness-- 'DecidedLazy)-- ('Rec0' Int)-- ':*:'-- 'S1' ('MetaSel 'Nothing-- 'NoSourceUnpackedness-- 'NoSourceStrictness-- 'DecidedLazy)-- 'Par1'))-- @---- If the parameter @a@ appears underneath a composition of other type constructors,-- then the representation involves composition, too:---- @-- data Rose a = Fork a [Rose a]-- @---- yields---- @-- instance 'Generic1' Rose where-- type 'Rep1' Rose =-- 'D1' ('MetaData \"Rose\" \"Main\" \"package-name\" 'False)-- ('C1' ('MetaCons \"Fork\" 'PrefixI 'False)-- ('S1' ('MetaSel 'Nothing-- 'NoSourceUnpackedness-- 'NoSourceStrictness-- 'DecidedLazy)-- 'Par1'-- ':*:'-- 'S1' ('MetaSel 'Nothing-- 'NoSourceUnpackedness-- 'NoSourceStrictness-- 'DecidedLazy)-- ([] ':.:' 'Rec1' Rose)))-- @---- where---- @-- newtype (':.:') f g p = 'Comp1' { 'unComp1' :: f (g p) }-- @-- *** Representation of @k -> *@ types---- |---- The 'Generic1' class can be generalized to range over types of kind-- @k -> *@, for any kind @k@. To do so, derive a 'Generic1' instance with the-- @PolyKinds@ extension enabled. For example, the declaration---- @-- data Proxy (a :: k) = Proxy deriving 'Generic1'-- @---- yields a slightly different instance depending on whether @PolyKinds@ is-- enabled. If compiled without @PolyKinds@, then @'Rep1' Proxy :: * -> *@, but-- if compiled with @PolyKinds@, then @'Rep1' Proxy :: k -> *@.-- *** 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 an unlifted kind, and 'Rec0' expects a type of-- kind @*@.---- 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' ('MetaData \"IntHash\" \"Main\" \"package-name\" 'False)-- ('C1' ('MetaCons \"IntHash\" 'PrefixI 'False)-- ('S1' ('MetaSel 'Nothing-- 'NoSourceUnpackedness-- 'NoSourceStrictness-- 'DecidedLazy)-- '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---- |---- /TODO/---- /TODO:/ Also clear up confusion about 'Rec0' and 'Rec1' not really indicating recursion.--
#endif
------------------------------------------------------------------------------- * Generic representation typesV1 ,U1 (..),Par1 (..),Rec1 (..),K1 (..),M1 (..),(:+:) (..),(:*:) (..),(:.:) (..)-- ** Unboxed representation types,URec (..),typeUAddr ,typeUChar ,typeUDouble ,typeUFloat ,typeUInt ,typeUWord -- ** Synonyms for convenience,Rec0 ,R ,D1 ,C1 ,S1 ,D ,C ,S -- * Meta-information,Datatype (..),Constructor (..),Selector (..),Fixity (..),FixityI (..),Associativity (..),prec ,SourceUnpackedness (..),SourceStrictness (..),DecidedStrictness (..),Meta (..)-- * Generic type classes,Generic (..),Generic1 (..))where-- We use some base typesimportData.Either (Either (..))importData.Maybe (Maybe (..),fromMaybe )importData.Ord (Down (..))importGHC.Integer(Integer,integerToInt)importGHC.Prim(Addr#,Char#,Double#,Float#,Int#,Word#)importGHC.Ptr (Ptr )importGHC.Types-- Needed for instancesimportGHC.Ix (Ix )importGHC.Base (Alternative (..),Applicative (..),Functor (..),Monad (..),MonadPlus (..),NonEmpty (..),String ,coerce,Semigroup (..),Monoid (..))importGHC.Classes(Eq(..),Ord(..))importGHC.Enum (Bounded ,Enum )importGHC.Read (Read (..))importGHC.Show (Show (..),showString )-- Needed for metadataimportData.Proxy (Proxy (..))importGHC.TypeLits (KnownSymbol ,KnownNat ,symbolVal ,natVal )---------------------------------------------------------------------------------- Representation types---------------------------------------------------------------------------------- | Void: used for datatypes without constructorsdataV1 (p ::k )deriving(Eq-- ^ @since 4.9.0.0,Ord-- ^ @since 4.9.0.0,Read -- ^ @since 4.9.0.0,Show -- ^ @since 4.9.0.0,Functor -- ^ @since 4.9.0.0,Generic -- ^ @since 4.9.0.0,Generic1 -- ^ @since 4.9.0.0)-- | @since 4.12.0.0instanceSemigroup (V1 p )whereV1 p
v <> :: V1 p -> V1 p -> V1 p
<> V1 p
_=V1 p
v -- | Unit: used for constructors without argumentsdataU1 (p ::k )=U1 deriving(Generic -- ^ @since 4.7.0.0,Generic1 -- ^ @since 4.9.0.0)-- | @since 4.9.0.0instanceEq(U1 p )whereU1 p
_== :: U1 p -> U1 p -> Bool
==U1 p
_=Bool
True-- | @since 4.7.0.0instanceOrd(U1 p )wherecompare :: U1 p -> U1 p -> Ordering
compareU1 p
_U1 p
_=Ordering
EQ-- | @since 4.9.0.0derivinginstanceRead (U1 p )-- | @since 4.9.0.0instanceShow (U1 p )whereshowsPrec :: Int -> U1 p -> ShowS
showsPrec Int
_U1 p
_=String -> ShowS
showString String
"U1"-- | @since 4.9.0.0instanceFunctor U1 wherefmap :: (a -> b) -> U1 a -> U1 b
fmap a -> b
_U1 a
_=U1 b
forall k (p :: k). U1 p
U1 -- | @since 4.9.0.0instanceApplicative U1 wherepure :: a -> U1 a
pure a
_=U1 a
forall k (p :: k). U1 p
U1 U1 (a -> b)
_<*> :: U1 (a -> b) -> U1 a -> U1 b
<*> U1 a
_=U1 b
forall k (p :: k). U1 p
U1 liftA2 :: (a -> b -> c) -> U1 a -> U1 b -> U1 c
liftA2 a -> b -> c
_U1 a
_U1 b
_=U1 c
forall k (p :: k). U1 p
U1 -- | @since 4.9.0.0instanceAlternative U1 whereempty :: U1 a
empty =U1 a
forall k (p :: k). U1 p
U1 U1 a
_<|> :: U1 a -> U1 a -> U1 a
<|> U1 a
_=U1 a
forall k (p :: k). U1 p
U1 -- | @since 4.9.0.0instanceMonad U1 whereU1 a
_>>= :: U1 a -> (a -> U1 b) -> U1 b
>>= a -> U1 b
_=U1 b
forall k (p :: k). U1 p
U1 -- | @since 4.9.0.0instanceMonadPlus U1 -- | @since 4.12.0.0instanceSemigroup (U1 p )whereU1 p
_<> :: U1 p -> U1 p -> U1 p
<> U1 p
_=U1 p
forall k (p :: k). U1 p
U1 -- | @since 4.12.0.0instanceMonoid (U1 p )wheremempty :: U1 p
mempty =U1 p
forall k (p :: k). U1 p
U1 -- | Used for marking occurrences of the parameternewtypePar1 p =Par1 {Par1 p -> p
unPar1 ::p }deriving(Eq-- ^ @since 4.7.0.0,Ord-- ^ @since 4.7.0.0,Read -- ^ @since 4.7.0.0,Show -- ^ @since 4.7.0.0,Functor -- ^ @since 4.9.0.0,Generic -- ^ @since 4.7.0.0,Generic1 -- ^ @since 4.9.0.0)-- | @since 4.9.0.0instanceApplicative Par1 wherepure :: a -> Par1 a
pure =a -> Par1 a
forall a. a -> Par1 a
Par1 <*> :: Par1 (a -> b) -> Par1 a -> Par1 b
(<*>) =Par1 (a -> b) -> Par1 a -> Par1 b
coerceliftA2 :: (a -> b -> c) -> Par1 a -> Par1 b -> Par1 c
liftA2 =(a -> b -> c) -> Par1 a -> Par1 b -> Par1 c
coerce-- | @since 4.9.0.0instanceMonad Par1 wherePar1 a
x >>= :: Par1 a -> (a -> Par1 b) -> Par1 b
>>= a -> Par1 b
f =a -> Par1 b
f a
x -- | @since 4.12.0.0derivinginstanceSemigroup p =>Semigroup (Par1 p )-- | @since 4.12.0.0derivinginstanceMonoid p =>Monoid (Par1 p )-- | Recursive calls of kind @* -> *@ (or kind @k -> *@, when @PolyKinds@-- is enabled)newtypeRec1 (f ::k ->Type)(p ::k )=Rec1 {Rec1 f p -> f p
unRec1 ::f p }deriving(Eq-- ^ @since 4.7.0.0,Ord-- ^ @since 4.7.0.0,Read -- ^ @since 4.7.0.0,Show -- ^ @since 4.7.0.0,Functor -- ^ @since 4.9.0.0,Generic -- ^ @since 4.7.0.0,Generic1 -- ^ @since 4.9.0.0)-- | @since 4.9.0.0derivinginstanceApplicative f =>Applicative (Rec1 f )-- | @since 4.9.0.0derivinginstanceAlternative f =>Alternative (Rec1 f )-- | @since 4.9.0.0instanceMonad f =>Monad (Rec1 f )whereRec1 f a
x >>= :: Rec1 f a -> (a -> Rec1 f b) -> Rec1 f b
>>= a -> Rec1 f b
f =f b -> Rec1 f b
forall k (f :: k -> *) (p :: k). f p -> Rec1 f p
Rec1 (f a
x f a -> (a -> f b) -> f b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
a ->Rec1 f b -> f b
forall k (f :: k -> *) (p :: k). Rec1 f p -> f p
unRec1 (a -> Rec1 f b
f a
a ))-- | @since 4.9.0.0derivinginstanceMonadPlus f =>MonadPlus (Rec1 f )-- | @since 4.12.0.0derivinginstanceSemigroup (f p )=>Semigroup (Rec1 f p )-- | @since 4.12.0.0derivinginstanceMonoid (f p )=>Monoid (Rec1 f p )-- | Constants, additional parameters and recursion of kind @*@newtypeK1 (i ::Type)c (p ::k )=K1 {K1 i c p -> c
unK1 ::c }deriving(Eq-- ^ @since 4.7.0.0,Ord-- ^ @since 4.7.0.0,Read -- ^ @since 4.7.0.0,Show -- ^ @since 4.7.0.0,Functor -- ^ @since 4.9.0.0,Generic -- ^ @since 4.7.0.0,Generic1 -- ^ @since 4.9.0.0)-- | @since 4.12.0.0instanceMonoid c =>Applicative (K1 i c )wherepure :: a -> K1 i c a
pure a
_=c -> K1 i c a
forall k i c (p :: k). c -> K1 i c p
K1 c
forall a. Monoid a => a
mempty liftA2 :: (a -> b -> c) -> K1 i c a -> K1 i c b -> K1 i c c
liftA2 =\a -> b -> c
_->(c -> c -> c) -> K1 i c a -> K1 i c b -> K1 i c c
coerce(c -> c -> c
forall a. Monoid a => a -> a -> a
mappend ::c ->c ->c )<*> :: K1 i c (a -> b) -> K1 i c a -> K1 i c b
(<*>) =(c -> c -> c) -> K1 i c (a -> b) -> K1 i c a -> K1 i c b
coerce(c -> c -> c
forall a. Monoid a => a -> a -> a
mappend ::c ->c ->c )-- | @since 4.12.0.0derivinginstanceSemigroup c =>Semigroup (K1 i c p )-- | @since 4.12.0.0derivinginstanceMonoid c =>Monoid (K1 i c p )-- | @since 4.9.0.0derivinginstanceApplicative f =>Applicative (M1 i c f )-- | @since 4.9.0.0derivinginstanceAlternative f =>Alternative (M1 i c f )-- | @since 4.9.0.0derivinginstanceMonad f =>Monad (M1 i c f )-- | @since 4.9.0.0derivinginstanceMonadPlus f =>MonadPlus (M1 i c f )-- | @since 4.12.0.0derivinginstanceSemigroup (f p )=>Semigroup (M1 i c f p )-- | @since 4.12.0.0derivinginstanceMonoid (f p )=>Monoid (M1 i c f p )-- | Meta-information (constructor names, etc.)newtypeM1 (i ::Type)(c ::Meta )(f ::k ->Type)(p ::k )=M1 {M1 i c f p -> f p
unM1 ::f p }deriving(Eq-- ^ @since 4.7.0.0,Ord-- ^ @since 4.7.0.0,Read -- ^ @since 4.7.0.0,Show -- ^ @since 4.7.0.0,Functor -- ^ @since 4.9.0.0,Generic -- ^ @since 4.7.0.0,Generic1 -- ^ @since 4.9.0.0)-- | Sums: encode choice between constructorsinfixr5:+: data(:+:) (f ::k ->Type)(g ::k ->Type)(p ::k )=L1 (f p )|R1 (g p )deriving(Eq-- ^ @since 4.7.0.0,Ord-- ^ @since 4.7.0.0,Read -- ^ @since 4.7.0.0,Show -- ^ @since 4.7.0.0,Functor -- ^ @since 4.9.0.0,Generic -- ^ @since 4.7.0.0,Generic1 -- ^ @since 4.9.0.0)-- | Products: encode multiple arguments to constructorsinfixr6:*: data(:*:) (f ::k ->Type)(g ::k ->Type)(p ::k )=f p :*: g p deriving(Eq-- ^ @since 4.7.0.0,Ord-- ^ @since 4.7.0.0,Read -- ^ @since 4.7.0.0,Show -- ^ @since 4.7.0.0,Functor -- ^ @since 4.9.0.0,Generic -- ^ @since 4.7.0.0,Generic1 -- ^ @since 4.9.0.0)-- | @since 4.9.0.0instance(Applicative f ,Applicative g )=>Applicative (f :*: g )wherepure :: a -> (:*:) f g a
pure a
a =a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
a f a -> g a -> (:*:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: a -> g a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
a (f (a -> b)
f :*: g (a -> b)
g )<*> :: (:*:) f g (a -> b) -> (:*:) f g a -> (:*:) f g b
<*> (f a
x :*: g a
y )=(f (a -> b)
f f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> f a
x )f b -> g b -> (:*:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: (g (a -> b)
g g (a -> b) -> g a -> g b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> g a
y )liftA2 :: (a -> b -> c) -> (:*:) f g a -> (:*:) f g b -> (:*:) f g c
liftA2 a -> b -> c
f (f a
a :*: g a
b )(f b
x :*: g b
y )=(a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> b -> c
f f a
a f b
x f c -> g c -> (:*:) f g c
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: (a -> b -> c) -> g a -> g b -> g c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> b -> c
f g a
b g b
y -- | @since 4.9.0.0instance(Alternative f ,Alternative g )=>Alternative (f :*: g )whereempty :: (:*:) f g a
empty =f a
forall (f :: * -> *) a. Alternative f => f a
empty f a -> g a -> (:*:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: g a
forall (f :: * -> *) a. Alternative f => f a
empty (f a
x1 :*: g a
y1 )<|> :: (:*:) f g a -> (:*:) f g a -> (:*:) f g a
<|> (f a
x2 :*: g a
y2 )=(f a
x1 f a -> f a -> f a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> f a
x2 )f a -> g a -> (:*:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: (g a
y1 g a -> g a -> g a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> g a
y2 )-- | @since 4.9.0.0instance(Monad f ,Monad g )=>Monad (f :*: g )where(f a
m :*: g a
n )>>= :: (:*:) f g a -> (a -> (:*:) f g b) -> (:*:) f g b
>>= a -> (:*:) f g b
f =(f a
m f a -> (a -> f b) -> f b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
a ->(:*:) f g b -> f b
forall k (f :: k -> *) (g :: k -> *) (p :: k). (:*:) f g p -> f p
fstP (a -> (:*:) f g b
f a
a ))f b -> g b -> (:*:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: (g a
n g a -> (a -> g b) -> g b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
a ->(:*:) f g b -> g b
forall k (f :: k -> *) (g :: k -> *) (p :: k). (:*:) f g p -> g p
sndP (a -> (:*:) f g b
f a
a ))wherefstP :: (:*:) f g p -> f p
fstP (f p
a :*: g p
_)=f p
a sndP :: (:*:) f g p -> g p
sndP (f p
_:*: g p
b )=g p
b -- | @since 4.9.0.0instance(MonadPlus f ,MonadPlus g )=>MonadPlus (f :*: g )-- | @since 4.12.0.0instance(Semigroup (f p ),Semigroup (g p ))=>Semigroup ((f :*: g )p )where(f p
x1 :*: g p
y1 )<> :: (:*:) f g p -> (:*:) f g p -> (:*:) f g p
<> (f p
x2 :*: g p
y2 )=(f p
x1 f p -> f p -> f p
forall a. Semigroup a => a -> a -> a
<> f p
x2 )f p -> g p -> (:*:) f g p
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: (g p
y1 g p -> g p -> g p
forall a. Semigroup a => a -> a -> a
<> g p
y2 )-- | @since 4.12.0.0instance(Monoid (f p ),Monoid (g p ))=>Monoid ((f :*: g )p )wheremempty :: (:*:) f g p
mempty =f p
forall a. Monoid a => a
mempty f p -> g p -> (:*:) f g p
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: g p
forall a. Monoid a => a
mempty -- | Composition of functorsinfixr7:.: newtype(:.:) (f ::k2 ->Type)(g ::k1 ->k2 )(p ::k1 )=Comp1 {(:.:) f g p -> f (g p)
unComp1 ::f (g p )}deriving(Eq-- ^ @since 4.7.0.0,Ord-- ^ @since 4.7.0.0,Read -- ^ @since 4.7.0.0,Show -- ^ @since 4.7.0.0,Functor -- ^ @since 4.9.0.0,Generic -- ^ @since 4.7.0.0,Generic1 -- ^ @since 4.9.0.0)-- | @since 4.9.0.0instance(Applicative f ,Applicative g )=>Applicative (f :.: g )wherepure :: a -> (:.:) f g a
pure a
x =f (g a) -> (:.:) f g a
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
f (g p) -> (:.:) f g p
Comp1 (g a -> f (g a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> g a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
x ))Comp1 f (g (a -> b))
f <*> :: (:.:) f g (a -> b) -> (:.:) f g a -> (:.:) f g b
<*> Comp1 f (g a)
x =f (g b) -> (:.:) f g b
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
f (g p) -> (:.:) f g p
Comp1 ((g (a -> b) -> g a -> g b) -> f (g (a -> b)) -> f (g a) -> f (g b)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 g (a -> b) -> g a -> g b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
(<*>) f (g (a -> b))
f f (g a)
x )liftA2 :: (a -> b -> c) -> (:.:) f g a -> (:.:) f g b -> (:.:) f g c
liftA2 a -> b -> c
f (Comp1 f (g a)
x )(Comp1 f (g b)
y )=f (g c) -> (:.:) f g c
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
f (g p) -> (:.:) f g p
Comp1 ((g a -> g b -> g c) -> f (g a) -> f (g b) -> f (g c)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 ((a -> b -> c) -> g a -> g b -> g c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> b -> c
f )f (g a)
x f (g b)
y )-- | @since 4.9.0.0instance(Alternative f ,Applicative g )=>Alternative (f :.: g )whereempty :: (:.:) f g a
empty =f (g a) -> (:.:) f g a
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
f (g p) -> (:.:) f g p
Comp1 f (g a)
forall (f :: * -> *) a. Alternative f => f a
empty <|> :: (:.:) f g a -> (:.:) f g a -> (:.:) f g a
(<|>) =(f (g a) -> f (g a) -> f (g a))
-> (:.:) f g a -> (:.:) f g a -> (:.:) f g a
coerce(f (g a) -> f (g a) -> f (g a)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>) ::f (g a )->f (g a )->f (g a ))::foralla .(f :.: g )a ->(f :.: g )a ->(f :.: g )a -- | @since 4.12.0.0derivinginstanceSemigroup (f (g p ))=>Semigroup ((f :.: g )p )-- | @since 4.12.0.0derivinginstanceMonoid (f (g p ))=>Monoid ((f :.: g )p )-- | Constants of unlifted kinds---- @since 4.9.0.0datafamilyURec (a ::Type)(p ::k )-- | Used for marking occurrences of 'Addr#'---- @since 4.9.0.0datainstanceURec (Ptr ())(p ::k )=UAddr {URec (Ptr ()) p -> Addr#
uAddr# ::Addr#}deriving(Eq-- ^ @since 4.9.0.0,Ord-- ^ @since 4.9.0.0,Functor -- ^ @since 4.9.0.0,Generic -- ^ @since 4.9.0.0,Generic1 -- ^ @since 4.9.0.0)-- | Used for marking occurrences of 'Char#'---- @since 4.9.0.0datainstanceURec Char(p ::k )=UChar {URec Char p -> Char#
uChar# ::Char#}deriving(Eq-- ^ @since 4.9.0.0,Ord-- ^ @since 4.9.0.0,Show -- ^ @since 4.9.0.0,Functor -- ^ @since 4.9.0.0,Generic -- ^ @since 4.9.0.0,Generic1 -- ^ @since 4.9.0.0)-- | Used for marking occurrences of 'Double#'---- @since 4.9.0.0datainstanceURec Double(p ::k )=UDouble {URec Double p -> Double#
uDouble# ::Double#}deriving(Eq-- ^ @since 4.9.0.0,Ord-- ^ @since 4.9.0.0,Show -- ^ @since 4.9.0.0,Functor -- ^ @since 4.9.0.0,Generic -- ^ @since 4.9.0.0,Generic1 -- ^ @since 4.9.0.0)-- | Used for marking occurrences of 'Float#'---- @since 4.9.0.0datainstanceURec Float(p ::k )=UFloat {URec Float p -> Float#
uFloat# ::Float#}deriving(URec Float p -> URec Float p -> Bool
(URec Float p -> URec Float p -> Bool)
-> (URec Float p -> URec Float p -> Bool) -> Eq (URec Float p)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (p :: k). URec Float p -> URec Float p -> Bool
/= :: URec Float p -> URec Float p -> Bool
$c/= :: forall k (p :: k). URec Float p -> URec Float p -> Bool
== :: URec Float p -> URec Float p -> Bool
$c== :: forall k (p :: k). URec Float p -> URec Float p -> Bool
Eq,Eq (URec Float p)
Eq (URec Float p)
-> (URec Float p -> URec Float p -> Ordering)
-> (URec Float p -> URec Float p -> Bool)
-> (URec Float p -> URec Float p -> Bool)
-> (URec Float p -> URec Float p -> Bool)
-> (URec Float p -> URec Float p -> Bool)
-> (URec Float p -> URec Float p -> URec Float p)
-> (URec Float p -> URec Float p -> URec Float p)
-> Ord (URec Float p)
URec Float p -> URec Float p -> Bool
URec Float p -> URec Float p -> Ordering
URec Float p -> URec Float p -> URec Float p
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall k (p :: k). Eq (URec Float p)
forall k (p :: k). URec Float p -> URec Float p -> Bool
forall k (p :: k). URec Float p -> URec Float p -> Ordering
forall k (p :: k). URec Float p -> URec Float p -> URec Float p
min :: URec Float p -> URec Float p -> URec Float p
$cmin :: forall k (p :: k). URec Float p -> URec Float p -> URec Float p
max :: URec Float p -> URec Float p -> URec Float p
$cmax :: forall k (p :: k). URec Float p -> URec Float p -> URec Float p
>= :: URec Float p -> URec Float p -> Bool
$c>= :: forall k (p :: k). URec Float p -> URec Float p -> Bool
> :: URec Float p -> URec Float p -> Bool
$c> :: forall k (p :: k). URec Float p -> URec Float p -> Bool
<= :: URec Float p -> URec Float p -> Bool
$c<= :: forall k (p :: k). URec Float p -> URec Float p -> Bool
< :: URec Float p -> URec Float p -> Bool
$c< :: forall k (p :: k). URec Float p -> URec Float p -> Bool
compare :: URec Float p -> URec Float p -> Ordering
$ccompare :: forall k (p :: k). URec Float p -> URec Float p -> Ordering
$cp1Ord :: forall k (p :: k). Eq (URec Float p)
Ord,Int -> URec Float p -> ShowS
[URec Float p] -> ShowS
URec Float p -> String
(Int -> URec Float p -> ShowS)
-> (URec Float p -> String)
-> ([URec Float p] -> ShowS)
-> Show (URec Float p)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall k (p :: k). Int -> URec Float p -> ShowS
forall k (p :: k). [URec Float p] -> ShowS
forall k (p :: k). URec Float p -> String
showList :: [URec Float p] -> ShowS
$cshowList :: forall k (p :: k). [URec Float p] -> ShowS
show :: URec Float p -> String
$cshow :: forall k (p :: k). URec Float p -> String
showsPrec :: Int -> URec Float p -> ShowS
$cshowsPrec :: forall k (p :: k). Int -> URec Float p -> ShowS
Show ,Functor -- ^ @since 4.9.0.0,(forall x. URec Float p -> Rep (URec Float p) x)
-> (forall x. Rep (URec Float p) x -> URec Float p)
-> Generic (URec Float p)
forall x. Rep (URec Float p) x -> URec Float p
forall x. URec Float p -> Rep (URec Float p) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall k (p :: k) x. Rep (URec Float p) x -> URec Float p
forall k (p :: k) x. URec Float p -> Rep (URec Float p) x
$cto :: forall k (p :: k) x. Rep (URec Float p) x -> URec Float p
$cfrom :: forall k (p :: k) x. URec Float p -> Rep (URec Float p) x
Generic ,Generic1 -- ^ @since 4.9.0.0)-- | Used for marking occurrences of 'Int#'---- @since 4.9.0.0datainstanceURec Int(p ::k )=UInt {URec Int p -> Int#
uInt# ::Int#}deriving(Eq-- ^ @since 4.9.0.0,Ord-- ^ @since 4.9.0.0,Show -- ^ @since 4.9.0.0,Functor -- ^ @since 4.9.0.0,Generic -- ^ @since 4.9.0.0,Generic1 -- ^ @since 4.9.0.0)-- | Used for marking occurrences of 'Word#'---- @since 4.9.0.0datainstanceURec Word(p ::k )=UWord {URec Word p -> Word#
uWord# ::Word#}deriving(Eq-- ^ @since 4.9.0.0,Ord-- ^ @since 4.9.0.0,Show -- ^ @since 4.9.0.0,Functor -- ^ @since 4.9.0.0,Generic -- ^ @since 4.9.0.0,Generic1 -- ^ @since 4.9.0.0)-- | Type synonym for @'URec' 'Addr#'@---- @since 4.9.0.0typeUAddr =URec (Ptr ())-- | Type synonym for @'URec' 'Char#'@---- @since 4.9.0.0typeUChar =URec Char-- | Type synonym for @'URec' 'Double#'@---- @since 4.9.0.0typeUDouble =URec Double-- | Type synonym for @'URec' 'Float#'@---- @since 4.9.0.0typeUFloat =URec Float-- | Type synonym for @'URec' 'Int#'@---- @since 4.9.0.0typeUInt =URec Int-- | Type synonym for @'URec' 'Word#'@---- @since 4.9.0.0typeUWord =URec Word-- | Tag for K1: recursion (of kind @Type@)dataR -- | Type synonym for encoding recursion (of kind @Type@)typeRec0 =K1 R -- | Tag for M1: datatypedataD -- | Tag for M1: constructordataC -- | Tag for M1: record selectordataS -- | Type synonym for encoding meta-information for datatypestypeD1 =M1 D -- | Type synonym for encoding meta-information for constructorstypeC1 =M1 C -- | Type synonym for encoding meta-information for record selectorstypeS1 =M1 S -- | Class for datatypes that represent datatypesclassDatatype d where-- | The name of the datatype (unqualified)datatypeName ::t d (f ::k ->Type)(a ::k )->[Char]-- | The fully-qualified name of the module where the type is declaredmoduleName ::t d (f ::k ->Type)(a ::k )->[Char]-- | The package name of the module where the type is declared---- @since 4.9.0.0packageName ::t d (f ::k ->Type)(a ::k )->[Char]-- | Marks if the datatype is actually a newtype---- @since 4.7.0.0isNewtype ::t d (f ::k ->Type)(a ::k )->BoolisNewtype t d f a
_=Bool
False-- | @since 4.9.0.0instance(KnownSymbol n ,KnownSymbol m ,KnownSymbol p ,SingI nt )=>Datatype ('MetaData n m p nt )wheredatatypeName :: t ('MetaData n m p nt) f a -> String
datatypeName t ('MetaData n m p nt) f a
_=Proxy n -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy n
forall k (t :: k). Proxy t
Proxy ::Proxy n )moduleName :: t ('MetaData n m p nt) f a -> String
moduleName t ('MetaData n m p nt) f a
_=Proxy m -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy m
forall k (t :: k). Proxy t
Proxy ::Proxy m )packageName :: t ('MetaData n m p nt) f a -> String
packageName t ('MetaData n m p nt) f a
_=Proxy p -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy p
forall k (t :: k). Proxy t
Proxy ::Proxy p )isNewtype :: t ('MetaData n m p nt) f a -> Bool
isNewtype t ('MetaData n m p nt) f a
_=Sing nt -> DemoteRep Bool
forall k (a :: k). SingKind k => Sing a -> DemoteRep k
fromSing (Sing nt
forall k (a :: k). SingI a => Sing a
sing ::Sing nt )-- | Class for datatypes that represent data constructorsclassConstructor c where-- | The name of the constructorconName ::t c (f ::k ->Type)(a ::k )->[Char]-- | The fixity of the constructorconFixity ::t c (f ::k ->Type)(a ::k )->Fixity conFixity t c f a
_=Fixity
Prefix -- | Marks if this constructor is a recordconIsRecord ::t c (f ::k ->Type)(a ::k )->BoolconIsRecord t c f a
_=Bool
False-- | @since 4.9.0.0instance(KnownSymbol n ,SingI f ,SingI r )=>Constructor ('MetaCons n f r )whereconName :: t ('MetaCons n f r) f a -> String
conName t ('MetaCons n f r) f a
_=Proxy n -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy n
forall k (t :: k). Proxy t
Proxy ::Proxy n )conFixity :: t ('MetaCons n f r) f a -> Fixity
conFixity t ('MetaCons n f r) f a
_=Sing f -> DemoteRep FixityI
forall k (a :: k). SingKind k => Sing a -> DemoteRep k
fromSing (Sing f
forall k (a :: k). SingI a => Sing a
sing ::Sing f )conIsRecord :: t ('MetaCons n f r) f a -> Bool
conIsRecord t ('MetaCons n f r) f a
_=Sing r -> DemoteRep Bool
forall k (a :: k). SingKind k => Sing a -> DemoteRep k
fromSing (Sing r
forall k (a :: k). SingI a => Sing a
sing ::Sing r )-- | Datatype to represent the fixity of a constructor. An infix-- | declaration directly corresponds to an application of 'Infix'.dataFixity =Prefix |Infix Associativity Intderiving(Eq-- ^ @since 4.6.0.0,Show -- ^ @since 4.6.0.0,Ord-- ^ @since 4.6.0.0,Read -- ^ @since 4.6.0.0,Generic -- ^ @since 4.7.0.0)-- | This variant of 'Fixity' appears at the type level.---- @since 4.9.0.0dataFixityI =PrefixI |InfixI Associativity Nat-- | Get the precedence of a fixity value.prec ::Fixity ->Intprec :: Fixity -> Int
prec Fixity
Prefix =Int
10prec (Infix Associativity
_Int
n )=Int
n -- | Datatype to represent the associativity of a constructordataAssociativity =LeftAssociative |RightAssociative |NotAssociative deriving(Eq-- ^ @since 4.6.0.0,Show -- ^ @since 4.6.0.0,Ord-- ^ @since 4.6.0.0,Read -- ^ @since 4.6.0.0,Enum -- ^ @since 4.9.0.0,Bounded -- ^ @since 4.9.0.0,Ix -- ^ @since 4.9.0.0,Generic -- ^ @since 4.7.0.0)-- | The unpackedness of a field as the user wrote it in the source code. For-- example, in the following data type:---- @-- data E = ExampleConstructor Int-- {\-\# NOUNPACK \#-\} Int-- {\-\# UNPACK \#-\} Int-- @---- The fields of @ExampleConstructor@ have 'NoSourceUnpackedness',-- 'SourceNoUnpack', and 'SourceUnpack', respectively.---- @since 4.9.0.0dataSourceUnpackedness =NoSourceUnpackedness |SourceNoUnpack |SourceUnpack deriving(Eq-- ^ @since 4.9.0.0,Show -- ^ @since 4.9.0.0,Ord-- ^ @since 4.9.0.0,Read -- ^ @since 4.9.0.0,Enum -- ^ @since 4.9.0.0,Bounded -- ^ @since 4.9.0.0,Ix -- ^ @since 4.9.0.0,Generic -- ^ @since 4.9.0.0)-- | The strictness of a field as the user wrote it in the source code. For-- example, in the following data type:---- @-- data E = ExampleConstructor Int ~Int !Int-- @---- The fields of @ExampleConstructor@ have 'NoSourceStrictness',-- 'SourceLazy', and 'SourceStrict', respectively.---- @since 4.9.0.0dataSourceStrictness =NoSourceStrictness |SourceLazy |SourceStrict deriving(Eq-- ^ @since 4.9.0.0,Show -- ^ @since 4.9.0.0,Ord-- ^ @since 4.9.0.0,Read -- ^ @since 4.9.0.0,Enum -- ^ @since 4.9.0.0,Bounded -- ^ @since 4.9.0.0,Ix -- ^ @since 4.9.0.0,Generic -- ^ @since 4.9.0.0)-- | The strictness that GHC infers for a field during compilation. Whereas-- there are nine different combinations of 'SourceUnpackedness' and-- 'SourceStrictness', the strictness that GHC decides will ultimately be one-- of lazy, strict, or unpacked. What GHC decides is affected both by what the-- user writes in the source code and by GHC flags. As an example, consider-- this data type:---- @-- data E = ExampleConstructor {\-\# UNPACK \#-\} !Int !Int Int-- @---- * If compiled without optimization or other language extensions, then the-- fields of @ExampleConstructor@ will have 'DecidedStrict', 'DecidedStrict',-- and 'DecidedLazy', respectively.---- * If compiled with @-XStrictData@ enabled, then the fields will have-- 'DecidedStrict', 'DecidedStrict', and 'DecidedStrict', respectively.---- * If compiled with @-O2@ enabled, then the fields will have 'DecidedUnpack',-- 'DecidedStrict', and 'DecidedLazy', respectively.---- @since 4.9.0.0dataDecidedStrictness =DecidedLazy |DecidedStrict |DecidedUnpack deriving(Eq-- ^ @since 4.9.0.0,Show -- ^ @since 4.9.0.0,Ord-- ^ @since 4.9.0.0,Read -- ^ @since 4.9.0.0,Enum -- ^ @since 4.9.0.0,Bounded -- ^ @since 4.9.0.0,Ix -- ^ @since 4.9.0.0,Generic -- ^ @since 4.9.0.0)-- | Class for datatypes that represent recordsclassSelector s where-- | The name of the selectorselName ::t s (f ::k ->Type)(a ::k )->[Char]-- | The selector's unpackedness annotation (if any)---- @since 4.9.0.0selSourceUnpackedness ::t s (f ::k ->Type)(a ::k )->SourceUnpackedness -- | The selector's strictness annotation (if any)---- @since 4.9.0.0selSourceStrictness ::t s (f ::k ->Type)(a ::k )->SourceStrictness -- | The strictness that the compiler inferred for the selector---- @since 4.9.0.0selDecidedStrictness ::t s (f ::k ->Type)(a ::k )->DecidedStrictness -- | @since 4.9.0.0instance(SingI mn ,SingI su ,SingI ss ,SingI ds )=>Selector ('MetaSel mn su ss ds )whereselName :: t ('MetaSel mn su ss ds) f a -> String
selName t ('MetaSel mn su ss ds) f a
_=String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
""(Sing mn -> DemoteRep (Maybe Symbol)
forall k (a :: k). SingKind k => Sing a -> DemoteRep k
fromSing (Sing mn
forall k (a :: k). SingI a => Sing a
sing ::Sing mn ))selSourceUnpackedness :: t ('MetaSel mn su ss ds) f a -> SourceUnpackedness
selSourceUnpackedness t ('MetaSel mn su ss ds) f a
_=Sing su -> DemoteRep SourceUnpackedness
forall k (a :: k). SingKind k => Sing a -> DemoteRep k
fromSing (Sing su
forall k (a :: k). SingI a => Sing a
sing ::Sing su )selSourceStrictness :: t ('MetaSel mn su ss ds) f a -> SourceStrictness
selSourceStrictness t ('MetaSel mn su ss ds) f a
_=Sing ss -> DemoteRep SourceStrictness
forall k (a :: k). SingKind k => Sing a -> DemoteRep k
fromSing (Sing ss
forall k (a :: k). SingI a => Sing a
sing ::Sing ss )selDecidedStrictness :: t ('MetaSel mn su ss ds) f a -> DecidedStrictness
selDecidedStrictness t ('MetaSel mn su ss ds) f a
_=Sing ds -> DemoteRep DecidedStrictness
forall k (a :: k). SingKind k => Sing a -> DemoteRep k
fromSing (Sing ds
forall k (a :: k). SingI a => Sing a
sing ::Sing ds )-- | Representable types of kind @*@.-- This class is derivable in GHC with the @DeriveGeneric@ flag on.---- A 'Generic' instance must satisfy the following laws:---- @-- 'from' . 'to' ≡ 'Prelude.id'-- 'to' . 'from' ≡ 'Prelude.id'-- @classGeneric a where-- | Generic representation typetypeRep a ::Type->Type-- | Convert from the datatype to its representationfrom ::a ->(Rep a )x -- | Convert from the representation to the datatypeto ::(Rep a )x ->a -- | Representable types of kind @* -> *@ (or kind @k -> *@, when @PolyKinds@-- is enabled).-- This class is derivable in GHC with the @DeriveGeneric@ flag on.---- A 'Generic1' instance must satisfy the following laws:---- @-- 'from1' . 'to1' ≡ 'Prelude.id'-- 'to1' . 'from1' ≡ 'Prelude.id'-- @classGeneric1 (f ::k ->Type)where-- | Generic representation typetypeRep1 f ::k ->Type-- | Convert from the datatype to its representationfrom1 ::f a ->(Rep1 f )a -- | Convert from the representation to the datatypeto1 ::(Rep1 f )a ->f a ---------------------------------------------------------------------------------- Meta-data---------------------------------------------------------------------------------- | Datatype to represent metadata associated with a datatype (@MetaData@),-- constructor (@MetaCons@), or field selector (@MetaSel@).---- * In @MetaData n m p nt@, @n@ is the datatype's name, @m@ is the module in-- which the datatype is defined, @p@ is the package in which the datatype-- is defined, and @nt@ is @'True@ if the datatype is a @newtype@.---- * In @MetaCons n f s@, @n@ is the constructor's name, @f@ is its fixity,-- and @s@ is @'True@ if the constructor contains record selectors.---- * In @MetaSel mn su ss ds@, if the field uses record syntax, then @mn@ is-- 'Just' the record name. Otherwise, @mn@ is 'Nothing'. @su@ and @ss@ are-- the field's unpackedness and strictness annotations, and @ds@ is the-- strictness that GHC infers for the field.---- @since 4.9.0.0dataMeta =MetaData SymbolSymbolSymbolBool|MetaCons SymbolFixityI Bool|MetaSel (Maybe Symbol)SourceUnpackedness SourceStrictness DecidedStrictness ---------------------------------------------------------------------------------- Derived instances---------------------------------------------------------------------------------- | @since 4.6.0.0derivinginstanceGeneric [a ]-- | @since 4.6.0.0derivinginstanceGeneric (NonEmpty a )-- | @since 4.6.0.0derivinginstanceGeneric (Maybe a )-- | @since 4.6.0.0derivinginstanceGeneric (Either a b )-- | @since 4.6.0.0derivinginstanceGeneric Bool-- | @since 4.6.0.0derivinginstanceGeneric Ordering-- | @since 4.6.0.0derivinginstanceGeneric (Proxy t )-- | @since 4.6.0.0derivinginstanceGeneric ()-- | @since 4.6.0.0derivinginstanceGeneric ((,)a b )-- | @since 4.6.0.0derivinginstanceGeneric ((,,)a b c )-- | @since 4.6.0.0derivinginstanceGeneric ((,,,)a b c d )-- | @since 4.6.0.0derivinginstanceGeneric ((,,,,)a b c d e )-- | @since 4.6.0.0derivinginstanceGeneric ((,,,,,)a b c d e f )-- | @since 4.6.0.0derivinginstanceGeneric ((,,,,,,)a b c d e f g )-- | @since 4.12.0.0derivinginstanceGeneric (Down a )-- | @since 4.6.0.0derivinginstanceGeneric1 []-- | @since 4.6.0.0derivinginstanceGeneric1 NonEmpty -- | @since 4.6.0.0derivinginstanceGeneric1 Maybe -- | @since 4.6.0.0derivinginstanceGeneric1 (Either a )-- | @since 4.6.0.0derivinginstanceGeneric1 Proxy -- | @since 4.6.0.0derivinginstanceGeneric1 ((,)a )-- | @since 4.6.0.0derivinginstanceGeneric1 ((,,)a b )-- | @since 4.6.0.0derivinginstanceGeneric1 ((,,,)a b c )-- | @since 4.6.0.0derivinginstanceGeneric1 ((,,,,)a b c d )-- | @since 4.6.0.0derivinginstanceGeneric1 ((,,,,,)a b c d e )-- | @since 4.6.0.0derivinginstanceGeneric1 ((,,,,,,)a b c d e f )-- | @since 4.12.0.0derivinginstanceGeneric1 Down ---------------------------------------------------------------------------------- Copied from the singletons package---------------------------------------------------------------------------------- | The singleton kind-indexed data family.datafamilySing (a ::k )-- | A 'SingI' constraint is essentially an implicitly-passed singleton.classSingI (a ::k )where-- | Produce the singleton explicitly. You will likely need the @ScopedTypeVariables@-- extension to use this method the way you want.sing ::Sing a -- | The 'SingKind' class is essentially a /kind/ class. It classifies all kinds-- for which singletons are defined. The class supports converting between a singleton-- type and the base (unrefined) type which it is built from.classSingKind k where-- | Get a base type from a proxy for the promoted kind. For example,-- @DemoteRep Bool@ will be the type @Bool@.typeDemoteRep k ::Type-- | Convert a singleton to its unrefined version.fromSing ::Sing (a ::k )->DemoteRep k -- Singleton symbolsdatainstanceSing (s ::Symbol)whereSSym ::KnownSymbol s =>Sing s -- | @since 4.9.0.0instanceKnownSymbol a =>SingI a wheresing :: Sing a
sing =Sing a
forall (a :: Symbol). KnownSymbol a => Sing a
SSym -- | @since 4.9.0.0instanceSingKind SymbolwheretypeDemoteRep Symbol=String fromSing :: Sing a -> DemoteRep Symbol
fromSing (Sing a
SSym ::Sing s )=Proxy a -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy a
forall k (t :: k). Proxy t
Proxy ::Proxy s )-- Singleton booleansdatainstanceSing (a ::Bool)whereSTrue ::Sing 'TrueSFalse ::Sing 'False-- | @since 4.9.0.0instanceSingI 'Truewheresing :: Sing 'True
sing =Sing 'True
STrue -- | @since 4.9.0.0instanceSingI 'Falsewheresing :: Sing 'False
sing =Sing 'False
SFalse -- | @since 4.9.0.0instanceSingKind BoolwheretypeDemoteRep Bool=BoolfromSing :: Sing a -> DemoteRep Bool
fromSing Sing a
STrue =Bool
DemoteRep Bool
TruefromSing Sing a
SFalse =Bool
DemoteRep Bool
False-- Singleton MaybedatainstanceSing (b ::Maybe a )whereSNothing ::Sing 'Nothing SJust ::Sing a ->Sing ('Just a )-- | @since 4.9.0.0instanceSingI 'Nothing wheresing :: Sing 'Nothing
sing =Sing 'Nothing
forall a. Sing 'Nothing
SNothing -- | @since 4.9.0.0instanceSingI a =>SingI ('Just a )wheresing :: Sing ('Just a)
sing =Sing a -> Sing ('Just a)
forall a (a :: a). Sing a -> Sing ('Just a)
SJust Sing a
forall k (a :: k). SingI a => Sing a
sing -- | @since 4.9.0.0instanceSingKind a =>SingKind (Maybe a )wheretypeDemoteRep (Maybe a )=Maybe (DemoteRep a )fromSing :: Sing a -> DemoteRep (Maybe a)
fromSing Sing a
SNothing =DemoteRep (Maybe a)
forall a. Maybe a
Nothing fromSing (SJust a )=DemoteRep a -> Maybe (DemoteRep a)
forall a. a -> Maybe a
Just (Sing a -> DemoteRep a
forall k (a :: k). SingKind k => Sing a -> DemoteRep k
fromSing Sing a
a )-- Singleton FixitydatainstanceSing (a ::FixityI )whereSPrefix ::Sing 'PrefixI SInfix ::Sing a ->Integer->Sing ('InfixI a n )-- | @since 4.9.0.0instanceSingI 'PrefixI wheresing :: Sing 'PrefixI
sing =Sing 'PrefixI
SPrefix -- | @since 4.9.0.0instance(SingI a ,KnownNat n )=>SingI ('InfixI a n )wheresing :: Sing ('InfixI a n)
sing =Sing a -> Integer -> Sing ('InfixI a n)
forall (a :: Associativity) (n :: Nat).
Sing a -> Integer -> Sing ('InfixI a n)
SInfix (Sing a
forall k (a :: k). SingI a => Sing a
sing ::Sing a )(Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy n
forall k (t :: k). Proxy t
Proxy ::Proxy n ))-- | @since 4.9.0.0instanceSingKind FixityI wheretypeDemoteRep FixityI =Fixity fromSing :: Sing a -> DemoteRep FixityI
fromSing Sing a
SPrefix =DemoteRep FixityI
Fixity
Prefix fromSing (SInfix a n )=Associativity -> Int -> Fixity
Infix (Sing a -> DemoteRep Associativity
forall k (a :: k). SingKind k => Sing a -> DemoteRep k
fromSing Sing a
a )(Int# -> Int
I#(Integer -> Int#
integerToIntInteger
n ))-- Singleton AssociativitydatainstanceSing (a ::Associativity )whereSLeftAssociative ::Sing 'LeftAssociative SRightAssociative ::Sing 'RightAssociative SNotAssociative ::Sing 'NotAssociative -- | @since 4.9.0.0instanceSingI 'LeftAssociative wheresing :: Sing 'LeftAssociative
sing =Sing 'LeftAssociative
SLeftAssociative -- | @since 4.9.0.0instanceSingI 'RightAssociative wheresing :: Sing 'RightAssociative
sing =Sing 'RightAssociative
SRightAssociative -- | @since 4.9.0.0instanceSingI 'NotAssociative wheresing :: Sing 'NotAssociative
sing =Sing 'NotAssociative
SNotAssociative -- | @since 4.0.0.0instanceSingKind Associativity wheretypeDemoteRep Associativity =Associativity fromSing :: Sing a -> DemoteRep Associativity
fromSing Sing a
SLeftAssociative =DemoteRep Associativity
Associativity
LeftAssociative fromSing Sing a
SRightAssociative =DemoteRep Associativity
Associativity
RightAssociative fromSing Sing a
SNotAssociative =DemoteRep Associativity
Associativity
NotAssociative -- Singleton SourceUnpackednessdatainstanceSing (a ::SourceUnpackedness )whereSNoSourceUnpackedness ::Sing 'NoSourceUnpackedness SSourceNoUnpack ::Sing 'SourceNoUnpack SSourceUnpack ::Sing 'SourceUnpack -- | @since 4.9.0.0instanceSingI 'NoSourceUnpackedness wheresing :: Sing 'NoSourceUnpackedness
sing =Sing 'NoSourceUnpackedness
SNoSourceUnpackedness -- | @since 4.9.0.0instanceSingI 'SourceNoUnpack wheresing :: Sing 'SourceNoUnpack
sing =Sing 'SourceNoUnpack
SSourceNoUnpack -- | @since 4.9.0.0instanceSingI 'SourceUnpack wheresing :: Sing 'SourceUnpack
sing =Sing 'SourceUnpack
SSourceUnpack -- | @since 4.9.0.0instanceSingKind SourceUnpackedness wheretypeDemoteRep SourceUnpackedness =SourceUnpackedness fromSing :: Sing a -> DemoteRep SourceUnpackedness
fromSing Sing a
SNoSourceUnpackedness =DemoteRep SourceUnpackedness
SourceUnpackedness
NoSourceUnpackedness fromSing Sing a
SSourceNoUnpack =DemoteRep SourceUnpackedness
SourceUnpackedness
SourceNoUnpack fromSing Sing a
SSourceUnpack =DemoteRep SourceUnpackedness
SourceUnpackedness
SourceUnpack -- Singleton SourceStrictnessdatainstanceSing (a ::SourceStrictness )whereSNoSourceStrictness ::Sing 'NoSourceStrictness SSourceLazy ::Sing 'SourceLazy SSourceStrict ::Sing 'SourceStrict -- | @since 4.9.0.0instanceSingI 'NoSourceStrictness wheresing :: Sing 'NoSourceStrictness
sing =Sing 'NoSourceStrictness
SNoSourceStrictness -- | @since 4.9.0.0instanceSingI 'SourceLazy wheresing :: Sing 'SourceLazy
sing =Sing 'SourceLazy
SSourceLazy -- | @since 4.9.0.0instanceSingI 'SourceStrict wheresing :: Sing 'SourceStrict
sing =Sing 'SourceStrict
SSourceStrict -- | @since 4.9.0.0instanceSingKind SourceStrictness wheretypeDemoteRep SourceStrictness =SourceStrictness fromSing :: Sing a -> DemoteRep SourceStrictness
fromSing Sing a
SNoSourceStrictness =DemoteRep SourceStrictness
SourceStrictness
NoSourceStrictness fromSing Sing a
SSourceLazy =DemoteRep SourceStrictness
SourceStrictness
SourceLazy fromSing Sing a
SSourceStrict =DemoteRep SourceStrictness
SourceStrictness
SourceStrict -- Singleton DecidedStrictnessdatainstanceSing (a ::DecidedStrictness )whereSDecidedLazy ::Sing 'DecidedLazy SDecidedStrict ::Sing 'DecidedStrict SDecidedUnpack ::Sing 'DecidedUnpack -- | @since 4.9.0.0instanceSingI 'DecidedLazy wheresing :: Sing 'DecidedLazy
sing =Sing 'DecidedLazy
SDecidedLazy -- | @since 4.9.0.0instanceSingI 'DecidedStrict wheresing :: Sing 'DecidedStrict
sing =Sing 'DecidedStrict
SDecidedStrict -- | @since 4.9.0.0instanceSingI 'DecidedUnpack wheresing :: Sing 'DecidedUnpack
sing =Sing 'DecidedUnpack
SDecidedUnpack -- | @since 4.9.0.0instanceSingKind DecidedStrictness wheretypeDemoteRep DecidedStrictness =DecidedStrictness fromSing :: Sing a -> DemoteRep DecidedStrictness
fromSing Sing a
SDecidedLazy =DemoteRep DecidedStrictness
DecidedStrictness
DecidedLazy fromSing Sing a
SDecidedStrict =DemoteRep DecidedStrictness
DecidedStrictness
DecidedStrict fromSing Sing a
SDecidedUnpack =DemoteRep DecidedStrictness
DecidedStrictness
DecidedUnpack 

AltStyle によって変換されたページ (->オリジナル) /