[Haskell-cafe] function types as instances of Num
Dan Weston
westondan at imageworks.com
Thu Oct 26 19:51:14 EDT 2006
How about:
{-# OPTIONS -fglasgow-exts #-}
import Control.Arrow
type Alpha alpha = alpha -> (Integer,alpha)
test = square . (lit 4)
lit :: Integer -> Alpha alpha
lit val stack = (val, stack)
instance Eq (Alpha alpha) where
x == y = uncurry (==) . (fst . x &&& fst . y) $ undefined
instance Show (Alpha alpha) where
show x = show . fst $ x undefined
instance Num (Alpha alpha) where
fromInteger i = (\s -> (i,s))
(+) = fBinary (+)
(-) = fBinary (-)
(*) = fBinary (*)
negate = fUnary negate
abs = fUnary abs
signum = fUnary signum
fUnary op x = (op . fst &&& snd ) . x
fBinary op x y = (uncurry op . (fst *** fst) &&& (snd . fst)) . (x &&& y)
Greg Buchholz wrote:
> Let's say we've got a little stack language, where you compute
> things by transformations of stacks, using compositions of functions
> from stacks to stacks (represented here as nested tuples). (See also
> Chris Okasaki's "Techniques for Embedding Postfix Languages in Haskell"
> www.eecs.harvard.edu/~nr/ cs252r/archive/chris-okasaki/hw02.ps )
>
> For example, the simple program below calculates the square of 4...
>> {-# OPTIONS -fglasgow-exts #-}
>>
>> main = print $ test ()
>> test = square . (lit 4)
>>
>> lit :: Integer -> a -> (Integer,a)
>> lit val stack = (val, stack)
>>
>> dup (a, b) = (a, (a, b))
>> mult (a, (b, c)) = (b*a, c)
>> square = mult . dup
>
> ...now let's say I find that using the function "lit" to annotation
> numeric literals ugly. What I really want is something like...
>
>> test' = square . 4
>
> ...Seems simple enough, I'll just make an appropriate instance of Num
> and I'll be able to use fromInteger...
>
>> instance Eq (a -> (Integer, a)) instance Show (a -> (Integer, a))
instance Num (a -> (Integer, a)) where
>> fromInteger = lit
>
> ...but now when I try it, GHC complains...
>
> No instance for (Num (a -> (Integer, t)))
> arising from the literal `4' at final.hs:15:17
> Possible fix:
> add an instance declaration for (Num (a -> (Integer, t)))
> In the second argument of `(.)', namely `4'
> In the expression: square . 4
> In the definition of `test'': test' = square . 4
>
> ...so it seems that (a -> (Integer, t)) can't be unified with (a ->
> (Integer, a)), or somesuch. Any thoughts on how to get this to work?
>
>
> Thanks,
>
> Greg Buchholz
>
>
> _______________________________________________
> 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