does this irritate anyone else?

Mike T. Machenry dskippy@ccs.neu.edu
Wed, 26 Feb 2003 17:30:45 -0500


  It would be nice if all the operations I wanted to call on my newtype were
class methods. This is not so unfortunatly. I am pretty sure Set is not a
type class. That would be the only solution that would really satisfy me I
guess. MkUn seems to be just renaming the problem, and making shorter
type constructors would granted make my code shorter, but I think it's alot
more readable if I can just perform union on a FugitiveLocations rather than
pulling some field inside said type contructor out for the union and putting
it back in the data structure. 

  Is there really no way to say "This newtype supports all the operations
of the type it was defined from."? Normally I would define it with type but
I could not then write this code which is "the offending code" you asked for.

class State a where
  applyMove :: a -> Move -> a

type DetectiveTickets = Array Detective (Array Ticket Int)

instance State DetectiveTickets where
  applyMove dT = ...

  I get an error about ambiguous types. (my apologies. I don't have my
interpreter handy) I would ideally like to solve the bigger problem this way
by allowing type defined types to be instances of classes rather than just
newtype and data defined types.

Thanks,
-mike

On Wed, Feb 26, 2003 at 08:50:48AM -0800, Hal Daume III wrote:
> One way to get around this is to do something like:
> 
> > newtype DetectiveLocations = DetectiveLocations SomeType1
> > newtype FugitiveLocations  = FugitiveLocations SomeType2
> >
> > class MkUn nt t | nt -> t where
> >    mk :: t -> nt
> >    un :: nt -> t
> >
> > instance MkUn DetectiveLocations SomeType1 where
> >    mk = DetectiveLocations
> >    un (DetectiveLocations dl) = dl
> >
> > -- similarly for FugLocs
> 
> Then, your function is a bit cleaner with (note that the type sig is very
> important now):
> 
> > findFugitive dL fL StartGame = 
> >     mk (minusSet (un dL) (occupiedStops (un fL))
> 
> Another way to do it would be if 'minusSet' were a class method, then you
> could use GHC's newtype deriving feature (or in Hugs just define the
> obvious instances).  For instance, if we had:
> 
> > class Set s where
> >    minusSet :: Set a -> Set a -> Set a
> >    ...
> 
> then you could do:
> 
> > newtype DetectiveLocations = DetectiveLocations SomeType1
> >     deriving (Set)
> > newtype FugitiveLocations  = FugitiveLocations SomeType2
> >     deriving (Set)
> 
> assuming SomeType1 and SomeType2 were instances of Set; then your second
> definition would be fine.
> 
> Finally, if you make your constructor names shorter, it doesn't look quite
> so bad and you get nice error messages and helpful type checking.
> 
> As for why you get ambiguous variables, I'd need to see the offending data
> and instance definitions.
> 
> HTH
> 
>  - Hal
> 
> --
> Hal Daume III
> 
>  "Computer science is no more about computers    | hdaume@isi.edu
>   than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume
> 
> On Wed, 26 Feb 2003, Mike T. Machenry wrote:
> 
> > I am trying to use type classes to get some percollate actions through a
> > nested data structure. The problem is I can't make an instance of a class
> > unless the type is defined with newtype or data. This means all of my
> > functions look something like this:
> > 
> > findFugitive :: DetectiveLocations -> FugitiveLocations -> Move -> FugitiveLocat
> > findFugitive (DetectiveLocations dL) (FugitiveLocations fL) StartGame =
> >   (FugitiveLocations minusSet fL (occupiedStops dL))
> > 
> > instead of this:
> > 
> > findFugitive :: DetectiveLocations -> FugitiveLocations -> Move -> FugitiveLocat
> > findFugitive dL fL StartGame = minusSet fL (occupiedStops dL)
> > 
> > which is much simpler to read. Why can't I make a normal type an instance of 
> > a type class? I get errors that it's an ambiguous type.
> > 
> > thanks,
> > -mike
> > _______________________________________________
> > Haskell mailing list
> > Haskell@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell
> > 
> 
> _______________________________________________
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell