large-generics-0.2.0.0: Generic programming API for large-records and large-anon
Safe HaskellNone
LanguageHaskell2010

Data.Record.Generic.Rep.Internal

Description

Definition of Rep and functions that do not depend on ".Generic"

Defined as a separate module to avoid circular module dependencies.

Synopsis

Documentation

newtype Rep f a Source #

Representation of some record a

The f parameter describes which functor has been applied to all fields of the record; in other words Rep I is isomorphic to the record itself.

Constructors

Rep (SmallArray (f Any)) 

Instances

Instances details
Eq x => Eq (Rep (K x :: Type -> Type) a) Source # 
Instance details

Defined in Data.Record.Generic.Rep.Internal

Methods

(==) :: Rep (K x) a -> Rep (K x) a -> Bool #

(/=) :: Rep (K x) a -> Rep (K x) a -> Bool #

Show x => Show (Rep (K x :: Type -> Type) a) Source # 
Instance details

Defined in Data.Record.Generic.Rep.Internal

Methods

showsPrec :: Int -> Rep (K x) a -> ShowS #

show :: Rep (K x) a -> String #

showList :: [Rep (K x) a] -> ShowS #

Basic functions

map' :: (forall x. f x -> g x) -> Rep f a -> Rep g a Source #

Strict map

map' f x is strict in x: if x is undefined, map f x will also be undefined, even if f never needs any values from x.

sequenceA :: Applicative m => Rep (m :.: f) a -> m (Rep f a) Source #

Conversion

unsafeFromList :: [b] -> Rep (K b) a Source #

Convert list to Rep

Does not check that the list has the right number of elements.

unsafeFromListAny :: [f Any] -> Rep f a Source #

Convert list to Rep

Does not check that the list has the right number of elements, nor the types of those elements.

collapse :: Rep (K a) b -> [a] Source #

toListAny :: Rep f a -> [f Any] Source #

Convert Rep to list

Auxiliary

noInlineUnsafeCo :: forall a b. a -> b Source #

Avoid potential segfault with ghc < 9.0

See https://gitlab.haskell.org/ghc/ghc/-/issues/16893. I haven't actually seen this fail in large-records, but we saw it fail in the compact representation branch of sop-core, and what we do here is not so different, so better to play it safe.