{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
module Data.Arguments
( Argument(..)
, LHS, RHS
, Arg(..)
, arg
) where
class Argument (f :: k1) (n :: k2) where
type GetArg f n :: k1
type SetArg f n x :: k1
data LHS
data RHS
instance Argument (Either a b) LHS where
type GetArg (Either a b) LHS = a
type SetArg (Either a b) LHS a' = Either a' b
instance Argument (Either a b) RHS where
type GetArg (Either a b) RHS = b
type SetArg (Either a b) RHS b' = Either a b'
data Arg n = Arg
arg :: Arg n
arg = Arg