I expected the following code to fail with a type error due to violation of the minBound and maxBound. But, as you can see, it goes through without flagging an error.
{-# OPTIONS_GHC -XTypeSynonymInstances #-}
module Main where
type Probability = Float
instance Bounded Probability where
minBound = 0.0
maxBound = 1.0
testout :: Float -> Probability
testout xx = xx + 1.0
main = do
putStrLn $ show $ testout 0.5
putStrLn $ show $ testout (-1.5)
putStrLn $ show $ testout 1.5
In the Prelude I get this
*Main> :type (testout 0.5)
(testout 0.5) :: Probability
And at the prompt I get this:
[~/test]$runhaskell demo.hs
1.5
-0.5
2.5
Clearly I'm not declaring Bounded properly, and I'm sure I'm doing something wrong syntactically. There isn't much simple stuff on Google regarding Bounded typeclasses, so any help would be much appreciated.
That's not what Bounded
is for. Bounded a
just defines the functions minBound :: a
and maxBound :: a
. It does not induce any special checking or anything.
You can define a bounded type using a so-called smart constructor. That is:
module Probability (Probability) where
newtype Probability = P { getP :: Float }
deriving (Eq,Ord,Show)
mkP :: Float -> Probability
mkP x | 0 <= x && x <= 1 = P x
| otherwise = error $ show x ++ " is not in [0,1]"
-- after this point, the Probability data constructor is not to be used
instance Num Probability where
P x + P y = mkP (x + y - x * y)
P x * P y = mkP (x * y)
fromIntegral = mkP . fromIntegral
...
So the only way to make a Probability
is to use the mkP
function eventually (this is done for you when you use numeric operations given our Num
instance), which checks that the argument is in range. Because of the module's export list, outside of this module is it not possible to construct an invalid probability.
Probably not the two-liner you were looking for, but oh well.
For extra composability, you could factor out this functionality by making a BoundCheck
module instead of Probability
. Just like above, except:
newtype BoundCheck a = BC { getBC :: a }
deriving (Bounded,Eq,Ord,Show)
mkBC :: (Bounded a) => a -> BoundCheck a
mkBC x | minBound <= x && x <= maxBound = BC x
| otherwise = error "..."
instance (Bounded a) => Num (BoundCheck a) where
BC x + BC y = mkBC (x + y)
...
Thus you can get the functionality you were wishing was built in for you when you asked the question.
To do this deriving stuff you may need the language extension {-# LANGUAGE GeneralizedNewtypeDeriving #-}
.