[Haskell-cafe] Ada-style ranges
Steffen Schuldenzucker
sschuldenzucker at uni-bonn.de
Mon Apr 26 07:42:50 EDT 2010
On 04/26/2010 12:50 PM, haskell at kudling.de wrote:
>
>
> Hi list,
>
>
>
> how would you describe Ada's ranges in Haskell's typesystem?
>
> http://en.wikibooks.org/wiki/Ada_Programming/Types/range
Hi Lenny,
can non-constant expressions be given as arguments to 'range'? If not, then
what about a opaque wrapper type?
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Range1 (Range1, fromRange1, mkBounded, mkRange1) where
newtype Range1 = Range1 { fromRange1 :: Integer }
deriving (Eq, Num, Ord, Show)
instance Bounded Range1 where
minBound = Range1 $ -5
maxBound = Range1 $ 10
mkBounded :: (Bounded a, Ord a) => (b -> a) -> b -> Maybe a
mkBounded f x = case f x of
y | minBound <= y && y <= maxBound -> Just y
| otherwise -> Nothing
mkRange1 :: Integer -> Maybe Range1
mkRange1 = mkBounded Range1
-- Steffen
More information about the Haskell-Cafe
mailing list