{-# LANGUAGE CPP #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeOperators #-} {-# OPTIONS_GHC -Wall #-} {- | This module contains a bunch of pre-defined proxies so that users don't /always/ have to write @(Proxy :: Proxy Word8)@, etc. This library uses the naming convention of 1, 2, 3, etc. as suffixes to denote higher-kindedness of the proxied type. For example: @ const :: Proxy (Const a b) -- ^ @Const a b@ is kinded '*', so there is no number -- appended to the name of the type. const1 :: Proxy (Const a) -- ^ @Const a@ is kinded '*' '->' '*', so there is the -- number 1 appended to the name of the type. const2 :: Proxy Const -- ^ @Const@ is kinded '*' '->' '*', so there is the -- number 2 appended to the name of the type. @ It is recommended that you import this module qualified to avoid naming conflicts. -} module Proxy ( bool , char , complex , complex1 , compose , compose1 , compose2 , compose3 , const , const1 , const2 , constr , constraint , datarep , datatype , dynamic , e0 , e1 , e2 , e3 , e6 , e9 , e12 , either , either1 , either2 , fixed , fixed1 , fixity #if MIN_VERSION_base(4,10,0) , hrefl , hrefl1 , hrefl2 #endif , identity , identity1 , ioref , ioref1 , int , int8 , int16 , int32 , int64 , list , list1 , nonEmpty , maybe , maybe1 , nonEmpty1 , ordering , proxy , proxy1 , ratio , ratio1 , refl , refl1 , refl2 , string , tuple , tuple1 , tuple2 , word , word8 , word16 , word32 , word64 , unique , version , void ) where import Data.Complex (Complex) import Data.Data (Constr, DataType, DataRep, Fixity) import Data.Dynamic (Dynamic) import Data.Fixed (Fixed, E0, E1, E2, E3, E6, E9, E12) import Data.Functor.Compose (Compose) import Data.Functor.Const (Const) import Data.Functor.Identity import Data.IORef (IORef) import Data.Int (Int8, Int16, Int32, Int64) import Data.Kind (Constraint) import Data.List.NonEmpty (NonEmpty) import Data.Proxy (Proxy(..)) import Data.Ratio (Ratio) import Data.Word (Word8, Word16, Word32, Word64) import Data.Type.Equality ( (:~:) #if MIN_VERSION_base(4,10,0) , (:~~:) #endif ) import Data.Unique (Unique) import Data.Version (Version) import Data.Void (Void) import Prelude hiding (const, either, maybe, product, sum) bool :: Proxy Bool bool = Proxy char :: Proxy Char char = Proxy complex :: Proxy (Complex a) complex = Proxy complex1 :: Proxy Complex complex1 = Proxy compose :: Proxy (Compose f g a) compose = Proxy compose1 :: Proxy (Compose f g) compose1 = Proxy compose2 :: Proxy (Compose f) compose2 = Proxy compose3 :: Proxy Compose compose3 = Proxy const :: Proxy (Const a b) const = Proxy const1 :: Proxy (Const a) const1 = Proxy const2 :: Proxy Const const2 = Proxy constr :: Proxy Constr constr = Proxy constraint :: Proxy Constraint constraint = Proxy datarep :: Proxy DataRep datarep = Proxy datatype :: Proxy DataType datatype = Proxy dynamic :: Proxy Dynamic dynamic = Proxy either :: Proxy (Either a b) either = Proxy either1 :: Proxy (Either a) either1 = Proxy either2 :: Proxy Either either2 = Proxy fixed :: Proxy (Fixed a) fixed = Proxy fixed1 :: Proxy Fixed fixed1 = Proxy e0 :: Proxy E0 e0 = Proxy e1 :: Proxy E1 e1 = Proxy e2 :: Proxy E2 e2 = Proxy e3 :: Proxy E3 e3 = Proxy e6 :: Proxy E6 e6 = Proxy e9 :: Proxy E9 e9 = Proxy e12 :: Proxy E12 e12 = Proxy fixity :: Proxy Fixity fixity = Proxy #if MIN_VERSION_base(4,10,0) hrefl :: Proxy (a :~~: b) hrefl = Proxy hrefl1 :: Proxy ((:~~:) a) hrefl1 = Proxy hrefl2 :: Proxy (:~~:) hrefl2 = Proxy #endif identity :: Proxy (Identity a) identity = Proxy identity1 :: Proxy Identity identity1 = Proxy ioref :: Proxy (IORef a) ioref = Proxy ioref1 :: Proxy IORef ioref1 = Proxy int :: Proxy Int int = Proxy int8 :: Proxy Int8 int8 = Proxy int16 :: Proxy Int16 int16 = Proxy int32 :: Proxy Int32 int32 = Proxy int64 :: Proxy Int64 int64 = Proxy list :: Proxy [a] list = Proxy list1 :: Proxy [] list1 = Proxy maybe :: Proxy (Maybe a) maybe = Proxy maybe1 :: Proxy Maybe maybe1 = Proxy nonEmpty :: Proxy (NonEmpty a) nonEmpty = Proxy nonEmpty1 :: Proxy NonEmpty nonEmpty1 = Proxy proxy :: Proxy (Proxy a) proxy = Proxy proxy1 :: Proxy Proxy proxy1 = Proxy ratio :: Proxy (Ratio a) ratio = Proxy ratio1 :: Proxy Ratio ratio1 = Proxy refl :: Proxy (a :~: b) refl = Proxy refl1 :: Proxy ((:~:) a) refl1 = Proxy refl2 :: Proxy (:~:) refl2 = Proxy string :: Proxy String string = Proxy tuple :: Proxy (a,b) tuple = Proxy tuple1 :: Proxy ( (,) a) tuple1 = Proxy tuple2 :: Proxy (,) tuple2 = Proxy word :: Proxy Word word = Proxy word8 :: Proxy Word8 word8 = Proxy word16 :: Proxy Word16 word16 = Proxy word32 :: Proxy Word32 word32 = Proxy word64 :: Proxy Word64 word64 = Proxy ordering :: Proxy Ordering ordering = Proxy unique :: Proxy Unique unique = Proxy version :: Proxy Version version = Proxy void :: Proxy Void void = Proxy