I'd like to write a horribly non-parametric version of a function of type
pretty :: (Show a) => a -> Text
such that
pretty :: Text -> Text = id
pretty :: String -> Text = T.pack
pretty :: (Show a) => a -> Text = T.pack . show
So the idea is that anything that already has a Show
instance can be turned into a "pretty" Text
by just show
-ing it, except for Text
and String
which we want to special-case.
The following code works:
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, FlexibleContexts #-}
{-# LANGUAGE DataKinds, ConstraintKinds #-}
module Pretty (pretty) where
import Data.Text (Text)
import qualified Data.Text as T
type family StringLike a :: Bool where
StringLike String = True
StringLike Text = True
StringLike a = False
class (b ~ StringLike a) => Pretty' a b where
pretty' :: a -> Text
instance Pretty' String True where
pretty' = T.pack
instance Pretty' Text True where
pretty' = id
instance (Show a, StringLike a ~ False) => Pretty' a False where
pretty' = T.pack . show
type Pretty a = (Pretty' a (StringLike a))
pretty :: (Pretty a) => a -> Text
pretty = pretty'
and it can be used without exporting anything except the pretty
function.
However, I am not too happy about the type signature for pretty
:
pretty :: (Pretty a) => a -> Text
I feel that since StringLike
is a closed type family, there should be a way for GHC to figure out that if only (Show a)
holds, (Pretty a)
is already satisfied, since:
The following hold trivially just by substituting the results of applying StringLike
:
(StringLike String ~ True, Pretty' String True)
(StringLike Text ~ True, Pretty' Text True)
For everything else, we also know the result of applying StringLike
:
(Show a, StringLike a ~ False) => (Pretty' a (StringLike a))
Is there a way to convince GHC of this?
I feel that since
StringLike
is a closed type family, there should be a way for GHC to figure out that if only(Show a)
holds,(Pretty a)
is already satisfied
To do that would require type inspection, and would break parameteric polymorphism. Consider defining a type family
type family IsInt a :: Bool where
IsInt Int = True
IsInt a = False
class (b ~ IsInt a) => TestInt a b where
isInt :: a -> Bool
instance TestInt Int True where
isInt _ = True
instance (IsInt a ~ False) => TestInt a False where
isInt _ = False
Now by your argument, GHC should be able to satisfy TestInt a
from ()
. In other words, we should be able to test for any given type whether it is equal to Int. This is clearly impossible.
Similarly, a Show a
dictionary is equivalent to a function a -> ShowS
. How would you be able to decide, given just that, whether the argument is StringLike
?
Maybe I misunderstood your goal but this seems like a lot of work to get the type you want.
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, UndecidableInstances, IncoherentInstances #-}
module Prettied where
import Data.Text (Text, pack)
class Pretty a where pretty :: a -> Text
instance Pretty Text where pretty = id
instance Pretty String where pretty = pack
instance Show a => Pretty a where pretty = pack . show
While it may seem that pretty
should have type Pretty a => a -> Text
, due to IncoherentInstances
it will actually have type Show a => a -> Text
. This should probably be in its own module because enabling IncoherentInstances
is one of those things that can break valid code.
If you love us? You can donate to us via Paypal or buy me a coffee so we can maintain and grow! Thank you!
Donate Us With