Type abstraction in face of field labels

The idea of labelled fields is to abstract away the relative order of those fields. You’re asking for something further(?) You want the user to not even know what other fields are in the datatype(?)

  • For H98-style ADTs, the supplier could export (some of) the field labels, but not the Constructor(s). So the user could at least select some values but not duplicate all of the original data type.

  • They could also use the labels to update build a new value from an old, with overwriteable fresh-able values restricted to only those fields.

  • But then the user couldn’t construct a whole fresh value of that type. (Because that would need access to the Constructor, (ab)using which could pattern-match on a value to grab all the fields the supplier was trying to hold abstract.)

  • ?Supply a PatternSynonym as pseudo-constructor that exposes only some of the fields; but for a fresh value fills in defaults for the inaccessible fields?

For all the implementations of anonymous/extensible records I’m aware of, the situation is quite a bit worse:

  • Firstly, again the relative ordering of fields is held abstract/indeed the idea of field position doesn’t apply.

  • The field labels are Symbol (or equivalent), which are automatically global/the exporter can’t mention them in hiding lists/they’re merely type-level names.

  • And since the term-level name for the label is exactly the same as the type-level Symbol, the (ab)user can ‘guess’ the name to access the field just by looking at its type. “public duplicates of values” is easy.

  • I suppose there could be a records system with separate term-level vs type-level labels, and with the term-level encrypted for what are supposed to be abstract fields ??? I’ve not seen/heard of that sort of bodging.

  • Supplier could make the type of the field content abstract; so a user could copy the value but not peek inside it(?)

  • A PatSyn defined over an anonymous record could kinda hide some labels – but “He’s behind you!” the (ab)user just looks at its type.

This is an example of what I was attempting to describe:


module Stooges(newStooges, larry, curly, moe) where

data Stooges = St Int Int Int

newStooges s0 = St s0 (s0+1) (s0+2)
larry (St s1 _ _) = s1
curly (St _ s2 _) = s2
moe   (St _ _ s3) = s3

module Stooged where
import Stooges

type Stooged = (Int, Int, Int)

newStooged = stooged . newStooges

stooged st = (larry st, curly st, moe st)

So I’ll try to explain the problem again in more abstract terms:

  • if each and every component of a data type has a corresponding inspector function which is exposed, the data type isn’t abstract.

Well … how does module Stooged know that larry, curly, moe is every component?

module Stooges( {- as above -} )  where
data Stooges = St Int Int Int Int

newStooges s0 = St s0 (s0+1) (s0+2) 0
...
shemp (St _ _ _ s4) = s4

How’s Stooged going to find out there’s a shemp? Stooges isn’t exporting constructor St, as per my “but not the Constructor(s)” .

My observation was in response to this comment:

Since it doesn’t specify whether all or only some components of the ADT’s hidden constructors will be exposed via (exports of) inspector functions, I simply assumed the worst-case scenario - an exposed inspector function for each component of each constructor.

As for your modification, it means a Stooged vales would be an incomplete duplicate of a Stooges value because of that extra (and concealed) component - it’s “one step back” from that worst-case scenario (“expose everything” ). So my observation would no longer fully apply as a result of your modification.

Ha, funny: I took that comment to be talking about something else entirely. Namely:

  • coping with same-named fields in different datatypes (AllowDuplicateFields); with
  • introducing . syntax for field access; so
  • combining those for (in effect) type-driven despatch of the ambiguous usage of ..