Types for Data.Sequence pattern synonyms

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

On Wed, 20 Apr 2016, David Feuer wrote:
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.
I prefer that Data.Sequence exports functions with the Seq type and that generalized functions are exported by a different module that is intended for generalization. The specific and general infix operators could have the same symbol and the user could choose via the module import which one to use.

On 21 April 2016 at 02:55, Henning Thielemann
On Wed, 20 Apr 2016, David Feuer wrote:
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.
I prefer that Data.Sequence exports functions with the Seq type and that generalized functions are exported by a different module that is intended for generalization. The specific and general infix operators could have the same symbol and the user could choose via the module import which one to use.
+1 -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

Very +1 for only exporting Seq-specific ones from Data.Sequence. On Wed, Apr 20, 2016 at 4:49 PM Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
On 21 April 2016 at 02:55, Henning Thielemann
wrote: On Wed, 20 Apr 2016, David Feuer wrote:
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.
I prefer that Data.Sequence exports functions with the Seq type and that generalized functions are exported by a different module that is intended for generalization. The specific and general infix operators could have
the
same symbol and the user could choose via the module import which one to use.
+1
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
participants (4)
-
Brent Yorgey
-
David Feuer
-
Henning Thielemann
-
Ivan Lazar Miljenovic