我为函子(○)制作了点号,但是我的应用程序(↯)无法正常工作,在test3
函数声明中出现错误
{-# LANGUAGE TypeOperators #-}
module Main where
import Protolude
-- composition of functors, analog of .
infixr 9 ○
type (○) f g a = f (g a)
-- functor application, analog of $
infixr 0 ↯
type (↯) f a = f a
test :: [] (Maybe Int)
test = [Just 1]
test2 :: ([] ○ Maybe) Int
test2 = [Just 1]
test3 :: ([] ○ Maybe) ↯ Int -- error here
test3 = [Just 1]
main :: IO ()
main = do
print test
print test2
return ()
我有一个错误
[Error]• The type synonym ‘○’ should have 3 arguments, but has been given 2 • In the type signature: test3 :: ([] ○ Maybe) ↯ Int
怎么了?
更新
这里是使用newtype的实现,因为type synonyms cannot be partially applied
(@ M.Aroosi)
我不喜欢它,因为我必须一直用数据类型构造函数包装数据
是否有一种方法可以实现它,而无需始终用Composition
或Apply
包装数据?
{-# LANGUAGE TypeOperators #-}
module Main where
import Protolude
-- I can't use `type` here, because type synonyms cannot be partially applied
-- composition of functors, analog of .
infixr 9 ○
newtype (○) f g a = Composition (f (g a)) deriving (Show)
-- functor application, analog of $
infixr 0 ↯
newtype (↯) f a = Apply (f a) deriving (Show)
test :: [] (Maybe Int)
test = [Just 1]
test2 :: ([] ○ Maybe) Int
test2 = Composition [Just 1]
test2' :: [] ○ Maybe ↯ Int
test2' = Apply (Composition [Just 1])
test3 :: ([] ○ Maybe ○ Maybe) Int
test3 = Composition [Composition (Just (Just 1))]
test3' :: [] ○ Maybe ○ Maybe ↯ Int
test3' = Apply (Composition [Composition (Just (Just 1))])
main :: IO ()
main = do
print test
print test2
print test2'
print test3
print test3'
return ()
更新
这可以在idris中轻松完成
module Main
test : List (Maybe Integer)
test = [Just 1]
-- using (.) from prelude
test1 : (List . Maybe) Integer
test1 = [Just 1]
-- using (.) and ($) from prelude
test2 : List . Maybe $ Integer
test2 = [Just 1]
main : IO ()
main = do
print test
print test1
print test2
更新
使用type
进行排版也可以使用purescript(可以!)
module Main where
import Prelude
import Data.Maybe (Maybe(..))
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Console (CONSOLE, logShow)
type Composition f g a = f (g a)
infixr 9 type Composition as ○
type Apply f a = f a
infixr 0 type Apply as ↯
test1 :: (Array ○ Maybe) Int
test1 = [Just 1]
test2 :: Array ○ Maybe ↯ Int
test2 = [Just 1]
test3 :: (Array ○ Maybe ○ Maybe) Int
test3 = [Just (Just 1)]
test4 :: Array ○ Maybe ○ Maybe ↯ Int
test4 = [Just (Just 1)]
main :: forall e. Eff (console :: CONSOLE | e) Unit
main = do
logShow test1
logShow test2
logShow test3
logShow test4
更新
正在努力使haskell成为可能
答案 0 :(得分:4)
因此,根据您的要求,以下是涉及类型族的解决方案。它基于Fcf
软件包背后的想法,并附有一篇文章解释该想法here
在我开始之前,有一些使用普通数据类型/新类型的主张:您可以为组合类型定义函子实例,以便将其用作单个单元,也就是可以定义instance (Functor f, Functor g) => Functor (Compose f g) where ..
,您可以'与下面的方法有关。
可能有一个库允许您使用类型列表而不是2(例如Compose [Maybe, [], Either Int] a
)来执行此操作,但是我现在似乎找不到它,因此,如果有人知道,可能是比我在下面提出的解决方案更好(我认为)。
首先,我们需要一些语言扩展:
{-# LANGUAGE
TypeFamilies,
TypeInType,
TypeOperators
#-}
我们还为Data.Kind
包括Type
import Data.Kind (Type)
让我们定义一个类型Exp a
,它将代表a
。
我们还将定义一个类型族Eval
,它将进行艰苦的工作,它将花费Exp a
并给我们一个a
type Exp a = a -> Type
type family Eval (e :: Exp a) :: a
我们现在可以定义我们的运算符(○)
和(↯)
(我更喜欢在这里使用更容易键入的运算符,例如#和$,但是我会坚持使用您选择的运算符这个答案)。
我们将它们定义为空数据类型。这是TypeInType
进入的地方(和TypeOperators
进入这里,这是因为我们正在使用运算符)。
infixr 9 ○
data (○) :: (b -> c) -> (a -> Exp b) -> a -> Exp c
infixr 0 ↯
data (↯) :: (a -> Exp b) -> a -> Exp b
请注意,Exp a
的最终种类如何?这样我们就可以为它们提供Eval
type instance Eval ((○) f g a) = f (Eval (g a))
type instance Eval ((↯) f a) = Eval (f a)
现在您可能想知道“ (○)
的第二个参数是a -> Exp b
类型,但我想给它类似Maybe
的类型,* -> *
类型!” ,这是我们针对该问题的3种解决方案:
(%)
,它与(○)
类似,但采用类型为a -> b
而不是a -> Exp b
的第二个参数。这仅需要替换最右边的合成运算符。 a -> b
“提升”到a -> Exp b
中,为此我将使用名为Lift
的数据类型。这只需要对合成中最右边的类型执行。 a -> Exp b
的“不执行任何操作”数据类型,我将其称为Pure
。 以下是用Haskell编写的三种解决方案:
infixr 9 %
data (%) :: (b -> c) -> (a -> b) -> a -> Exp c
type instance Eval ((%) f g a) = f (g a)
data Lift :: (a -> b) -> a -> Exp b
type instance Eval (Lift f a) = f a
data Pure :: a -> Exp a
type instance Eval (Pure a) = a
我们可以使用此设置进行的另一件事是创建一个类型级别的函数数据类型(称为“ Compose”),该数据类型将获取类型列表并产生其组成
data Compose :: [a -> a] -> a -> Exp a
type instance Eval (Compose '[] a) = a
type instance Eval (Compose (x:xs) a) = x (Eval (Compose xs a))
现在,我们可以制作我们的程序,其中包含一些测试和一个main
,它仅显示测试的值:
{-# LANGUAGE
TypeFamilies,
TypeInType,
TypeOperators
#-}
module Main where
import Data.Kind (Type)
type Exp a = a -> Type
type family Eval (e :: Exp a) :: a
infixr 9 ○
data (○) :: (b -> c) -> (a -> Exp b) -> a -> Exp c
infixr 0 ↯
data (↯) :: (a -> Exp b) -> a -> Exp b
type instance Eval ((○) f g a) = f (Eval (g a))
type instance Eval ((↯) f a) = Eval (f a)
infixr 9 %
data (%) :: (b -> c) -> (a -> b) -> a -> Exp c
type instance Eval ((%) f g a) = f (g a)
data Lift :: (a -> b) -> a -> Exp b
type instance Eval (Lift f a) = f a
data Pure :: a -> Exp a
type instance Eval (Pure a) = a
data Compose :: [a -> a] -> a -> Exp a
type instance Eval (Compose '[] a) = a
type instance Eval (Compose (x:xs) a) = x (Eval (Compose xs a))
test :: [] (Maybe Int)
test = [Just 1]
-- using %
test2 :: Eval (([] % Maybe) Int)
test2 = [Just 1]
test2' :: Eval ([] % Maybe ↯ Int)
test2' = [Just 1]
-- works for longer types too
test3 :: Eval (([] ○ Maybe % Maybe) Int)
test3 = [Just (Just 1)]
test3' :: Eval ([] ○ Maybe % Maybe ↯ Int)
test3' = [Just (Just 1)]
-- we can instead Lift the rightmost type
test4 :: Eval (([] ○ Maybe ○ Lift Maybe) Int)
test4 = [Just (Just 1)]
test4' :: Eval ([] ○ Maybe ○ Lift Maybe ↯ Int)
test4' = [Just (Just 1)]
-- an even longer type, with definition "matching" the type declaration
test5 :: Eval ([] ○ Maybe ○ Either Bool % Maybe ↯ Int)
test5 = (:[]) . Just . Right . Just $ 1
-- Same as above, but instead let's use Pure so we don't need to lift the Maybe or use %
test6 :: Eval ([] ○ Maybe ○ Either Bool ○ Maybe ○ Pure ↯ Int)
test6= (:[]) . Just . Right . Just $ 1
-- same as above, uses Compose
test7 :: Eval (Compose [[], Maybe, Either Bool, Maybe] Int)
test7= (:[]) . Just . Right . Just $ 1
main :: IO ()
main = do
print test
print test2
print test2'
print test3
print test3'
print test4
print test4'
print test5
print test6
print test7
return ()