Re: [Haskell-cafe] selectively allow alternatives in a sum type

Trees that grow is essentially this, but using type families.
data Foo ksi = LeftFoo !(XLeftFoo ksi) !A | RightFoo !(XRightFoo ksi) !B
type family XLeftFoo ksi :: Type type family XRightFoo ksi :: Type
Then you can define
data Both type instance XLeftFoo Both = () type instance XRightFoo Both = ()
or
data OnlyLeft type instance XLeftFoo OnlyLeft = () type instance XRightFoo OnlyLeft = Void
---
Third option is to simply have parametrized data:
data Foo b = LeftFoo !A | RIghtFoo !b
type FooBoth = Foo B type FooOnlyLeft = Foo Void
---
Sometimes I prefer a higher-kinded data approach, especially if there is very little variants needed, and they are "uniform" (e.g. second variant doesn't have some fields). Yet, sometimes simple parameterized data is simplest approach (especially as you get stuff for free by deriving Traversable!).
On the other hand, if type is big and have many uniform extension points (even if there are few different combinations), then HKD becomes boilerplate heavy as well. The drawback of TTG, is that writing polymorphic code (i.e. which work for any or some `ksi`s) is not very fun: a lot of equality constraints etc.
- Oleg
So I re-discovered Trees that Grow sans the trick of using type families to name particular combinations of parameters. Hooray Najd, and thanks Oleg for bringing this up. Olaf

To avoid actually realizing those boring fields in memory, use an unlifted
newtype.
type VoidUnit# :: TYPE ('TupleRep '[])
newtype VoidUnit# = VoidUnit# VoidUnit#
absurd# :: VoidUnit# -> a
absurd# (VoidUnit# v) = absurd# v
Unfortunately, GHC's pattern checker isn't smart enough to see by itself
that VoidUnit# is uninhabited, even though that's pretty obvious to a human.
TTG also has coercion problems thanks to the type families. *Sigh*
On Wed, Aug 31, 2022, 4:48 PM Olaf Klinke
Trees that grow is essentially this, but using type families.
data Foo ksi = LeftFoo !(XLeftFoo ksi) !A | RightFoo !(XRightFoo ksi) !B
type family XLeftFoo ksi :: Type type family XRightFoo ksi :: Type
Then you can define
data Both type instance XLeftFoo Both = () type instance XRightFoo Both = ()
or
data OnlyLeft type instance XLeftFoo OnlyLeft = () type instance XRightFoo OnlyLeft = Void
---
Third option is to simply have parametrized data:
data Foo b = LeftFoo !A | RIghtFoo !b
type FooBoth = Foo B type FooOnlyLeft = Foo Void
---
Sometimes I prefer a higher-kinded data approach, especially if there is very little variants needed, and they are "uniform" (e.g. second variant doesn't have some fields). Yet, sometimes simple parameterized data is simplest approach (especially as you get stuff for free by deriving Traversable!).
On the other hand, if type is big and have many uniform extension points (even if there are few different combinations), then HKD becomes boilerplate heavy as well. The drawback of TTG, is that writing polymorphic code (i.e. which work for any or some `ksi`s) is not very fun: a lot of equality constraints etc.
- Oleg
So I re-discovered Trees that Grow sans the trick of using type families to name particular combinations of parameters. Hooray Najd, and thanks Oleg for bringing this up.
Olaf
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Sometimes I feel the need to selectively allow or disallow alternatives
This seems like the kind of lightweight property that Liquid Haskell (a GHC plugin) is especially suited for. Here's a small example of "at some places in the program we want the type system to enforce that only the constructor LeftFoo can be used." data Foo = LeftFoo !Int | RightFoo !Char {-@ measure isLeftFoo @-} isLeftFoo :: Foo -> Bool isLeftFoo LeftFoo{} = True isLeftFoo _ = False {-@ takesOnlyLeftFoo :: {x:Foo | isLeftFoo x} -> Int @-} takesOnlyLeftFoo :: Foo -> Int takesOnlyLeftFoo (LeftFoo i) = i I've taken Olaf's hypothetical Foo and swapped in Int for A and Char for B, defined a function *isLeftFoo* that returns True for LeftFoo-constructed Foos, and I call *isLeftFoo* in the type of a function that is meant to only be called with LeftFoo values. This syntax in the mushroom-at-symbol comments is a refinement type. It has the same structure as the haskell type `Foo -> Int` but adds a precondition on the input that *isLeftFoo* returns True. When you compile your project with Liquid Haskell, the precondition will be checked at compile time by checking that callers establish the fact on any value they pass into *takesOnlyLeftFoo*.

Chiming in here, maybe I missed something. Liquid Haskell is great, but in this
case, in my opinion, easier is better:
newtype LeftFoo = LeftFoo !Int
newtype RightFoo = RightFoo !Char
data Foo = LFoo LeftFoo | RFoo RightFoo – Probably with strictness annotations.
isLeftFoo :: Foo -> Bool
isLeftFoo (LFoo _) = True
isLeftFoo _ = False
takesOnlyLeftFoo :: LeftFoo -> Int
takesOnlyLeftFoo (LeftFoo i) = i
Dominik
Patrick L Redmond via Haskell-Cafe
Sometimes I feel the need to selectively allow or disallow alternatives
This seems like the kind of lightweight property that Liquid Haskell (a GHC plugin) is especially suited for. Here’s a small example of “at some places in the program we want the type system to enforce that only the constructor LeftFoo can be used.”
data Foo = LeftFoo !Int | RightFoo !Char
{-@ measure isLeftFoo @-} isLeftFoo :: Foo -> Bool isLeftFoo LeftFoo{} = True isLeftFoo _ = False
{-@ takesOnlyLeftFoo :: {x:Foo | isLeftFoo x} -> Int @-} takesOnlyLeftFoo :: Foo -> Int takesOnlyLeftFoo (LeftFoo i) = i
I’ve taken Olaf’s hypothetical Foo and swapped in Int for A and Char for B, defined a function isLeftFoo that returns True for LeftFoo-constructed Foos, and I call isLeftFoo in the type of a function that is meant to only be called with LeftFoo values.
This syntax in the mushroom-at-symbol comments is a refinement type. It has the same structure as the haskell type `Foo -> Int` but adds a precondition on the input that isLeftFoo returns True. When you compile your project with Liquid Haskell, the precondition will be checked at compile time by checking that callers establish the fact on any value they pass into takesOnlyLeftFoo.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On 01-09-22 16:33, Dominik Schrempf wrote:
Chiming in here, maybe I missed something. Liquid Haskell is great, but in this case, in my opinion, easier is better:
newtype LeftFoo = LeftFoo !Int
newtype RightFoo = RightFoo !Char
data Foo = LFoo LeftFoo | RFoo RightFoo – Probably with strictness annotations.
isLeftFoo :: Foo -> Bool isLeftFoo (LFoo _) = True isLeftFoo _ = False
takesOnlyLeftFoo :: LeftFoo -> Int takesOnlyLeftFoo (LeftFoo i) = i
Dominik
Chiming in here too. I do this all the time if the subpart is to be used on 2 or more places. Easiest way to do this without extensions. -- Rubén. (pgp: 1E88 3AC4 89EB FA22)

I made a TH function earlier this year to produce types for constructors:
data Foo = LeftFoo !Int | RightFoo !Char
deriving Show
$(constructorType 'LeftFoo)
deriving instance Show LeftFooC
In a repl you can see it generates a type with a single constructor, an
introducer, and an eliminator.
*Main> :browse
type Foo :: *
data Foo = LeftFoo !Int | RightFoo !Char
type LeftFooC :: *
data LeftFooC = LeftFooC Int
introLeftFooC :: Foo -> Maybe LeftFooC
elimLeftFooC :: LeftFooC -> Foo
*Main> introLeftFooC (RightFoo 'a')
Nothing
*Main> introLeftFooC (LeftFoo 123)
Just (LeftFooC 123)
*Main> elimLeftFooC $ LeftFooC 456
LeftFoo 456
If you find that useful, I ripped it out of my other repo and pasted it
here: https://gist.github.com/plredmond/5fd15fb388647b248de87693542d2adb
On Thu, Sep 1, 2022 at 3:54 PM Ruben Astudillo
On 01-09-22 16:33, Dominik Schrempf wrote:
Chiming in here, maybe I missed something. Liquid Haskell is great, but in this case, in my opinion, easier is better:
newtype LeftFoo = LeftFoo !Int
newtype RightFoo = RightFoo !Char
data Foo = LFoo LeftFoo | RFoo RightFoo – Probably with strictness annotations.
isLeftFoo :: Foo -> Bool isLeftFoo (LFoo _) = True isLeftFoo _ = False
takesOnlyLeftFoo :: LeftFoo -> Int takesOnlyLeftFoo (LeftFoo i) = i
Dominik
Chiming in here too. I do this all the time if the subpart is to be used on 2 or more places. Easiest way to do this without extensions.
-- Rubén. (pgp: 1E88 3AC4 89EB FA22)
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

In my real use case, things are not as simple as the example Foo, of course. There are fields of the same type, distributed across the choices, but some are optional in some choices and mandatory in others. Rank-1 parameters permit a range including, but not limited, to Indentity -- mandatory Maybe -- optional Const () -- missing Const Void -- constructor disallowed e.g. data Bar left right = LeftBar A (left O) | RightBar A B (right O) type OptionalLeftMandatoryRight = Bar Maybe Identity -- encodes: "If B is present so must be O, but if not, O is optional". type OnlyA = Bar (Const ()) (Const Void) -- isomorphic to A getO :: Applicative f => Bar f Identity -> f O getO (LeftBar _ o) = o getO (RightBar _ _ (Identity o)) = pure o getA :: Bar left right -> A getA (LeftBar a _) = a getA (RightBar a _ _) = a With distinct data types for LeftBar and RightBar, the functions getO, getA in their generality would only be possible via type classes. In some sense, the type parameters act as an explicit type class dictionary. I believe this is in the spirit of Trees that Grow, where the combination (left,right) = (Maybe,Identity) would be encoded in a type family. Olaf On Thu, 2022-09-01 at 22:33 +0200, Dominik Schrempf wrote:
Chiming in here, maybe I missed something. Liquid Haskell is great, but in this case, in my opinion, easier is better:
newtype LeftFoo = LeftFoo !Int
newtype RightFoo = RightFoo !Char
data Foo = LFoo LeftFoo | RFoo RightFoo – Probably with strictness annotations.
isLeftFoo :: Foo -> Bool isLeftFoo (LFoo _) = True isLeftFoo _ = False
takesOnlyLeftFoo :: LeftFoo -> Int takesOnlyLeftFoo (LeftFoo i) = i
Dominik
Patrick L Redmond via Haskell-Cafe
writes: Sometimes I feel the need to selectively allow or disallow alternatives
This seems like the kind of lightweight property that Liquid Haskell (a GHC plugin) is especially suited for. Here’s a small example of “at some places in the program we want the type system to enforce that only the constructor LeftFoo can be used.”
data Foo = LeftFoo !Int | RightFoo !Char
{-@ measure isLeftFoo @-} isLeftFoo :: Foo -> Bool isLeftFoo LeftFoo{} = True isLeftFoo _ = False
{-@ takesOnlyLeftFoo :: {x:Foo | isLeftFoo x} -> Int @-} takesOnlyLeftFoo :: Foo -> Int takesOnlyLeftFoo (LeftFoo i) = i
I’ve taken Olaf’s hypothetical Foo and swapped in Int for A and Char for B, defined a function isLeftFoo that returns True for LeftFoo-constructed Foos, and I call isLeftFoo in the type of a function that is meant to only be called with LeftFoo values.
This syntax in the mushroom-at-symbol comments is a refinement type. It has the same structure as the haskell type `Foo -> Int` but adds a precondition on the input that isLeftFoo returns True. When you compile your project with Liquid Haskell, the precondition will be checked at compile time by checking that callers establish the fact on any value they pass into takesOnlyLeftFoo.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
participants (5)
-
David Feuer
-
Dominik Schrempf
-
Olaf Klinke
-
Patrick L Redmond
-
Ruben Astudillo