[Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

Luke Palmer lrpalmer at gmail.com
Fri Dec 7 13:29:43 EST 2007


On Dec 7, 2007 6:21 PM, Dan Weston <westondan at imageworks.com> wrote:
> This is great! Two questions:
>
> 1) I want to make sure the function arity matches the list length (as a
> runtime check). I think I can do this with an arity function using
> Data.Typeable. I came up with:
>
> arity f = a (typeOf f) where
>    a tr | typeRepTyCon tr /= mkTyCon "->" = 0
>         | otherwise = 1 + (a . fromJust . funResultTy tr . head
>                              . typeRepArgs $ tr)
>
> This looks awful. Is there a better way to get the function arity?
>
> 2) Once I have say arity (+) == 2 at runtime, how can I get it reified
> into Succ (Succ Zero)) at compile time to be able to use it as the first
> argument in your nary function? Can/should I use Template Haskell for this?

You can project the compile time numbers into runtime ones:

> class ProjectN n where
>     projectN :: n -> Int
>
> instance ProjectN Zero where
>     projectN _ = 0
>
> instance (ProjectN n) => ProjectN (Succ n) where
>     projectN _ = 1 + projectN (undefined :: n)

And then make sure the length matches the projected number of
arguments.  Other disagreements will be resolved at compile time.

Luke

> Dan
>
> Victor Nazarov wrote:
> >
> >> {-# OPTIONS -fglasgow-exts #-}
> >> {-# OPTIONS -fallow-undecidable-instances #-}
> >
> > data Zero
> > data Succ a
> >
> > class Nary n x y | n x -> y where
> >   nary :: n -> x -> [String] -> y
> >
> > instance Nary Zero x x where
> >   nary _ x [] = x
> >
> > instance (Nary n y z, Read x) => Nary (Succ n) (x->y) z where
> >   nary _ f (x:xs) = nary (undefined::n) (f $ read x) xs
> >
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list