{-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} module Overloaded.Constructors where import Data.Kind (Type) -- | Class for the overloaded constructors. -- -- Instances for this class are automatically generated by type-checker -- plugin, but you may also defined your own. See an example instances for 'Either'. -- -- @ -- {-\# OPTIONS -fplugin=Overloaded -fplugin-opt=Overloaded:Constructors #-} -- @ -- -- Additionally, this overload steals syntax transforming all -- @(:name arg1 arg2)@ into @'build' \@"name" (arg1, arg2)@ expressions. -- Parenthesis are important as standalone @:name@ is (for now) not valid -- Haskell syntax and they also naturally delimit the arguments. -- -- For nullary constructors the @a@ type is unit @()@, -- for unary the type is used as is, -- and for others the parameters are wrapped into a tuple. -- The last case is not particularly pretty, but its overloadable. -- -- class HasConstructor x (s :: Type) (a :: Type) | x s -> a where build :: a -> s match :: s -> Maybe a ------------------------------------------------------------------------------- -- An example ------------------------------------------------------------------------------- instance a' ~ a => HasConstructor "Left" (Either a b) a' where build = Left match = \s -> case s of Left a -> Just a Right _ -> Nothing instance a' ~ b => HasConstructor "Right" (Either a b) a' where build = Right match = \s -> case s of Left _ -> Nothing Right b -> Just b