Types for Data.Sequence pattern synonyms
David Feuer
david.feuer at gmail.com
Wed Apr 20 16:39:19 UTC 2016
As discussed, I plan to add pattern synonyms Empty, :<|, and :|> to
make working with sequences more convenient. The remaining question is
what types they should have. From the Data.Sequence standpoint, the
best thing would be to make them work *only* for Seq, so that the Seq
type will be inferred from their use. However, modules using multiple
sequence types might benefit from more flexibility, via ad hoc
classes. This, however, requires that something else pin down the
sequence type, and could cause more confusing error messages. I'm
leaning toward the simple, monomorphic approach, but I figured I
should ask here in case anyone disagrees strongly.
{-# LANGUAGE PatternSynonyms, ScopedTypeVariables,
MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances,
ViewPatterns #-}
module Patt where
import Data.Sequence as S
import Prelude as P
class FastFront x xs | xs -> x where
fcons :: x -> xs -> xs
fviewl :: xs -> ViewLS x xs
class FastRear x xs | xs -> x where
fsnoc :: xs -> x -> xs
fviewr :: xs -> ViewRS x xs
class FastEmpty x xs | xs -> x where
fMkEmpty :: xs
fIsEmpty :: xs -> Bool
instance FastFront a (Seq a) where
fcons = (<|)
fviewl xs = case viewl xs of
EmptyL -> EmptyLS
y :< ys -> ConsLS y ys
instance FastFront a [a] where
fcons = (:)
fviewl [] = EmptyLS
fviewl (x : xs) = ConsLS x xs
instance FastRear a (Seq a) where
fsnoc = (|>)
fviewr xs = case viewr xs of
EmptyR -> EmptyRS
ys :> y -> SnocRS ys y
instance FastEmpty a (Seq a) where
fMkEmpty = mempty
fIsEmpty = S.null
instance FastEmpty a [a] where
fMkEmpty = []
fIsEmpty = P.null
data ViewLS x xs = EmptyLS | ConsLS x xs
data ViewRS x xs = EmptyRS | SnocRS xs x
pattern x :<| xs <- (fviewl -> ConsLS x xs) where
x :<| xs = fcons x xs
pattern xs :|> x <- (fviewr -> SnocRS xs x) where
xs :|> x = fsnoc xs x
pattern Empty <- (fIsEmpty -> True) where
Empty = fMkEmpty
More information about the Libraries
mailing list