th-deepstrict-0.1.0.0: Check that datatypes are deep strict using Template Haskell.
Safe HaskellNone
LanguageHaskell2010

Language.Haskell.TH.DeepStrict

Description

Check that a datatype is deeply strict, ie, it recursively only has strict fields.

Synopsis

DeepStrict

data DeepStrict reason Source #

A type is deep strict if and only if for each constructor:

  • All of its fields are strict, ie, they have a ! if possible.
  • The type of of each field is deep strict.

The Monoid instance allows us to gather up reasons why a type fails to be deep strict.

Examples

() is deep strict because its single constructor doesn't have any fields so it is vacuously deep strict.

Int, Char, etc are all deep strict because they are wrappers around unlifted types that cannot be lazy.

Maybe Int is not deep strict. It has a Nothing constructor, which is fine. But, the Just constructor has a lazy field, which means it's not deep strict.

Constructors

DeepStrict 
NotDeepStrict !reason 

Instances

Instances details
Functor DeepStrict Source # 
Instance details

Defined in Language.Haskell.TH.DeepStrict

Methods

fmap :: (a -> b) -> DeepStrict a -> DeepStrict b #

(<$) :: a -> DeepStrict b -> DeepStrict a #

Lift reason => Lift (DeepStrict reason :: Type) Source # 
Instance details

Defined in Language.Haskell.TH.DeepStrict

Methods

lift :: Quote m => DeepStrict reason -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => DeepStrict reason -> Code m (DeepStrict reason) #

Semigroup reason => Monoid (DeepStrict reason) Source # 
Instance details

Defined in Language.Haskell.TH.DeepStrict

Methods

mempty :: DeepStrict reason #

mappend :: DeepStrict reason -> DeepStrict reason -> DeepStrict reason #

mconcat :: [DeepStrict reason] -> DeepStrict reason #

Semigroup reason => Semigroup (DeepStrict reason) Source # 
Instance details

Defined in Language.Haskell.TH.DeepStrict

Methods

(<>) :: DeepStrict reason -> DeepStrict reason -> DeepStrict reason #

sconcat :: NonEmpty (DeepStrict reason) -> DeepStrict reason #

stimes :: Integral b => b -> DeepStrict reason -> DeepStrict reason #

Show reason => Show (DeepStrict reason) Source # 
Instance details

Defined in Language.Haskell.TH.DeepStrict

Methods

showsPrec :: Int -> DeepStrict reason -> ShowS #

show :: DeepStrict reason -> String #

showList :: [DeepStrict reason] -> ShowS #

Eq reason => Eq (DeepStrict reason) Source # 
Instance details

Defined in Language.Haskell.TH.DeepStrict

Methods

(==) :: DeepStrict reason -> DeepStrict reason -> Bool #

(/=) :: DeepStrict reason -> DeepStrict reason -> Bool #

Ord reason => Ord (DeepStrict reason) Source # 
Instance details

Defined in Language.Haskell.TH.DeepStrict

Methods

compare :: DeepStrict reason -> DeepStrict reason -> Ordering #

(<) :: DeepStrict reason -> DeepStrict reason -> Bool #

(<=) :: DeepStrict reason -> DeepStrict reason -> Bool #

(>) :: DeepStrict reason -> DeepStrict reason -> Bool #

(>=) :: DeepStrict reason -> DeepStrict reason -> Bool #

max :: DeepStrict reason -> DeepStrict reason -> DeepStrict reason #

min :: DeepStrict reason -> DeepStrict reason -> DeepStrict reason #

Ppr reason => Ppr (DeepStrict reason) Source # 
Instance details

Defined in Language.Haskell.TH.DeepStrict

Methods

ppr :: DeepStrict reason -> Doc #

ppr_list :: [DeepStrict reason] -> Doc #

data DeepStrictReason Source #

Reasons why a type fails to be deep strict.

Constructors

LazyType !Type ![DeepStrictReason]

The type is lazy.

LazyConstructor !Name ![DeepStrictReason]

The type has a lazy constructor.

FieldReason !FieldKey ![DeepStrictReason]

One of the fields of the constructor fails to be deep strict.

LazyField !FieldKey

One of the fields of the constructor is lazy, ie, doesn't have a !.

LazyOther !String 

Checking data types

isDeepStrict :: Type -> Q DeepStrictWithReason Source #

Determine if a type is deep strict Invariant: The type doesn't contain any free variables, eg, Maybe a will fail.

assertDeepStrict :: Type -> Q [Dec] Source #

Assert that a type is deep strict. If the type isn't deep strict then this will produce an error with the reasons why.

Context

data Context Source #

Allow overriding various setting that determine what types we consider deep strict.

Constructors

Context 

Fields

data Strictness Source #

Whether a type is used strictly by a data type. We use these to annotate types with deep strictness overrides. Types that have fields labelled as Strict require those types to be deep strict. Types that have fields labelled as Lazy will never be deep strict, but this can be helpful for nicer messages.

Constructors

Strict 
Lazy