{-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE UndecidableSuperClasses #-} module Hcompta.Has where import Data.Proxy (Proxy(..)) import GHC.Exts (Constraint) -- * Class 'Has' type Has ty a = (Get ty a, Set ty a) -- ** Class 'Get' class Get ty a where get :: a -> ty -- ** Class 'Set' class Set ty a where set :: ty -> a -> a -- * Class 'HasI' type HasI cl a = (GetI cl a, SetI cl a) -- ** Type family ':@' -- | Return the type associated with @cl@ and @a@, -- and which is an instance of @cl (cl :@ a)@. type family (:@) (cl:: * -> Constraint) (a:: *) :: * infixr 9 :@ -- ** Class 'GetI' class cl (cl:@a) => GetI cl a where getI_ :: Proxy cl -> a -> cl:@a -- | Convenient helper to be used with 'TypeApplications'. getI :: forall cl a. GetI cl a => a -> cl:@a getI = getI_ (Proxy::Proxy cl) -- ** Class 'SetI' class cl (cl:@a) => SetI cl a where setI_ :: Proxy cl -> cl:@a -> a -> a -- | Convenient helper to be used with 'TypeApplications'. setI :: forall cl a. SetI cl a => cl:@a -> a -> a setI = setI_ (Proxy::Proxy cl)