Reputation: 405
I want to write a function that can be called on numbers (e.g. 1
) and on strings (e.g. "a"
). It is important in my application to simplify "user code" as much as possible.
The minimal example of my code looks like this
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeSynonymInstances #-}
type StrInt = Either String Int
class Lift a where
toStrInt :: a -> StrInt
instance Lift String where
toStrInt= Left
instance Lift Int where
toStrInt= Right
declare:: StrInt ->String
declare (Left a) = "String: " ++ a
declare (Right n) = "Number: " ++ (show n)
declare' :: Lift a => a -> String
declare' a = declare (toStrInt a)
myDecA = declare' "a"
myDec1 = declare' 1
Compiling this gives the error
Ambiguous type variable ‘a0’ arising from a use of ‘declare'’
prevents the constraint ‘(Lift a0)’ from being solved.
I understand the problem and I know that I can replace the last line with any of the following:
myDec1 = declare' (1::Int)
myDec1 = declare (Right 1)
But that defeats the purpose of what I'm trying to achieve. Is there a clever way of setting the same idea such that it makes clear that 1 is an Int?
Also, In my application (more complex than the minimal example above) The declare
function only works for Int
s. So I can't generalize it for all Num a
.
Upvotes: 3
Views: 121
Reputation: 725
Like I said in my comment, this is a hacky solution. There might be a cleaner way.
But what you can do is enable OverloadedStrings
and then make NumStr
an instance of IsString
and Num
so that you can convert literals to it.
{-# LANGUAGE OverloadedStrings #-}
module Hacky where
import Data.String (IsString(..))
newtype StrInt = StrInt (Either String Int)
instance IsString StrInt where
fromString str = StrInt (Left str)
instance Num StrInt where
-- fromIntegral is to convert 'Integer' to 'Int'.
fromInteger n = StrInt (Right (fromIntegral n))
-- other methods for 'Num' are missing...
declare :: StrInt -> String
declare (StrInt (Left a)) = "String: " ++ a
declare (StrInt (Right n)) = "Number: " ++ show n
main :: IO ()
main = do
putStrLn $ declare "hi"
putStrLn $ declare 1
Note that I didn't implement the other required methods for Num
, which you may wish to do, otherwise code like declare (1 + 3)
won't typecheck.
I'd be happier with this if there was something like OverloadedNumbers
, but I couldn't find a pragma like that.
Upvotes: 2
Reputation: 2044
This is not possible using Haskell. The reason for this is that while 1
looks like an Int
, it's actually a Num a => a
. Haskell does not have a way to know that Int
is the only a
that satisfies (Num a, Lift a) => a
, so it needs to be told this explicitly. For example, if I create in another module the following instance:
instance Num String where
...
Then declare' 1
becomes ambiguous, and could reasonably result in either "String:..."
or "Int:..."
. Haskell can't know at compile time that I won't do this, so we have a problem.
Upvotes: 5