[Haskell-beginners] Return a Foldable instance
James Cook
mokus at deepbondi.net
Wed May 4 22:06:38 CEST 2011
On May 4, 2011, at 3:26 PM, David McBride wrote:
> I still have a question about this. If you look at the
> Text.Regex.Posix library you can do this:
>
>> "asdf" =~ "asdf" :: String
> "asdf"
>
>> "asdf" =~ "asdf" :: Int
> 1
>> :t "asdf" =~ "asdf"
> "asdf" =~ "asdf" :: (RegexContext Regex [Char] target) => target
>
> So, there is something similar to what the op was asking for. Why is
> this possible, but his is not?
Because unlike the Foldable class, the RegexContext class does provide
functions that return values of its type parameters. RegexContext
is defined as follows:
> class RegexLike regex source => RegexContext regex source target
where
> match :: regex -> source -> target
> matchM :: Monad m => regex -> source -> m target
The 'match' function returns a value of type 'target'. For Foldable,
though:
> class Foldable t where
> fold :: Monoid m => t m -> m
> foldMap :: Monoid m => (a -> m) -> t a -> m
> foldr :: (a -> b -> b) -> b -> t a -> b
> foldl :: (a -> b -> a) -> a -> t b -> a
> foldr1 :: (a -> a -> a) -> t a -> a
> foldl1 :: (a -> a -> a) -> t a -> a
None of those functions return anything that mentions "t", so the
Foldable class is not able to construct values of an unknown Foldable
type.
For a simpler example, the same ideas applies to more-familiar
typeclasses defined in the Prelude. For example, you can have
expressions of type "Num a => a", because the Num class defines a
function "fromInteger :: Integer -> a" - so if you have an Integer,
you can make a value of any type that is an instance of Num. But you
cannot have a useful expression of type "Show a => a", because Show
doesn't define any functions that produce values.
-- James
More information about the Beginners
mailing list