{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ExplicitNamespaces #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
#if __GLASGOW_HASKELL__ <= 710
{-# LANGUAGE Trustworthy #-}
#else
{-# LANGUAGE Safe #-}
#endif
module Universum.TypeOps
( type Each
, type With
, type ($)
) where
#if __GLASGOW_HASKELL__ <= 710
import GHC.Prim (Constraint)
#else
import Data.Kind (Constraint)
#endif
type f $ a = f a
infixr 2 $
type family (<+>) (c :: [k -> Constraint]) (a :: k) where
(<+>) '[] a = (() :: Constraint)
(<+>) (ch ': ct) a = (ch a, (<+>) ct a)
infixl 9 <+>
type family Each (c :: [k -> Constraint]) (as :: [k]) where
Each c '[] = (() :: Constraint)
Each c (h ': t) = (c <+> h, Each c t)
type With a b = a <+> b