对于类型对齐的序列,我如何用foldMap表示foldr?

dfe*_*uer 10 haskell types monoids type-variables foldable

我正在玩类型对齐的序列,特别是我正在搞乱折叠它们的想法.可折叠的类型对齐序列看起来像这样:

class FoldableTA fm where
  foldMapTA :: Category h =>
                (forall b c . a b c -> h b c) ->
                fm a b d -> h b d
  foldrTA :: (forall b c d . a c d -> h b c -> h b d) ->
             h p q -> fm a q r -> h p r
  foldlTA :: ...
Run Code Online (Sandbox Code Playgroud)

通过首先使用以天真的方式将序列转换为类型对齐的列表(即,使用类型对齐的列表类别)然后折叠该列表,实现foldrTA起来非常容易.不幸的是,这可能是非常低效的,因为长列表可以预先设置为短列表.我一直试图找出一种方法来使用类似于用于更有效地定义右和左折叠的技巧,但这些类型让我头晕目眩.这似乎不够通用,我从其他方向采取的每一步都会让我得到更多的类型变量,而不是我能追踪到的.foldMapTAfoldMapTAData.FoldableEndo

Joa*_*ner 7

我发现这个typechecks:

{-# LANGUAGE RankNTypes #-}
module FoldableTA where

import Control.Category
import Prelude hiding (id, (.))

class FoldableTA fm where
  foldMapTA :: Category h => (forall b c . a b c -> h b c) -> fm a b d -> h b d
  foldrTA :: (forall b c d . a c d -> h b c -> h b d) -> h p q -> fm a q r -> h p r
  foldrTA f z t = appEndoTA (foldMapTA (\x -> TAEndo (f x)) t) z

newtype TAEndo h c d = TAEndo { appEndoTA :: forall b. h b c -> h b d  }

instance Category (TAEndo h) where
    id = TAEndo id
    TAEndo f1 . TAEndo f2 = TAEndo (f1 . f2)
Run Code Online (Sandbox Code Playgroud)

不知道它是否有意义,但是周围有如此多的类型索引,我怀疑有很多类型检查代码没有意义.

  • 实际上,我非常确定任何终止并具有正确类型的东西都可以通过参数确保正确.非常感谢! (2认同)