function types as instances of Num

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

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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Dan Weston wrote:
How about:
Hmm. I'm probably being dense today, but when I add the following definitions to your program... main = print $ (square . 4) () square (a,b) = (a*a,b) ...I still get the same error... No instance for (Num (() -> (t, t1))) arising from the literal `4' at weston.hs:5:25 Possible fix: add an instance declaration for (Num (() -> (t, t1))) In the second argument of `(.)', namely `4' In the second argument of `($)', namely `(square . 4) ()' In the expression: print $ ((square . 4) ()) ...maybe you could show me your implementation of "main" and "square" to help nudge me in the right direction. (I'm using ghc-6.6) Thanks, Greg Buchholz

You need to monomorphize the result before printing: main = print $ ((square . 4) :: Alpha ()) Presumably you will apply (square . 4) at some point to a concrete state at some point, and you wouldn't need to provide the type explicitly. Greg Buchholz wrote:
Dan Weston wrote:
How about:
Hmm. I'm probably being dense today, but when I add the following definitions to your program...
main = print $ (square . 4) () square (a,b) = (a*a,b)
...I still get the same error...
No instance for (Num (() -> (t, t1))) arising from the literal `4' at weston.hs:5:25 Possible fix: add an instance declaration for (Num (() -> (t, t1))) In the second argument of `(.)', namely `4' In the second argument of `($)', namely `(square . 4) ()' In the expression: print $ ((square . 4) ())
...maybe you could show me your implementation of "main" and "square" to help nudge me in the right direction. (I'm using ghc-6.6)
Thanks,
Greg Buchholz _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

The problem seems equivalent to the following: http://pobox.com/~oleg/ftp/Haskell/typecast.html#local-fd That is, the inferred type is too general to chose the appropriate instance. The solution is also the same: either add type annotations to restrict the inferred type (and so make it _match_ the desired instance) -- or use local type inference. Here's the working code of your Haskell embedding of the Forth-like stack language:
{-# OPTIONS -fglasgow-exts #-} {-# OPTIONS -fallow-undecidable-instances #-}
main = print $ test ()
test = square . 4
dup (a, b) = (a, (a, b)) mult (a, (b, c)) = (b*a, c) square = mult . dup
instance Num c => Eq (a -> (c, b)) instance Num c => Show (a -> (c, b)) instance (Num c, TypeCast a b) => Num (a -> (c, b)) where fromInteger val stack = (fromInteger val,typeCast stack) [TypeCast elided]

Try test' = square . (4 :: a -> (Integer,a)) Otherwise, how is the compiler to know that you want 4 to be of that type? S | -----Original Message----- | From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Greg | Buchholz | Sent: 26 October 2006 18:46 | To: haskell-cafe@haskell.org | Subject: [Haskell-cafe] function types as instances of Num | | | 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@haskell.org | http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (4)
-
Dan Weston
-
Greg Buchholz
-
oleg@pobox.com
-
Simon Peyton-Jones