
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

Hi Taru If you haven't obviously got dispatch on type then records are certainly fine. Some obigatory examples: http://www.cas.mcmaster.ca/~kahl/Publications/TR/2000-01/Kahl-Braun-Scheffcz... (see the Editor type page 13) http://www.cas.mcmaster.ca/~kahl/Publications/Conf/Kahl-1999a.pdf http://web.cecs.pdx.edu/~sheard/papers/JfpPearl.ps Parsec's Text.ParserCombinators.Parsec.Token module is an example that has seen widespread use. http://hackage.haskell.org/packages/archive/parsec/2.1.0.1/doc/html/Text-Par... Best wishes Stephen

Excerpts from Stephen Tetley's message of Sat Jan 16 10:27:33 +0200 2010:
If you haven't obviously got dispatch on type then records are certainly fine.
Yes, no dispatch on type. I got a class based implementation compiling, but it seems overly complex. Maybe the record approach is better after all. This is a bit more complex than Parsec unfortunately. (an analogue would be adding encodings to the types of Parsec parsers) import Data.Word data IsDir data IsFile type Ino = Word32 data Attr = Attr {} data Proxy t type family FT (fht :: ((* -> *) -> *)) (fd :: *) class FH (t :: (* -> *) -> *) where fhFre :: Proxy t -> Word64 -> IO () fhAllo :: forall any. FT t any -> IO Word64 fhRe :: forall any. Word64 -> IO (FT t any) data UseRaw :: ((* -> *) -> *) type instance FT UseRaw any = Word64 instance FH UseRaw where fhFre _ _ = return () fhAllo = return fhRe = return data UseStablePtr :: (* -> *) -> (* -> *) -> * type instance FT (UseStablePtr ty) fh = ty fh instance FH (UseStablePtr ty) where -- omitted class FH (FhImpl ty) => Fuse' ty where type FhImpl ty :: (* -> *) -> * open' :: ty -> Ino -> IO (FT (FhImpl ty) IsFile) read' :: ty -> Ino -> FT (FhImpl ty) IsFile -> Word64 -> Word32 -> IO [Word8] opendir' :: ty -> Ino -> IO (FT (FhImpl ty) IsDir) getattr' :: forall fileOrDir. ty -> Ino -> FT (FhImpl ty) fileOrDir -> IO Attr data MyUserType = MyUserType instance Fuse' MyUserType where type FhImpl MyUserType = UseRaw open' = \_ _ -> return 22 - Taru Karttunen
participants (2)
-
Stephen Tetley
-
Taru Karttunen