Copyright | (c) 2023 Sayo contributors |
---|---|
License | MPL-2.0 (see the file LICENSE) |
Maintainer | ymdfield@outlook.jp |
Safe Haskell | None |
Language | GHC2021 |
Data.Effect.HFunctor.TH
Description
This module provides TemplateHaskell
functions to derive an instance of
HFunctor
.
Documentation
makeHFunctor :: Name -> Q [Dec] Source #
Derive an instance of HFunctor
for a type constructor of any higher-order
kind taking at least two arguments.
makeHFunctor' :: Name -> (Infinite (Q Type) -> Q Type) -> Q [Dec] Source #
Derive an instance of HFunctor
for a type constructor of any higher-order
kind taking at least two arguments.
Furthermore, you can manually provide type constraints for the instance:
{-# LANGUAGE BlockArguments #-} import Data.List.Infinite (Infinite ((:<))) data Example (g :: Type -> Type) h (f :: Type -> Type) (a :: Type) where Example :: g (h f a) -> Example g h f a makeHFunctor' ''Example \(g :< h :< _) -> [t| (Functor $g, HFunctor $h) |]