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

Kannan Goundan kannan at cakoose.com
Wed Nov 12 00:48:13 UTC 2014


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 ?]
    createFolder :: Path -> Entry FOLDER
    createFile :: Path -> Entry FOLDER

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



More information about the Haskell-Cafe mailing list