[Haskell-cafe] From records to a type class

Taru Karttunen taruti at taruti.net
Fri Jan 15 23:40:06 EST 2010


Hello

I am wrapping Fuse in a pure Haskell binding and have some issues
with the interface. Currently I am using a record for managing 
the callback functions, but I think there may be a more elegant 
formulation.

Any ideas how to formulate the Fuse record as a typeclass elegantly?

Some notes:
+ TFs not FDs.
+ Separate fh* implementations (raw/stableptr/custom implemented by user)
  easily selected by the library user.
+ Readable type errors.
+ One large typeclass + overlapping instances works, but seems hacky.
+ MPTCs will probably work but is it good form to use them with TFs?
+ Or is using a record better currently?

ps. Note that the interface is very much simplified for the sake
of the discussion. (e.g. [Word8] instead of ByteString).

> import Data.Word
> 
> data IsDir
> data IsFile
> 
> type Ino  = Word32
> data Attr = Attr {}
> 
> data Fuse (fh :: * -> *) = Fuse {
>       open          :: Ino -> IO (fh IsFile)
>     , read          :: Ino -> fh IsFile -> Word64 -> Word32 -> IO [Word8]
>     , opendir       :: Ino -> IO (fh IsDir)
>     , getattr       :: forall fileOrDir. Ino -> fh fileOrDir -> IO Attr
>     -- ...
> 
>     -- File handle management
>     , fhFree  :: Word64 -> IO ()
>     , fhAlloc :: forall any. fh any -> IO Word64
>     , fhRef   :: forall any. Word64 -> IO (fh any)
>     }
> 
> -- Optimally get rid of this wrapping...
> newtype RawFH t = R { r :: Word64 }
> noFhEmpty :: Fuse RawFH
> noFhEmpty = Fuse { fhFree    = \_ -> return ()
>                  , fhAlloc   = return . r
>                  , fhRef     = return . R
>                  }
> 
> stablePtrEmpty :: Fuse anyfh
> stablePtrEmpty = Fuse {} -- implement fh* with StablePtrs (omitted)
> 
> -- User file handle type might be like this:
> 
> data Obj t where
>     Dir  :: {} -> Obj IsDir
>     File :: {} -> Obj IsFile


- Taru Karttunen


More information about the Haskell-Cafe mailing list