gpt4 book ai didi

haskell - 约束含义作为约束

转载 作者:行者123 更新时间:2023-12-02 18:53:09 25 4
gpt4 key购买 nike

如何将 Haskell 中的约束含义编码为新的约束?在我的示例中,我想要求每个 Functor c d f 都需要使得 Obj c x 隐含 Obj c (f x)。我正在编写约束 forall x 。 Obj c x => Obj d (f x).

{-# LANGUAGE AllowAmbiguousTypes       #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE QuantifiedConstraints #-}

import Prelude hiding (id, Functor, fmap)
import Data.Kind

class Category c where
type Obj c a :: Constraint
id :: (Obj c x) => c x x
comp :: (Obj c x) => c y z -> c x y -> c x z

class ( Category c, Category d, forall x . Obj c x => Obj d (f x))
=> Functor c d f where
fmap :: (Obj c x, Obj c y) => c x y -> d (f x) (f y)

doublefmap :: forall c f x . (Category c , Functor c c f, Obj c x)
=> c x x -> c (f (f x)) (f (f x))
doublefmap = fmap @c @c @f . fmap @c @c @f

但这会产生以下错误:

Minimal.hs:27:14: error:
• Could not deduce: Obj c (f x) arising from a use of ‘fmap’
from the context: (Functor c c f, Obj c x)
bound by the type signature for:
doublefmap :: forall (c :: * -> * -> *) (f :: * -> *) x.
(Category c, Functor c c f, Obj c x) =>
c x x -> c (f (f x)) (f (f x))
at Minimal.hs:(25,1)-(26,44)
• In the first argument of ‘(.)’, namely ‘fmap @c @c @f’
In the expression: fmap @c @c @f . fmap @c @c @f
In an equation for ‘doublefmap’:
doublefmap = fmap @c @c @f . fmap @c @c @f
• Relevant bindings include
doublefmap :: c x x -> c (f (f x)) (f (f x))
(bound at Minimal.hs:27:1)

我在这里做错了什么?我应该给编译器什么额外的提示?有没有更好的方法来实现这一目标?

我的猜测是我需要使用 Data.Constraint:-,但是如何使用?

最佳答案

以下似乎可行,但我不知道这是否是一个更简单的方法。它使用 Data.Constraint 中的运算符 (\\)

{-# LANGUAGE AllowAmbiguousTypes       #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE QuantifiedConstraints #-}

import Prelude hiding (id, Functor, fmap)
import Data.Constraint

class Category c where
type Obj c a :: Constraint
id :: (Obj c x) => c x x
comp :: (Obj c x) => c y z -> c x y -> c x z

class (Category c, Category d) => Functor c d f where
fobj :: forall x. Obj c x :- Obj c (f x)
fmap :: (Obj c x, Obj c y) => c x y -> d (f x) (f y)

doublefmap :: forall c f x . (Category c , Functor c c f, Obj c x)
=> c x x -> c (f (f x)) (f (f x))
doublefmap = (fmap @c @c @f . fmap @c @c @f) \\ fobj @c @c @f @x

关于haskell - 约束含义作为约束,我们在Stack Overflow上找到一个类似的问题: https://stackoverflow.com/questions/59437971/

25 4 0
Copyright 2021 - 2024 cfsdn All Rights Reserved 蜀ICP备2022000587号
广告合作:1813099741@qq.com 6ren.com