morley-1.20.0: Developer tools for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Morley.Util.ShowType

Contents

Description

This is essentially show-type adapted to work with GHC 9.4. The unfortunate thing is, GHC 9.4 conflates Type and Constraint for the purpose of instance overlap, but not instance resolution, hence we have to use an overlappable kind-polymorphic "catch-all" instance instead of the more specific Constraint-kinded one.

See https://gitlab.haskell.org/ghc/ghc/-/issues/23446, https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0032-constraint-vs-type.rst, https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0518-type-vs-constraint.rst for more information.

There is an argument for eventually upstreaming this, but it's small enough to bundle in-tree, and time constraints on our side are pretty tight at the time of writing.

Synopsis

Showtype

class Showtype (a :: k) where Source #

Conversion of types to readable Strings. Analogous to Show.

Minimal complete definition

showtype | showtypesPrec

Methods

showtype :: proxy a -> String Source #

Convert a type a to a readable String. Analogous to show in Show.

showtypesPrec :: Int -> proxy a -> String -> String Source #

Convert a type a to a readable String with additional arguments. Analogous to showsPrec in Show.

Instances

Instances details
KnownNat n => Showtype (n :: Nat) Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy n -> String Source #

showtypesPrec :: Int -> proxy n -> String -> String Source #

Showtype 'EQ Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy 'EQ -> String Source #

showtypesPrec :: Int -> proxy 'EQ -> String -> String Source #

Showtype 'GT Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy 'GT -> String Source #

showtypesPrec :: Int -> proxy 'GT -> String -> String Source #

Showtype 'LT Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy 'LT -> String Source #

showtypesPrec :: Int -> proxy 'LT -> String -> String Source #

Showtype '() Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy '() -> String Source #

showtypesPrec :: Int -> proxy '() -> String -> String Source #

Showtype 'False Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy 'False -> String Source #

showtypesPrec :: Int -> proxy 'False -> String -> String Source #

Showtype 'True Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy 'True -> String Source #

showtypesPrec :: Int -> proxy 'True -> String -> String Source #

KnownSymbol s => Showtype (s :: Symbol) Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy s -> String Source #

showtypesPrec :: Int -> proxy s -> String -> String Source #

Typeable a => Showtype (a :: k) Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy a -> String Source #

showtypesPrec :: Int -> proxy a -> String -> String Source #

Showtype ('Nothing :: Maybe a) Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy 'Nothing -> String Source #

showtypesPrec :: Int -> proxy 'Nothing -> String -> String Source #

Showtype ('[] :: [k]) Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy '[] -> String Source #

showtypesPrec :: Int -> proxy '[] -> String -> String Source #

Showtype a2 => Showtype ('Just a2 :: Maybe a1) Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy ('Just a2) -> String Source #

showtypesPrec :: Int -> proxy ('Just a2) -> String -> String Source #

(Showtype a, Showlisttype as) => Showtype (a ': as :: [k]) Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy (a ': as) -> String Source #

showtypesPrec :: Int -> proxy (a ': as) -> String -> String Source #

Showtype a2 => Showtype ('Left a2 :: Either a1 b) Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy ('Left a2) -> String Source #

showtypesPrec :: Int -> proxy ('Left a2) -> String -> String Source #

Showtype a2 => Showtype ('Right a2 :: Either a1 b) Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy ('Right a2) -> String Source #

showtypesPrec :: Int -> proxy ('Right a2) -> String -> String Source #

(Showtype a, Showtype b) => Showtype ('(a, b) :: (k1, k2)) Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy '(a, b) -> String Source #

showtypesPrec :: Int -> proxy '(a, b) -> String -> String Source #

(Showtype a, Showtype b, Showtype c) => Showtype ('(a, b, c) :: (k1, k2, k3)) Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy '(a, b, c) -> String Source #

showtypesPrec :: Int -> proxy '(a, b, c) -> String -> String Source #

(Showtype a, Showtype b, Showtype c, Showtype d) => Showtype ('(a, b, c, d) :: (k1, k2, k3, k4)) Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy '(a, b, c, d) -> String Source #

showtypesPrec :: Int -> proxy '(a, b, c, d) -> String -> String Source #

(Showtype a, Showtype b, Showtype c, Showtype d, Showtype e) => Showtype ('(a, b, c, d, e) :: (k1, k2, k3, k4, k5)) Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy '(a, b, c, d, e) -> String Source #

showtypesPrec :: Int -> proxy '(a, b, c, d, e) -> String -> String Source #

(Showtype a, Showtype b, Showtype c, Showtype d, Showtype e, Showtype f) => Showtype ('(a, b, c, d, e, f) :: (k1, k2, k3, k4, k5, k6)) Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy '(a, b, c, d, e, f) -> String Source #

showtypesPrec :: Int -> proxy '(a, b, c, d, e, f) -> String -> String Source #

(Showtype a, Showtype b, Showtype c, Showtype d, Showtype e, Showtype f, Showtype g) => Showtype ('(a, b, c, d, e, f, g) :: (k1, k2, k3, k4, k5, k6, k7)) Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy '(a, b, c, d, e, f, g) -> String Source #

showtypesPrec :: Int -> proxy '(a, b, c, d, e, f, g) -> String -> String Source #

(Showtype a, Showtype b, Showtype c, Showtype d, Showtype e, Showtype f, Showtype g, Showtype h) => Showtype ('(a, b, c, d, e, f, g, h) :: (k1, k2, k3, k4, k5, k6, k7, k8)) Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy '(a, b, c, d, e, f, g, h) -> String Source #

showtypesPrec :: Int -> proxy '(a, b, c, d, e, f, g, h) -> String -> String Source #

(Showtype a, Showtype b, Showtype c, Showtype d, Showtype e, Showtype f, Showtype g, Showtype h, Showtype i) => Showtype ('(a, b, c, d, e, f, g, h, i) :: (k1, k2, k3, k4, k5, k6, k7, k8, k9)) Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy '(a, b, c, d, e, f, g, h, i) -> String Source #

showtypesPrec :: Int -> proxy '(a, b, c, d, e, f, g, h, i) -> String -> String Source #

(Showtype a, Showtype b, Showtype c, Showtype d, Showtype e, Showtype f, Showtype g, Showtype h, Showtype i, Showtype j) => Showtype ('(a, b, c, d, e, f, g, h, i, j) :: (k1, k2, k3, k4, k5, k6, k7, k8, k9, k10)) Source # 
Instance details

Defined in Morley.Util.ShowType

Methods

showtype :: proxy '(a, b, c, d, e, f, g, h, i, j) -> String Source #

showtypesPrec :: Int -> proxy '(a, b, c, d, e, f, g, h, i, j) -> String -> String Source #

printtype :: Showtype a => proxy a -> IO () Source #