Reputation: 43330
I'm looking for a numeric type able to represent, say, a value 0.213123
or 0.0
, or 1.0
, but refusing the out of range values, such as -0.2123
and 1.2312
. Does there exist a specific type fitting that purpose, and what is the optimal general approach to restricting numbers to a specific range?
Of course, the first answer coming to mind is: just use Double
, but getting spoiled by Haskell's type system I've gotten used to maximally securing the program on a type level.
Upvotes: 7
Views: 596
Reputation: 47062
A variation on the smart constructor pattern.
This may be overkill.
{-# LANGUAGE TemplateHaskell #-}
module Foo (Foo(), doubleFromFoo,
maybeFooFromDouble, unsafeFooFromDouble, thFooFromDouble)
where
import Language.Haskell.TH
Anyway, standard newtype
...
newtype Foo = Foo Double
Getting a Double
out is easy...
doubleFromFoo :: Foo -> Double
doubleFromFoo (Foo x) = x
Putting a Double
in at runtime incurs a runtime check, no getting round that...
maybeFooFromDouble :: Double -> Maybe Foo
maybeFooFromDouble x
| 0 <= x && x <= 1 = Just (Foo x)
| otherwise = Nothing
...unless you're happy being unsafe (and have some social means of enforcing that all uses of unsafeFooFromDouble
are actually safe)...
unsafeFooFromDouble :: Double -> Foo
unsafeFooFromDouble = Foo
But if it's a compile-time constant, you can do the check at compile-time, with no runtime overhead:
thFooFromDouble :: (Real a, Show a) => a -> Q Exp
thFooFromDouble x
| 0 <= x && x <= 1 = return $ AppE (VarE 'unsafeFooFromDouble)
(LitE (RationalL (toRational x)))
| otherwise = fail $ show x ++ " is not between 0 and 1"
And this is how you use that last function:
$(thFooFromDouble 0.3)
Remember not to put any spaces between the $
and the (
!.
Upvotes: 2
Reputation: 38758
newtype Rep1 = Rep1 Double
checkRange :: Double -> Maybe Double
checkRange x
| 0 < x && x < 1 = Just x
| otherwise = Nothing
toRep1 :: Double -> Maybe Rep1
toRep1 x = Rep1 . (\x -> tan $ (x-0.5) * pi) <$> checkRange x
fromRep1 :: Rep1 -> Double
fromRep1 (Rep1 x) = atan x / pi + 0.5
data Rep2 = Rep2 Integer Integer
fromRep2 :: Rep2 -> Double
fromRep2 (Rep2 a b) = fromIntegral (abs a) / fromIntegral (abs a + abs b + 1)
toRep2 :: Double -> Maybe Rep2
toRep2 = error "left to the reader"
Upvotes: 3
Reputation: 64740
A Serious Suggestions
You could use a newtype wrapper (and smart constructor) around a word of the proper bit size:
newtype SmallFrac = SF Word64
-- Example conversion (You'd actually want to make
-- instances of common classes, I assume)
sfToDouble :: SmallFrac -> Double
sfToDouble (SF x) = fromIntegral x / fromIntegral (maxBound `asTypeOf` x)
instance Show SmallFrac where
show = show . sfToDouble
Implementing multiplication and division might be more costly than you would like, but at least addition is easy (modulo protecting against over/underflow) and you claim to not need any operations so even better.
A Less Useful Suggestion
If all you need is a symbol representing a value exists between one and zero then take dave4420's suggestion and just have a unit type:
newtype SmallFrac = SF ()
There are no operations for this type, not even conversion to/from other types of interest such as Double
, but this meets the request as stated.
Upvotes: 5
Reputation: 60503
Not standard. You'd have to make one -- I'd suggest a smart constructor. Keep in mind though that such a type supports very few numeric operations -- you can't add them and keep them in the set, nor negate them, so I would advise against a Num
instance. A Monoid
on multiplication would be reasonable.
Upvotes: 4