
Kannan Goundan
Karl Voelker
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