Safe Haskell | None |
---|---|
Language | Haskell2010 |
This library provides a mechanism for overloading an indentifier with mutliple definitions. The number of overloads is finite and have to be defined at once.
The advantage of this library over the regular typeclass approach is that it behaves very well with type inference.
{-# LANGUAGE TemplateHaskell, TypeFamilies, FlexibleInstances #-}
module Overload.Example where
import Data.Maybe
import Overload
f1 :: Bool
f1 = True
f2 :: Int -> Int
f2 x = x + 1
f3 :: Num a = Maybe a
f3 = Just 0
overload
"f" ['f1, 'f2, 'f3]
test :: IO ()
test = do
print (f 1)
print (f && True)
print (fromMaybe 10 f)
Notice that we didn't have to annotate anything. For the function case it was enough to use
f
as a function. Since there's only one overload that's a function, the argument and
the return value are inferred as Int
s.