I'm looking for a good way to handle a library interface that accepts both 
strings and numbers in particular argument positions:

Start with the following definitions. I've defined ResourceTree as a class here 
since the details don't matter.

> data Segment = Key String | Index Int 
>     deriving (Eq, Show)
> 
> type Path = [Segment]
> 
> class ResourceTree a where
>     lookupPath :: Path -> a -> Maybe String

What I'm after is to make the following code, representative of intended client 
usage to work:

> examples :: (ResourceTree a) => a -> [Maybe String]
> examples r = [
>         r `at` "status",
>         r `at` 7,
>         r `at` "part" ./ "sku",
>         r `at` "items" ./ 2,
>         r `at` 7 ./ "name",
>         r `at` 7 ./ 9
>     ]

The first way I thought to do this was with type classes:

> class    Segmentable a       where { toSegment :: a -> Segment }
> instance Segmentable Segment where { toSegment = id }
> instance Segmentable String  where { toSegment = Key }
> instance Segmentable Int     where { toSegment = Index }
> 
> class    Pathable a      where { toPath :: a -> Path }
> instance Pathable Path   where { toPath = id }
> instance Pathable String where { toPath s = [ Key s ] }
> instance Pathable Int    where { toPath i = [ Index i ] }
> 
> (./) :: (Segmentable a, Pathable b) => a -> b -> Path
> a ./ b = toSegment a : toPath  b
> infixr 4 ./
> 
> at :: (ResourceTree a, Pathable b) => a -> b -> Maybe String
> a `at` b = lookupPath (toPath b) a
> infix 2 `at`

This works great for all uses in the client code where the type of the numeric 
arguments are known or otherwise forced to be Int. However, when used with 
numeric constants (as in the function example above), it fails due to the way 
that numeric constants are defined in Haskell. For example, the constant 9 in 
example results in this error:

    Ambiguous type variable `t4' in the constraints:
      `Pathable t4' arising from a use of `./' at Test.hs:48:15-20
      `Num t4' arising from the literal `9' at Test.hs:48:20
    Probable fix: add a type signature that fixes these type variable(s)

I suppose that even though there is only one type that is both an instance of 
Num and of Pathable (Int), that can't be deduced with certainty.

In the client code, one could fix this by typing the constants thus:

> r `at` (7::Int) ./ (9::Int)

But to me that makes a hash out of the concise syntax I was trying to achieve.

Also, this code requires both FlexibleInstances and TypeSynonymInstances 
pragmas (though the later requirement could be worked around.), though I'm lead 
to understand that those are common enough. I think also that, these are only 
needed in the library, not the client code.

The other way I thought to do this is by making Path and Segment instances of 
Num and IsString:

> instance Num      Segment where { fromInteger = Index . fromInteger }
> instance IsString Segment where { fromString  = Key . fromString }
> instance Num      Path    where { fromInteger i = [ Index $ fromInteger i ] }
> instance IsString Path    where { fromString  s = [ Key $ fromString s ] }
> 
> (./) :: Segment -> Path -> Path
> a ./ b =  a : b
> infixr 4 ./
> 
> at :: (ResourceTree a) => a -> Path -> Maybe String
> a `at` b = lookupPath b a
> infix 2 `at`

This works but has two downsides: 1) Segment and Path are poor instances of 
Num, eliciting errors for missing methods and resulting in run-time errors 
should any client code accidentally use them as such. 2) It requires the 
OverloadedStrings pragma in every client module.

Any comments on these two approaches would be appreciated, How to improve them? 
Which is the lesser of two evils?

On the other hand, I realize that many may object that intended interface isn't 
very Haskell like. The data object I need to represent (ResourceTree) comes 
from external input and really does have the strange "paths of strings or 
integers" construction, I can't change that. And it is expected that much 
client code will use constant paths to access and manipulate various parts of 
such objects, hence the desire for a concise operator set that works with 
constants. Given that there are actually several operations on ResourceTree 
involving paths (where the operation requires the whole Path as a single 
value), any thoughts on a more Haskell like construction?

Thanks,
        - MtnViewMark


Mark Lentczner
http://www.ozonehouse.com/mark/
m...@glyphic.com



_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to