From ndospark320 at gmail.com Sat Apr 10 22:48:42 2021 From: ndospark320 at gmail.com (Dannyu NDos) Date: Sun, 11 Apr 2021 07:48:42 +0900 Subject: Generalize indexing function Message-ID: I noticed that the list indexing function, (!!), is generalizable. I'm showing some instances: {-# LANGUAGE MultiParamTypeClasses #-} import Data.Complex import Data.Functor.Compose import Data.Functor.Product import Data.Functor.Sum import Data.List.NonEmpty import Data.Maybe infix 9 !? infixl 9 ! class Indexable i a where (!?) :: i b -> a -> Maybe b (!) :: Indexable i a => i b -> a -> b x ! n = fromJust (x !? n) instance Indexable [] Int where [] !? _ = Nothing (x:_) !? 0 = Just x (_:xs) !? n | n < 0 = Nothing | otherwise = xs !? (n-1) instance Indexable ((->) a) (Identity a) where f !? Identity n = Just (f n) instance Indexable ((,) a) () where (_,x) !? _ = Just x instance Indexable Complex Bool where (x :+ _) !? False = Just x (_ :+ y) !? True = Just y instance (Indexable f a, Indexable g b) => Indexable (Compose f g) (a,b) where Compose z !? (m,n) = do y <- z !? m y !? n instance (Indexable f a, Indexable g b) => Indexable (Product f g) (Either a b) where Pair x _ !? Left m = x !? m Pair _ y !? Right n = y !? n instance (Indexable f a, Indexable g a) => Indexable (Sum f g) (Identity a) where InL x !? Identity n = x !? n InR y !? Identity n = y !? n instance Indexable NonEmpty Int where (x :| xs) !? n = (x : xs) !? n -------------- next part -------------- An HTML attachment was scrubbed... URL: From keith.wygant at gmail.com Sat Apr 10 22:57:21 2021 From: keith.wygant at gmail.com (Keith) Date: Sat, 10 Apr 2021 22:57:21 +0000 Subject: Generalize indexing function In-Reply-To: References: Message-ID: Might be more convenient to use an associated type family. And in practice, using types like '()' and 'Bool' as indexes is not super useful when you've already committed to using 'Int' as the (partial) index type of '[]'. - Keith Sent from my phone with K-9 Mail. On April 10, 2021 10:48:42 PM UTC, Dannyu NDos wrote: >I noticed that the list indexing function, (!!), is generalizable. I'm >showing some instances: > >{-# LANGUAGE MultiParamTypeClasses #-} > >import Data.Complex >import Data.Functor.Compose >import Data.Functor.Product >import Data.Functor.Sum >import Data.List.NonEmpty >import Data.Maybe > >infix 9 !? >infixl 9 ! > >class Indexable i a where > (!?) :: i b -> a -> Maybe b > >(!) :: Indexable i a => i b -> a -> b >x ! n = fromJust (x !? n) > >instance Indexable [] Int where > [] !? _ = Nothing > (x:_) !? 0 = Just x > (_:xs) !? n > | n < 0 = Nothing > | otherwise = xs !? (n-1) > >instance Indexable ((->) a) (Identity a) where > f !? Identity n = Just (f n) > >instance Indexable ((,) a) () where > (_,x) !? _ = Just x > >instance Indexable Complex Bool where > (x :+ _) !? False = Just x > (_ :+ y) !? True = Just y > >instance (Indexable f a, Indexable g b) => Indexable (Compose f g) (a,b) >where > Compose z !? (m,n) = do > y <- z !? m > y !? n > >instance (Indexable f a, Indexable g b) => Indexable (Product f g) (Either >a b) where > Pair x _ !? Left m = x !? m > Pair _ y !? Right n = y !? n > >instance (Indexable f a, Indexable g a) => Indexable (Sum f g) (Identity a) >where > InL x !? Identity n = x !? n > InR y !? Identity n = y !? n > >instance Indexable NonEmpty Int where > (x :| xs) !? n = (x : xs) !? n -------------- next part -------------- An HTML attachment was scrubbed... URL: From lemming at henning-thielemann.de Sun Apr 11 00:14:33 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Sun, 11 Apr 2021 02:14:33 +0200 (CEST) Subject: Generalize indexing function In-Reply-To: References: Message-ID: On Sat, 10 Apr 2021, Keith wrote: > Might be more convenient to use an associated type family. I have done something similar here: http://hackage.haskell.org/package/comfort-array From carter.schonwald at gmail.com Sun Apr 11 03:18:12 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sat, 10 Apr 2021 23:18:12 -0400 Subject: Generalize indexing function In-Reply-To: References: Message-ID: I really like the landscape of indexinbg flavores you've included henning! i've def thought about similar stuff, and its nice to see it fleshed out :) On Sat, Apr 10, 2021 at 8:15 PM Henning Thielemann < lemming at henning-thielemann.de> wrote: > > On Sat, 10 Apr 2021, Keith wrote: > > > Might be more convenient to use an associated type family. > > I have done something similar here: > http://hackage.haskell.org/package/comfort-array > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From george at wils.online Sun Apr 11 06:32:04 2021 From: george at wils.online (George Wilson) Date: Sun, 11 Apr 2021 16:32:04 +1000 Subject: Generalize indexing function In-Reply-To: References: Message-ID: Does this class have any laws? From what I can tell, this is useful only as an overloading of some identifiers - I don't see what useful functions I could write in terms of this as an abstraction. Cheers, George On Sun, 11 Apr 2021, 08:49 Dannyu NDos, wrote: > I noticed that the list indexing function, (!!), is generalizable. I'm > showing some instances: > > {-# LANGUAGE MultiParamTypeClasses #-} > > import Data.Complex > import Data.Functor.Compose > import Data.Functor.Product > import Data.Functor.Sum > import Data.List.NonEmpty > import Data.Maybe > > infix 9 !? > infixl 9 ! > > class Indexable i a where > (!?) :: i b -> a -> Maybe b > > (!) :: Indexable i a => i b -> a -> b > x ! n = fromJust (x !? n) > > instance Indexable [] Int where > [] !? _ = Nothing > (x:_) !? 0 = Just x > (_:xs) !? n > | n < 0 = Nothing > | otherwise = xs !? (n-1) > > instance Indexable ((->) a) (Identity a) where > f !? Identity n = Just (f n) > > instance Indexable ((,) a) () where > (_,x) !? _ = Just x > > instance Indexable Complex Bool where > (x :+ _) !? False = Just x > (_ :+ y) !? True = Just y > > instance (Indexable f a, Indexable g b) => Indexable (Compose f g) (a,b) > where > Compose z !? (m,n) = do > y <- z !? m > y !? n > > instance (Indexable f a, Indexable g b) => Indexable (Product f g) (Either > a b) where > Pair x _ !? Left m = x !? m > Pair _ y !? Right n = y !? n > > instance (Indexable f a, Indexable g a) => Indexable (Sum f g) (Identity > a) where > InL x !? Identity n = x !? n > InR y !? Identity n = y !? n > > instance Indexable NonEmpty Int where > (x :| xs) !? n = (x : xs) !? n > > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From tanuki at gmail.com Sun Apr 11 07:01:47 2021 From: tanuki at gmail.com (Akhra Gannon) Date: Sun, 11 Apr 2021 00:01:47 -0700 Subject: Generalize indexing function In-Reply-To: References: Message-ID: It's distributive under IsList. fromList (xs !! n) == (fromList xs) !! n On Sat, Apr 10, 2021, 11:33 PM George Wilson wrote: > Does this class have any laws? From what I can tell, this is useful only > as an overloading of some identifiers - I don't see what useful functions I > could write in terms of this as an abstraction. > > Cheers, > George > > On Sun, 11 Apr 2021, 08:49 Dannyu NDos, wrote: > >> I noticed that the list indexing function, (!!), is generalizable. I'm >> showing some instances: >> >> {-# LANGUAGE MultiParamTypeClasses #-} >> >> import Data.Complex >> import Data.Functor.Compose >> import Data.Functor.Product >> import Data.Functor.Sum >> import Data.List.NonEmpty >> import Data.Maybe >> >> infix 9 !? >> infixl 9 ! >> >> class Indexable i a where >> (!?) :: i b -> a -> Maybe b >> >> (!) :: Indexable i a => i b -> a -> b >> x ! n = fromJust (x !? n) >> >> instance Indexable [] Int where >> [] !? _ = Nothing >> (x:_) !? 0 = Just x >> (_:xs) !? n >> | n < 0 = Nothing >> | otherwise = xs !? (n-1) >> >> instance Indexable ((->) a) (Identity a) where >> f !? Identity n = Just (f n) >> >> instance Indexable ((,) a) () where >> (_,x) !? _ = Just x >> >> instance Indexable Complex Bool where >> (x :+ _) !? False = Just x >> (_ :+ y) !? True = Just y >> >> instance (Indexable f a, Indexable g b) => Indexable (Compose f g) (a,b) >> where >> Compose z !? (m,n) = do >> y <- z !? m >> y !? n >> >> instance (Indexable f a, Indexable g b) => Indexable (Product f g) >> (Either a b) where >> Pair x _ !? Left m = x !? m >> Pair _ y !? Right n = y !? n >> >> instance (Indexable f a, Indexable g a) => Indexable (Sum f g) (Identity >> a) where >> InL x !? Identity n = x !? n >> InR y !? Identity n = y !? n >> >> instance Indexable NonEmpty Int where >> (x :| xs) !? n = (x : xs) !? n >> >> >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From lemming at henning-thielemann.de Sun Apr 11 10:03:04 2021 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Sun, 11 Apr 2021 12:03:04 +0200 (CEST) Subject: Generalize indexing function In-Reply-To: References: Message-ID: <91dbe53-ee-2e8a-4528-78ca9342439f@henning-thielemann.de> On Sun, 11 Apr 2021, Akhra Gannon wrote: > It's distributive under IsList. > fromList (xs !! n) == (fromList xs) !! n fromList (xs !! n) ? I think, xs!!n is a single element. From tanuki at gmail.com Sun Apr 11 10:11:55 2021 From: tanuki at gmail.com (Akhra Gannon) Date: Sun, 11 Apr 2021 03:11:55 -0700 Subject: Generalize indexing function In-Reply-To: <91dbe53-ee-2e8a-4528-78ca9342439f@henning-thielemann.de> References: <91dbe53-ee-2e8a-4528-78ca9342439f@henning-thielemann.de> Message-ID: Yeah, I mis-composed that. Pretty sure there's a formulation around take/head that works but I'm clearly not in a headspace to find it! On Sun, Apr 11, 2021, 3:03 AM Henning Thielemann < lemming at henning-thielemann.de> wrote: > > On Sun, 11 Apr 2021, Akhra Gannon wrote: > > > It's distributive under IsList. > > fromList (xs !! n) == (fromList xs) !! n > > fromList (xs !! n) ? > > I think, xs!!n is a single element. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Sun Apr 11 10:35:53 2021 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Sun, 11 Apr 2021 11:35:53 +0100 Subject: Generalize indexing function In-Reply-To: <91dbe53-ee-2e8a-4528-78ca9342439f@henning-thielemann.de> References: <91dbe53-ee-2e8a-4528-78ca9342439f@henning-thielemann.de> Message-ID: <20210411103553.GB649@cloudinit-builder> On Sun, Apr 11, 2021 at 12:03:04PM +0200, Henning Thielemann wrote: > On Sun, 11 Apr 2021, Akhra Gannon wrote: > > > It's distributive under IsList. > > fromList (xs !! n) == (fromList xs) !! n > > fromList (xs !! n) ? > > I think, xs!!n is a single element. Presumably `xs !! n == fromList xs !! n` From keith.wygant at gmail.com Sun Apr 11 15:28:13 2021 From: keith.wygant at gmail.com (Keith) Date: Sun, 11 Apr 2021 15:28:13 +0000 Subject: Generalize indexing function In-Reply-To: <20210411103553.GB649@cloudinit-builder> References: <91dbe53-ee-2e8a-4528-78ca9342439f@henning-thielemann.de> <20210411103553.GB649@cloudinit-builder> Message-ID: `xs !! () == fromList xs !! ()` seems to be a type error? -- Keith Sent from my phone with K-9 Mail. On April 11, 2021 10:35:53 AM UTC, Tom Ellis wrote: >On Sun, Apr 11, 2021 at 12:03:04PM +0200, Henning Thielemann wrote: >> On Sun, 11 Apr 2021, Akhra Gannon wrote: >> >> > It's distributive under IsList. >> > fromList (xs !! n) == (fromList xs) !! n >> >> fromList (xs !! n) ? >> >> I think, xs!!n is a single element. > >Presumably `xs !! n == fromList xs !! n` >_______________________________________________ >Libraries mailing list >Libraries at haskell.org >http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries -------------- next part -------------- An HTML attachment was scrubbed... URL: From keith.wygant at gmail.com Sun Apr 11 15:33:55 2021 From: keith.wygant at gmail.com (Keith) Date: Sun, 11 Apr 2021 15:33:55 +0000 Subject: Generalize indexing function In-Reply-To: <20210411103553.GB649@cloudinit-builder> References: <91dbe53-ee-2e8a-4528-78ca9342439f@henning-thielemann.de> <20210411103553.GB649@cloudinit-builder> Message-ID: <8A3348AE-A309-4592-9A1F-DB9265037AD4@gmail.com> Maybe `xs !! n == fromList xs !! fromEnum n`? -- Keith Sent from my phone with K-9 Mail. On April 11, 2021 10:35:53 AM UTC, Tom Ellis wrote: >On Sun, Apr 11, 2021 at 12:03:04PM +0200, Henning Thielemann wrote: >> On Sun, 11 Apr 2021, Akhra Gannon wrote: >> >> > It's distributive under IsList. >> > fromList (xs !! n) == (fromList xs) !! n >> >> fromList (xs !! n) ? >> >> I think, xs!!n is a single element. > >Presumably `xs !! n == fromList xs !! n` >_______________________________________________ >Libraries mailing list >Libraries at haskell.org >http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries -------------- next part -------------- An HTML attachment was scrubbed... URL: From keith.wygant at gmail.com Sun Apr 11 15:41:35 2021 From: keith.wygant at gmail.com (Keith) Date: Sun, 11 Apr 2021 15:41:35 +0000 Subject: Generalize indexing function In-Reply-To: <20210411103553.GB649@cloudinit-builder> References: <91dbe53-ee-2e8a-4528-78ca9342439f@henning-thielemann.de> <20210411103553.GB649@cloudinit-builder> Message-ID: <535D494D-9EA7-44A8-BCE3-AFE213269ED3@gmail.com> Sorry to spam, just realized that destroys the Map and (->) instances. -- Keith Sent from my phone with K-9 Mail. On April 11, 2021 10:35:53 AM UTC, Tom Ellis wrote: >On Sun, Apr 11, 2021 at 12:03:04PM +0200, Henning Thielemann wrote: >> On Sun, 11 Apr 2021, Akhra Gannon wrote: >> >> > It's distributive under IsList. >> > fromList (xs !! n) == (fromList xs) !! n >> >> fromList (xs !! n) ? >> >> I think, xs!!n is a single element. > >Presumably `xs !! n == fromList xs !! n` >_______________________________________________ >Libraries mailing list >Libraries at haskell.org >http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries -------------- next part -------------- An HTML attachment was scrubbed... URL: