| Copyright | Andrew G. Seniuk 2014-2015 |
|---|---|
| License | BSD-style (see the LICENSE file) |
| Maintainer | Andrew Seniuk <rasfar@gmail.com> |
| Stability | provisional |
| Portability | GHC |
| Safe Haskell | None |
| Language | Haskell2010 |
Control.DeepSeq.Bounded.Generic.GSeqable
Description
Generic function version of Seqable (via Generics.SOP).
Probably, a GHC.Generics variant would also be possible.
This metaboilerplate is standard for using the generic deriving facilities of Generics.SOP. Consider seqaid for a turnkey solution.
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GADTs #-} -- for GHC < 7.8 (== 7.6.3)
import Generics.SOP.TH
import Control.DeepSeq.Bounded.Seqable
data TA = A1 TB TA | A2
data TB = B1 Int | B2 TA
deriveGeneric ''TA
deriveGeneric ''TB
main = return $! force_ Propagate (A1 (force_ Propagate (B2 undefined)) A2)Documentation
seqharn :: Generic a => a -> a Source
is semantically the same as seqharn xx, except its
strictness, parallellism, etc. can be tweaked dynamically...
seqharn = to . hliftA (gforce_ Insulate) . from
I can see how this would be useful at compile-time, but how can we use this if seqharn only runs post-compilation? Or is it just analogous to forcep?...
Also: How exactly to dynamically configure this?...