如何 'show' 不可显示的类型?
How to 'show' unshowable types?
我正在使用 data-reify
和 graphviz
将 eDSL 转换为漂亮的图形表示,用于自省。
作为一个简单的人为示例,请考虑:
{-# LANGUAGE GADTs #-}
data Expr a where
Constant :: a -> Expr a
Map :: (other -> a) -> Expr a -> Expr a
Apply :: Expr (other -> a) -> Expr a -> Expr a
instance Functor Expr where
fmap fun val = Map fun val
instance Applicative Expr where
fun_expr <*> data_expr = Apply fun_expr data_expr
pure val = Constant val
-- And then some functions to optimize an Expr AST, evaluate Exprs, etc.
为了更好地自省,我想打印存储在 DSL 数据类型的某些 AST 节点中的值。
但是,通常任何 a
都可能存储在 Constant
中,即使那些没有实现 Show
。这不一定是个问题,因为我们可以像这样限制 Expr
的实例:
instance Show a => Show (Expr a) where
...
但这不是我想要的:我仍然希望能够打印 Expr
即使 a
不是 Show
-able,通过打印一些占位符值(例如它的类型和它不可打印的消息)。
因此,如果我们有 a
实现 Show
,我们想做一件事,如果特定 a
没有实现,我们想做另一件事。
此外,DSL还有构造函数Map
和Apply
,问题更大。构造函数存在于 other
中,因此我们不能对 other
、a
或 (other -> a)
做任何假设。将 other
类型的约束添加到 Map
resp。 Apply
构造函数会破坏 Functor
的实现。 Applicative
转发给他们。
但在这里我也想打印函数:
- 一个独特的参考。使用
System.Mem.StableName
. 这总是可能的(即使它并不漂亮,因为它需要 unsafePerformIO
)
- 它的类型,如果可能的话(一种技术是使用
show (typeOf fun)
,但它要求fun
是Typeable
)。
我们又遇到了一个问题,如果我们有一个 f
实现了 Typeable
,我们想做一件事,如果 f
没有实现,我们又想做另一件事。
如何做到这一点?
额外免责声明:这里的目标不是为不支持它的类型创建 'correct' Show
实例。没有愿望以后可以Read
他们,或者print a != print b
暗示a != b
.
目标是以'nice for human introspection'方式打印任何数据结构。
我坚持的部分是,如果 a
resp 有额外的约束,我想使用一种实现。 (other -> a)
,但如果这些不存在,则为 'default'。
也许键入 类 和 FlexibleInstances
,或者这里可能需要类型族?我还没弄明白(也许我一起走错了路)。
并非所有问题都有解决方案。并非所有约束系统都有令人满意的分配。
所以...放宽限制。将你需要的数据存储在你的数据结构中,并使用类型签名 like show
, fmap
, pure
的函数, 和 (<*>)
,但不完全等于它们。如果您需要 IO
,请在您的类型签名中使用 IO
。简而言之:让自己摆脱对标准库适合您的特殊需求的期望。
要处理您可能有或没有实例的事情,请存储说明您是否有实例的数据:
data InstanceOrNot c where
Instance :: c => InstanceOrNot c
Not :: InstanceOrNot c
(也许 Constraint
-kinded Either
-like,而不是 Maybe
-like,会更合适。我怀疑当你开始编码时你会发现需要什么.) 要求致电 notFmap
的客户和朋友酌情提供这些。
在评论中,我建议根据您需要的约束对您的类型进行参数化,并为无约束版本提供一个 Functor
实例。这是一个简短的示例,展示了它的外观:
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
import Data.Kind
type family All cs a :: Constraint where
All '[] a = ()
All (c:cs) a = (c a, All cs a)
data Lol cs a where
Leaf :: a -> Lol cs a
Fmap :: All cs b => (a -> b) -> Lol cs a -> Lol cs b
instance Functor (Lol '[]) where
fmap f (Leaf a) = Leaf (f a)
fmap f (Fmap g garg) = Fmap (f . g) garg
好时机! Well-typed 最近发布了一个库,它允许您恢复运行时信息。他们特别有一个显示任意值的例子。它在 github https://github.com/well-typed/recover-rtti。
原来这是一个在过去被多人认可的问题,被称为'Constrained Monad Problem'。有一个优雅的解决方案,在 Neil Sculthorpe 和 Jan Bracker 以及 George Giorgidze 和 Andy Gill 的论文 The Constrained-Monad Problem 中有详细解释。
该技术的简要总结:Monad(和其他类型类)有一个 'normal form'。我们可以 'lift' 原语(它们以我们希望的任何方式受到约束)进入这个 'normal form' 结构,它本身是一个存在的数据类型,然后使用我们已经提升到的类型类可用的任何操作。这些操作本身不受约束,因此我们可以使用 Haskell 的所有常规类型类函数。
最后,为了将其转回具体类型(同样具有我们感兴趣的所有约束),我们 'lower' 它是一个操作,它为每个类型类的操作采用一个函数,它将应用于合适的时间。
这样,来自外部的约束(它们是提供给降低的函数的一部分)和来自内部的约束(它们是我们提升的原语的一部分)能够匹配,最后我们得到一个大的快乐约束我们已经能够使用任何正常 Functor/Monoid/Monad/etc 的数据类型。操作。
有趣的是,虽然中间操作不受约束,但据我所知,不可能写出 'breaks' 它们的内容,因为这会破坏所考虑的类型类应遵守的绝对法则。
这在 constrained-normal Hackage 包中可用,可在您自己的代码中使用。
我遇到的这个例子可以按如下方式实现:
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE UndecidableInstances #-}
module Example where
import Data.Dynamic
import Data.Kind
import Data.Typeable
import Control.Monad.ConstrainedNormal
-- | Required to have a simple constraint which we can use as argument to `Expr` / `Expr'`.
-- | This is definitely the part of the example with the roughest edges: I have yet to figure out
-- | how to make Haskell happy with constraints
class (Show a, Typeable a) => Introspectable a where {}
instance (Show a, Typeable a) => Introspectable a where {}
data Expr' (c :: * -> Constraint) a where
C :: a -> Expr' c a
-- M :: (a -> b) -> Expr' a -> Expr' b --^ NOTE: This one is actually never used as ConstrainedNormal will use the 'free' implementation based on A + C.
A :: c a => Expr' c (a -> b) -> Expr' c a -> Expr' c b
instance Introspectable a => Show (Expr' Introspectable a) where
show e = case e of
C x -> "(C " ++ show x ++ ")"
-- M f x = "(M " ++ show val ++ ")"
A fx x -> "(A " ++ show (typeOf fx) ++ " " ++ show x ++ ")"
-- | In user-facing code you'd not want to expose the guts of this construction
-- So let's introduce a 'wrapper type' which is what a user would normally interact with.
type Expr c a = NAF c (Expr' c) a
liftExpr :: c a => Expr' c a -> Expr c a
liftExpr expr = liftNAF expr
lowerExpr :: c a => Expr c a -> Expr' c a
lowerExpr lifted_expr = lowerNAF C A lifted_expr
constant :: Introspectable a => a -> Expr c a
constant val = pure val -- liftExpr (C val)
你现在可以写
ghci> val = constant 10 :: Expr Introspectable Int
(C 10)
ghci> (+2) <$> val
(C 12)
ghci> (+) <$> constant 10 <*> constant 32 :: Expr Introspectable Int
并且通过使用 Data.Constraint.Trivial
(trivial-constrained 库的一部分,虽然也可以编写您自己的 'empty constrained'),但可以改为编写
ghci> val = constant 10 :: Expr Unconstrained Int
它将像以前一样工作,但现在 val
无法打印。
我还没有弄清楚的一件事是如何正确处理约束子集(即,如果我有一个只需要 Show
的函数,让它可以处理 Introspectable
).目前一切都必须与 'big' 约束集一起工作。
另一个小缺点当然是您必须注释约束类型(例如,如果您不需要约束,请手动编写 Unconstrained
),否则 GHC 会抱怨 c0
未知。
我们已经实现了目标,即可以可选地 将类型限制为可打印,所有不需要打印的机器也可以在所有实例上工作类型族,包括那些不可打印的类型,类型可以用作 Monoid
s、Functor
s、Applicative
s 等,只要你喜欢。
我认为这是一个很好的方法,并要表扬 Neil Sculthorpe 等人。感谢他们在论文上的工作以及使这成为可能的 constrained-normal
库。太酷了!
我正在使用 data-reify
和 graphviz
将 eDSL 转换为漂亮的图形表示,用于自省。
作为一个简单的人为示例,请考虑:
{-# LANGUAGE GADTs #-}
data Expr a where
Constant :: a -> Expr a
Map :: (other -> a) -> Expr a -> Expr a
Apply :: Expr (other -> a) -> Expr a -> Expr a
instance Functor Expr where
fmap fun val = Map fun val
instance Applicative Expr where
fun_expr <*> data_expr = Apply fun_expr data_expr
pure val = Constant val
-- And then some functions to optimize an Expr AST, evaluate Exprs, etc.
为了更好地自省,我想打印存储在 DSL 数据类型的某些 AST 节点中的值。
但是,通常任何 a
都可能存储在 Constant
中,即使那些没有实现 Show
。这不一定是个问题,因为我们可以像这样限制 Expr
的实例:
instance Show a => Show (Expr a) where
...
但这不是我想要的:我仍然希望能够打印 Expr
即使 a
不是 Show
-able,通过打印一些占位符值(例如它的类型和它不可打印的消息)。
因此,如果我们有 a
实现 Show
,我们想做一件事,如果特定 a
没有实现,我们想做另一件事。
此外,DSL还有构造函数Map
和Apply
,问题更大。构造函数存在于 other
中,因此我们不能对 other
、a
或 (other -> a)
做任何假设。将 other
类型的约束添加到 Map
resp。 Apply
构造函数会破坏 Functor
的实现。 Applicative
转发给他们。
但在这里我也想打印函数:
- 一个独特的参考。使用
System.Mem.StableName
. 这总是可能的(即使它并不漂亮,因为它需要 - 它的类型,如果可能的话(一种技术是使用
show (typeOf fun)
,但它要求fun
是Typeable
)。
unsafePerformIO
)
我们又遇到了一个问题,如果我们有一个 f
实现了 Typeable
,我们想做一件事,如果 f
没有实现,我们又想做另一件事。
如何做到这一点?
额外免责声明:这里的目标不是为不支持它的类型创建 'correct' Show
实例。没有愿望以后可以Read
他们,或者print a != print b
暗示a != b
.
目标是以'nice for human introspection'方式打印任何数据结构。
我坚持的部分是,如果 a
resp 有额外的约束,我想使用一种实现。 (other -> a)
,但如果这些不存在,则为 'default'。
也许键入 类 和 FlexibleInstances
,或者这里可能需要类型族?我还没弄明白(也许我一起走错了路)。
并非所有问题都有解决方案。并非所有约束系统都有令人满意的分配。
所以...放宽限制。将你需要的数据存储在你的数据结构中,并使用类型签名 like show
, fmap
, pure
的函数, 和 (<*>)
,但不完全等于它们。如果您需要 IO
,请在您的类型签名中使用 IO
。简而言之:让自己摆脱对标准库适合您的特殊需求的期望。
要处理您可能有或没有实例的事情,请存储说明您是否有实例的数据:
data InstanceOrNot c where
Instance :: c => InstanceOrNot c
Not :: InstanceOrNot c
(也许 Constraint
-kinded Either
-like,而不是 Maybe
-like,会更合适。我怀疑当你开始编码时你会发现需要什么.) 要求致电 notFmap
的客户和朋友酌情提供这些。
在评论中,我建议根据您需要的约束对您的类型进行参数化,并为无约束版本提供一个 Functor
实例。这是一个简短的示例,展示了它的外观:
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
import Data.Kind
type family All cs a :: Constraint where
All '[] a = ()
All (c:cs) a = (c a, All cs a)
data Lol cs a where
Leaf :: a -> Lol cs a
Fmap :: All cs b => (a -> b) -> Lol cs a -> Lol cs b
instance Functor (Lol '[]) where
fmap f (Leaf a) = Leaf (f a)
fmap f (Fmap g garg) = Fmap (f . g) garg
好时机! Well-typed 最近发布了一个库,它允许您恢复运行时信息。他们特别有一个显示任意值的例子。它在 github https://github.com/well-typed/recover-rtti。
原来这是一个在过去被多人认可的问题,被称为'Constrained Monad Problem'。有一个优雅的解决方案,在 Neil Sculthorpe 和 Jan Bracker 以及 George Giorgidze 和 Andy Gill 的论文 The Constrained-Monad Problem 中有详细解释。
该技术的简要总结:Monad(和其他类型类)有一个 'normal form'。我们可以 'lift' 原语(它们以我们希望的任何方式受到约束)进入这个 'normal form' 结构,它本身是一个存在的数据类型,然后使用我们已经提升到的类型类可用的任何操作。这些操作本身不受约束,因此我们可以使用 Haskell 的所有常规类型类函数。 最后,为了将其转回具体类型(同样具有我们感兴趣的所有约束),我们 'lower' 它是一个操作,它为每个类型类的操作采用一个函数,它将应用于合适的时间。 这样,来自外部的约束(它们是提供给降低的函数的一部分)和来自内部的约束(它们是我们提升的原语的一部分)能够匹配,最后我们得到一个大的快乐约束我们已经能够使用任何正常 Functor/Monoid/Monad/etc 的数据类型。操作。
有趣的是,虽然中间操作不受约束,但据我所知,不可能写出 'breaks' 它们的内容,因为这会破坏所考虑的类型类应遵守的绝对法则。
这在 constrained-normal Hackage 包中可用,可在您自己的代码中使用。
我遇到的这个例子可以按如下方式实现:
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE UndecidableInstances #-}
module Example where
import Data.Dynamic
import Data.Kind
import Data.Typeable
import Control.Monad.ConstrainedNormal
-- | Required to have a simple constraint which we can use as argument to `Expr` / `Expr'`.
-- | This is definitely the part of the example with the roughest edges: I have yet to figure out
-- | how to make Haskell happy with constraints
class (Show a, Typeable a) => Introspectable a where {}
instance (Show a, Typeable a) => Introspectable a where {}
data Expr' (c :: * -> Constraint) a where
C :: a -> Expr' c a
-- M :: (a -> b) -> Expr' a -> Expr' b --^ NOTE: This one is actually never used as ConstrainedNormal will use the 'free' implementation based on A + C.
A :: c a => Expr' c (a -> b) -> Expr' c a -> Expr' c b
instance Introspectable a => Show (Expr' Introspectable a) where
show e = case e of
C x -> "(C " ++ show x ++ ")"
-- M f x = "(M " ++ show val ++ ")"
A fx x -> "(A " ++ show (typeOf fx) ++ " " ++ show x ++ ")"
-- | In user-facing code you'd not want to expose the guts of this construction
-- So let's introduce a 'wrapper type' which is what a user would normally interact with.
type Expr c a = NAF c (Expr' c) a
liftExpr :: c a => Expr' c a -> Expr c a
liftExpr expr = liftNAF expr
lowerExpr :: c a => Expr c a -> Expr' c a
lowerExpr lifted_expr = lowerNAF C A lifted_expr
constant :: Introspectable a => a -> Expr c a
constant val = pure val -- liftExpr (C val)
你现在可以写
ghci> val = constant 10 :: Expr Introspectable Int
(C 10)
ghci> (+2) <$> val
(C 12)
ghci> (+) <$> constant 10 <*> constant 32 :: Expr Introspectable Int
并且通过使用 Data.Constraint.Trivial
(trivial-constrained 库的一部分,虽然也可以编写您自己的 'empty constrained'),但可以改为编写
ghci> val = constant 10 :: Expr Unconstrained Int
它将像以前一样工作,但现在 val
无法打印。
我还没有弄清楚的一件事是如何正确处理约束子集(即,如果我有一个只需要 Show
的函数,让它可以处理 Introspectable
).目前一切都必须与 'big' 约束集一起工作。
另一个小缺点当然是您必须注释约束类型(例如,如果您不需要约束,请手动编写 Unconstrained
),否则 GHC 会抱怨 c0
未知。
我们已经实现了目标,即可以可选地 将类型限制为可打印,所有不需要打印的机器也可以在所有实例上工作类型族,包括那些不可打印的类型,类型可以用作 Monoid
s、Functor
s、Applicative
s 等,只要你喜欢。
我认为这是一个很好的方法,并要表扬 Neil Sculthorpe 等人。感谢他们在论文上的工作以及使这成为可能的 constrained-normal
库。太酷了!