问题
I want to write an instance of Show
for lists of the following type:
newtype Mu f = Mu (forall a. (f a -> a) -> a)
data ListF a r = Nil | Cons a r deriving (Show)
type List a = Mu (ListF a)
Module Data.Functor.Foldable defines it, but it converting it to Fix
, something I want to avoid.
How can I define this Show
instance?
回答1:
The slogan, "Follow the types!", works for us here, fulltime.
From your code, with some renaming for easier comprehension,
{-# LANGUAGE RankNTypes #-}
data ListF a r = Nil | Cons a r deriving (Show)
newtype List a = Mu {runMu :: forall r. (ListF a r -> r) -> r}
So that we can have
fromList :: [a] -> List a
fromList (x:xs) = Mu $ \g -> g -- g :: ListF a r -> r
(Cons x $ -- just make all types fit
runMu (fromList xs) g)
fromList [] = Mu $ \g -> g Nil
{- or, equationally,
runMu (fromList (x:xs)) g = g (Cons x $ runMu (fromList xs) g)
runMu (fromList []) g = g Nil
such that (thanks, @dfeuer!)
runMu (fromList [1,2,3]) g = g (Cons 1 (g (Cons 2 (g (Cons 3 (g Nil))))))
-}
and we want
instance (Show a) => Show (List a) where
-- show :: List a -> String
show (Mu f) = "(" ++ f showListF ++ ")" -- again, just make the types fit
... we must produce a string; we can only call f
; what could be its argument? According to its type,
where
showListF :: Show a => ListF a String -> String -- so that, f showListF :: String !
showListF Nil = ...
showListF (Cons x s) = ...
There doesn't seen to be any other way to connect the wires here.
With this, print $ fromList [1..5]
prints (1 2 3 4 5 )
.
Indeed this turned out to be a verbose version of chi's answer.
edit: g
is for "algebra" (thanks, @chi!) and f
(in Mu f
) is for "folding". Now the meaning of this type becomes clearer: given an "algebra" (a reduction function), a Mu f
value will use it in the folding of its "inherent list" represented by this "folding function". It represents the folding of a list with one-step reduction semantics, using it on each step of the folding.
回答2:
Define your own algebra first
showOneLayer :: Show a => ListF a String -> String
showOneLayer ... = ...
Then,
instance Show a => Show (Mu (ListF a)) where
show (Mu f) = f showOneLayer
回答3:
As WillNess showed, you probably want a newtype
to wrap your List
:
newtype Mu f = Mu {reduce :: forall a. (f a -> a) -> a}
-- I've added a field name for convenience.
data ListF a r = Nil | Cons a r
deriving (Show, Functor, Foldable, Traversable)
-- You'll probably want these other instances at some point.
newtype List a = List {unList :: Mu (ListF a)}
WillNess also wrote a useful fromList
function; here's another version:
fromList :: Foldable f => f a -> List a
fromList xs =
List $ Mu $ foldr (\a as g -> g (Cons a (as g))) ($ Nil) xs
Now let's write a basic (not quite right) version. I'll turn on ScopedTypeVariables
to add type signatures without annoying duplication.
instance Show a => Show (List a) where
showsPrec _ xs = reduce (unList xs) go
where
go :: ListF a ShowS -> ShowS
go Nil = id
go (Cons x r) = (',':) . showsPrec 0 x . r
This will show a list, sort of:
show (fromList []) = ""
show (fromList [1]) = ",1"
show (fromList [1,2]) = ",1,2"
Hrm. We need to install the leading [
and the trailing ]
, and somehow deal with the extra leading comma. One good way to do that is to keep track of whether we're on the first list element:
instance Show a => Show (List a) where
showsPrec _ (List xs) = ('[':) . reduce xs go False . (']':)
where
go :: ListF a (Bool -> [Char] -> [Char]) -> Bool -> [Char] -> [Char]
go Nil _ = id
go (Cons x r) started =
(if started then (',':) else id)
. showsPrec 0 x
. r True
Now we actually show things properly!
But actually, we've gone to quite a bit more trouble than necessary. All we really needed was a Foldable
instance:
instance Foldable List where
foldr c n (List (Mu g)) = g $ \case
Nil -> n
Cons a as -> c a as
Then we can write
instance Show a => Show (List a) where
showsPrec p xs = showsPrec p (toList xs)
来源:https://stackoverflow.com/questions/50946004/how-to-write-a-show-instance-for-mu-recursive-types