On 2007.12.18 21:07:25 -0500, Brad Larsen <[EMAIL PROTECTED]> scribbled 0.6K 
characters:
> Hi there list,
>
> How would one go about creating a new type for a subset of the integers,
> for (contrived) example just the even integers?  I was thinking of making a
> new type
>
> newtype EvenInt = EvenInt Integer
>
> but the problem with this is that it accepts any integer, even odd ones.
> So to prevent this, the module does not export the constructor for
> it---rather, the module exports a function `mkEvenInt' that creates an
> EvenInt if the given value is acceptable or raises an error otherwise.
>
> What's the right way to do this?  Thanks!
>
> Brad Larsen

Well, I've had cause to do this in the past.

Before I paste the following code, I'd like to emphasize that I wrote it a 
while when I was even more new to Haskell; that it compiles but hasn't been 
tested very much; and that I'm sure there are better ways to do it.

What I wanted to do was to define a type for a subset of 'reals' (floats) which 
are either 0, or positive. The code looks like this:

> {- For many equations and results, it is nonsensical to have negative 
> results, > but we don't want
> to use solely natural numbers because then we lose precision. So we define a
> PosReal type which tries
> to define the subset of real numbers which are 0 or positive; this way the 
> type
> system checks for negative
> results instead of every other function having conditionals checking for
> negative input or output. -}
> newtype PosReal = MakePosReal Float deriving (Show, Eq, Ord)
>
> -- Basic numerical operations on positive reals
> instance Num PosReal where
>     fromInteger = toPosReal . fromInteger
>     x + y = MakePosReal (fromPosReal x + fromPosReal y)
>     x - y = toPosReal ((fromPosReal x) - (fromPosReal y))
>     x * y = MakePosReal (fromPosReal x * fromPosReal y)
>     abs x | x >= 0 = x
>           | otherwise = x * (-1)
>     signum x | x >= 0 = 1
>              | otherwise = (-1)
>
> -- Define division on PosReals
> instance Fractional PosReal where
>     x / y = toPosReal ((fromPosReal x) / (fromPosReal y))
>     fromRational x = MakePosReal (fromRational x)
>
> -- Positive reals are truncated at 0
> toPosReal :: Float -> PosReal
> toPosReal x
>     | x < 0     = MakePosReal 0
>     | otherwise = MakePosReal x
> fromPosReal :: PosReal -> Float
> fromPosReal (MakePosReal i) = i
>
> -- Define an instance to allow QuickCheck operations
> instance Arbitrary PosReal where
>     arbitrary = liftM3 fraction arbitrary arbitrary arbitrary
>         where fraction :: Integer -> Integer -> Integer -> PosReal
>               fraction a b c = fromInteger a + (fromInteger b / (abs 
> (fromInteger c) + 1))


--
gwern
RFI el Audiotel muezzin E911 B61-11 Revolution 5.0i N5P6 espionage

Attachment: pgpL1SXFCbylD.pgp
Description: PGP signature

_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to