[Haskell-cafe] Associated patterns

adam vogt vogt.adam at gmail.com
Tue Jan 21 15:34:59 UTC 2014


Hi Alejandro,

If your inspiration for "associated __" comes from the -XTypeFamilies,
consider that you can take a working program, move all associated
type/data families to top-level, and the program will still work. The
only point of associating them with a class is to help prevent people
from forgetting to write the type instance, and possibly to improve
documentation.

So maybe using a class method in the definition of a pattern synonym
is close enough:

{-# LANGUAGE ViewPatterns, PatternSynonyms #-}
import qualified Data.Sequence as Seq
class Listy t where
    listySplit   :: t a -> Maybe (a, t a)
    listyUnsplit :: a -> t a -> t a

instance Listy [] where
    listySplit (a:b) = Just (a,b)
    listySplit _ = Nothing
    listyUnsplit = (:)
instance Listy Seq.Seq where
    listySplit (Seq.viewl -> a Seq.:< b) = Just (a,b)
    listySplit _ = Nothing
    listyUnsplit = (Seq.<|)

pattern L x xs <- (listySplit -> Just (x,xs))

-- example
sum1 :: (Listy t, Num a) => t a -> a
sum1 (L x xs) = x + sum1 xs
sum1 _ = 0

I don't see a way to make the expression `L x xs' stand for
listyUnsplit. Maybe someone else can figure this out, or this is a
forthcoming feature?

--
Adam

On Tue, Jan 21, 2014 at 5:31 AM, Alejandro Serrano Mena
<trupill at gmail.com> wrote:
> Dear haskell-cafe,
> I've read in Reddit that pattern synonyms have been merged in GHC HEAD
> [http://www.reddit.com/r/haskell/comments/1vpaey/pattern_synonyms_merged_into_ghchead/].
>
> I would like to know whether associated patterns, that is, patterns which
> come under the umbrella of a type class, have also been implemented.
>
> I think that associated patterns would fill the gap in difference of
> features between type classes and common data types. For plain data types,
> you can declare both functions and patterns (either via constructors or now
> via pattern synonyms). However, you can only declare functions (either
> term-level or type-level) in type classes. This means that the pattern match
> mechanism, very useful to get clear code, is not useful if you want to use
> type classes.
>
> Alejandro.
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list