selectively allow alternatives in a sum type

Dear Café, Is there prior art/existing packages for the following? Is it maybefunctional programming folklore? Is it a sign of bad program design? Sometimes I feel the need to selectively allow or disallow alternatives in a sum type. That is, suppose we have a sum type data Foo = LeftFoo !A | RightFoo !B and at some places in the program we want the type system to enforce that only the constructor LeftFoo can be used. My solution would be to use a strict version of Data.Functor.Const and make the type higher rank: newtype Const' a b = Const' !a -- Const' Void b ~ Void -- Const' () b ~ () data Foo' f = LeftFoo' !A | RightFoo' !(f B) type Foo = Foo' Identity type LeftFoo = Foo' (Const' Void) -- can not construct a RightFoo' The advantage over defining LeftFoo as an entirely different type is that Foo and LeftFoo can share functions operating entirely on the left option. Olaf

Disregard Const' below, Data.Functor.Const as a newtype is always
strict, as is Identity.
That also ensures Foo' Identity is isomorphic to the original Foo.
Apologies for the noise.
Olaf
-------- Forwarded Message --------
From: 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 On 30.8.2022 16.30, Olaf Klinke wrote:
Dear Café,
Is there prior art/existing packages for the following? Is it maybefunctional programming folklore? Is it a sign of bad program design? Sometimes I feel the need to selectively allow or disallow alternatives in a sum type. That is, suppose we have a sum type
data Foo = LeftFoo !A | RightFoo !B
and at some places in the program we want the type system to enforce that only the constructor LeftFoo can be used. My solution would be to use a strict version of Data.Functor.Const and make the type higher rank:
newtype Const' a b = Const' !a -- Const' Void b ~ Void -- Const' () b ~ ()
data Foo' f = LeftFoo' !A | RightFoo' !(f B) type Foo = Foo' Identity type LeftFoo = Foo' (Const' Void) -- can not construct a RightFoo'
The advantage over defining LeftFoo as an entirely different type is that Foo and LeftFoo can share functions operating entirely on the left option.
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.

On Tue, 30 Aug 2022, Olaf Klinke wrote:
Is there prior art/existing packages for the following? Is it maybefunctional programming folklore? Is it a sign of bad program design? Sometimes I feel the need to selectively allow or disallow alternatives in a sum type. That is, suppose we have a sum type
data Foo = LeftFoo !A | RightFoo !B
and at some places in the program we want the type system to enforce that only the constructor LeftFoo can be used.
We could use a type variable and type classes. f :: (ContainsA x) => ... x ... g :: (ContainsA x, ContainsB x) => ... x ... where the classes ContainsA and ContainsB provide accessors to the summands. Then x could be either A or B or Either A B and so on and there would be instances instance ContainsA A instance ContainsB B instance (a ~ A) => ContainsA (Either a b) instance (b ~ B) => ContainsB (Either a b)

Hi, In this specific case you could use a GADT: data Foo (only_left :: Bool) where LeftFoo :: A -> Foo only_left RightFoo :: B -> Foo 'False onlyLeft :: Foo 'True -> String onlyLeft = \case LeftFoo _a -> "an A" anyFoo :: Foo a -> String anyFoo = \case LeftFoo _a -> "an A" RightFoo _b -> "a B" But it isn't very modular. A more heavyweight alternative is to use some kind of variants instead. See https://docs.haskus.org/variant.html for example where I describe my implementation. I wish we had more compiler support for constructor polymorphism like this though. Sylvain On 30/08/2022 15:30, Olaf Klinke wrote:
Dear Café,
Is there prior art/existing packages for the following? Is it maybefunctional programming folklore? Is it a sign of bad program design? Sometimes I feel the need to selectively allow or disallow alternatives in a sum type. That is, suppose we have a sum type
data Foo = LeftFoo !A | RightFoo !B
and at some places in the program we want the type system to enforce that only the constructor LeftFoo can be used. My solution would be to use a strict version of Data.Functor.Const and make the type higher rank:
newtype Const' a b = Const' !a -- Const' Void b ~ Void -- Const' () b ~ ()
data Foo' f = LeftFoo' !A | RightFoo' !(f B) type Foo = Foo' Identity type LeftFoo = Foo' (Const' Void) -- can not construct a RightFoo'
The advantage over defining LeftFoo as an entirely different type is that Foo and LeftFoo can share functions operating entirely on the left option.
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.

