[Haskell-cafe] Representing record subtypes, sort of.

James M jmartin at eecs.berkeley.edu
Wed Nov 12 22:26:49 UTC 2014


A potentially more elegant approach is using existential types.

{-# LANGUAGE ExistentialQuantification #-}

class IsFsEntry a where
    bar :: a -> String

data FsFile = FsFile
instance IsFsEntry FsFile where
    bar _ = "File"

data FsFolder = FsFolder
instance IsFsEntry FsFolder where
    bar _ = "Folder"

data FsEntry = forall a . (IsFsEntry a) => MkFsEntry a

https://gist.github.com/jcmartin/cfa5e28ba36574a7e68d

James

On Wed, Nov 12, 2014 at 11:13 AM, Jeffrey Brown <jeffbrown.the at gmail.com>
wrote:

> I am imagining an alternative idiom for heterogeneous treatment in which
> there is a single constructor, but the data type includes an attribute that
> is a dictionary keyed with function names, leading to values that are the
> corresponding code.
>
> It seems like that would have to be memory-wasteful, duplicating the code
> in every object, since Haskell does not permit pointers to a single code
> source, but maybe I'm wrong about that.
>
> On Wed, Nov 12, 2014 at 12:56 AM, Frank Staals <frank at fstaals.net> wrote:
>
>> Kannan Goundan <kannan at cakoose.com> writes:
>>
>> > Karl Voelker <karl <at> karlv.net> writes:
>> >
>> >> {-# LANGUAGE DataKinds #-}
>> >> {-# LANGUAGE GADTs #-}
>> >> {-# LANGUAGE KindSignatures #-}
>> >> module FS where
>> >>
>> >> type Date = String
>> >>
>> >> data FileKind = FILE | FOLDER
>> >>
>> >> data Entry (k :: FileKind) where
>> >>   File   :: String -> Date -> Int -> Entry FILE
>> >>   Folder :: String -> String -> Entry FOLDER
>> >
>> > This is a little beyond my Haskell knowledge.  What would the function
>> > signatures look like?  Here are my guesses:
>> >
>> >     listFolder :: Path -> [Entry ?]
>>
>> Unfortunately, we cannot have our cake and eat it as well. Entry FILE
>> and Entry FOLDER are now different types, and hence you cannot construct
>> a list containing both. In other words; we cannot really fill in the ?
>> in the type signature (or at least not that I'm aware of). Either we use
>> Either (pun intended): listFolder :: Path -> [Either (Entry FILE) (Entry
>> FOLDER)] or you have to create some existential type around an Entry
>> again, i.e.
>>
>> data SomeEntry where
>>   SomeEntry :: Entry k -> SomeEntry
>>
>> listFolder :: Path -> [SomeEntry]
>>
>> You can get the file kind back by pattern matching again.
>>
>> >     createFolder :: Path -> Entry FOLDER
>> >     createFile :: Path -> Entry FOLDER
>>
>> the second one should produce something of type Entry FILE.
>>
>> > Also, lets say I wanted to just get the "id" fields from a list of
>> `Entry`
>> > values.  Can someone help me fill in the blanks here?
>> >
>> >     l :: [Entry ?]
>> >     let ids = map (?) l
>>
>> This is basically the same issue as before. You cannot construct a list
>> that contains both Entry FILE and Entry FOLDER values. We can use type
>> classes together with the SomeEntry solution above though.
>>
>> ----
>>
>> In general I like the fact that we can use the GADTs to obtain extra
>> type level guarantees. However, working with lists (or other data
>> structures) with them is a crime. I think for that, we need better
>> support for working with hetrogenious collections.
>>
>> --
>>
>> - Frank
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20141112/34588c29/attachment.html>


More information about the Haskell-Cafe mailing list