One downside of this *particular* formulation is that it doesn't play well
with Coercible.
On Tue, Aug 30, 2022, 9:31 AM Olaf Klinke
Dear Café,
Is there prior art/existing packages for the following? Is it maybefunctional programming folklore? Is it a sign of bad program design? Sometimes I feel the need to selectively allow or disallow alternatives in a sum type. That is, suppose we have a sum type
data Foo = LeftFoo !A | RightFoo !B
and at some places in the program we want the type system to enforce that only the constructor LeftFoo can be used. My solution would be to use a strict version of Data.Functor.Const and make the type higher rank:
newtype Const' a b = Const' !a -- Const' Void b ~ Void -- Const' () b ~ ()
data Foo' f = LeftFoo' !A | RightFoo' !(f B) type Foo = Foo' Identity type LeftFoo = Foo' (Const' Void) -- can not construct a RightFoo'
The advantage over defining LeftFoo as an entirely different type is that Foo and LeftFoo can share functions operating entirely on the left option.
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.

In university, I wrote a bunch of CPUs in clash/haskell for an FPGA CPU
design class. In one pipelined scalar CPU, I had a number of CPU
instructions, and as the instructions moved down the pipe, the set of
allowed instructions would change. E.g. a memory read instruction would
eventually get changed to a register write instruction, and there was no
reason to permit a memory read instruction to be representable after the
memory read stage of the pipeline.
I vaguely recall using a GADT+typeclass strategy something like this to
check this at compile time:
data Stage = F | D | R | X -- fetch/decode/read/execute
data Instruction allowed where
MemRead :: MemAddress -> Register -> Instruction [F,D,R]
RegWrite :: Word64 -> Register -> Instruction [F,D,R,X]
...
-- Type-level list membership
executeR :: (Contains R in, Contains X out) => ReadContext -> Instruction
in -> (ReadResult, Instruction out)
executeR ctx (MemRead a r) = ...
executeR ctx (RegWrite w r) = ...
executeX :: Contains X in => ExecutionContext -> Instruction in ->
ExecutionResult
executeX ctx (RegWrite w r) = ...
If I'm remembering this correctly, Haskell's `GADTs meet their match` based
type checker was smart enough to know when a constructor was not allowed
for a function,
and would not give me spurious exhaustiveness warnings.
I think I had another strategy still using typeclasses, but not using
type-level lists/sets, but I can't remember what it would have been.
Will
On Tue, Aug 30, 2022 at 11:09 AM David Feuer
One downside of this *particular* formulation is that it doesn't play well with Coercible.
On Tue, Aug 30, 2022, 9:31 AM Olaf Klinke
wrote: Dear Café,
Is there prior art/existing packages for the following? Is it maybefunctional programming folklore? Is it a sign of bad program design? Sometimes I feel the need to selectively allow or disallow alternatives in a sum type. That is, suppose we have a sum type
data Foo = LeftFoo !A | RightFoo !B
and at some places in the program we want the type system to enforce that only the constructor LeftFoo can be used. My solution would be to use a strict version of Data.Functor.Const and make the type higher rank:
newtype Const' a b = Const' !a -- Const' Void b ~ Void -- Const' () b ~ ()
data Foo' f = LeftFoo' !A | RightFoo' !(f B) type Foo = Foo' Identity type LeftFoo = Foo' (Const' Void) -- can not construct a RightFoo'
The advantage over defining LeftFoo as an entirely different type is that Foo and LeftFoo can share functions operating entirely on the left option.
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.
_______________________________________________ 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 (6)
-
David Feuer
-
Henning Thielemann
-
Olaf Klinke
-
Oleg Grenrus
-
Sylvain Henry
-
William Yager