对于一个项目,我创建了一个基于Int的类型,只要程序试图使用超出限制的值(在我的情况下为[0..127]),就会抛出错误。下面的代码执行此操作,它适用于我。
在Haskell中是否可以创建第二个有界类型(例如[0..255])而不复制此代码?
感谢您的回答
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Minitel.Type.MNatural (MNat, mnat, fromMNat) where
-- | The MNat type. The constructor is hidden.
newtype MNat = MakeMNat Int deriving (Real, Eq, Ord, Show)
-- | MNat is a bounded type
instance Bounded MNat where
minBound = MakeMNat 0
maxBound = MakeMNat 127
-- | Converts an Int into an MNat
mnat :: Int -> MNat
mnat x | loLimit <= x && x <= hiLimit = MakeMNat x
| otherwise = error "Number out of bounds"
where loLimit = fromIntegral (minBound :: MNat)
hiLimit = fromIntegral (maxBound :: MNat)
-- | Converts an MNat into an Int
fromMNat :: MNat -> Int
fromMNat (MakeMNat i) = i
-- | Converts an Int binary function returning Int to a MNat binary function
-- returning an MNat
mfnat :: (Int -> Int) -> (MNat -> MNat)
mfnat f = mnat . f . fromMNat
mfnat2 :: (Int -> Int -> Int) -> (MNat -> MNat -> MNat)
mfnat2 f x y = mnat $ f (fromMNat x) (fromMNat y)
-- | You can do additions, substractions and multiplication with MNat
instance Num MNat where
fromInteger = mnat . fromIntegral
(+) = mfnat2 (+)
(-) = mfnat2 (-)
(*) = mfnat2 (*)
abs = mfnat abs
signum = mfnat signum
-- | Allows to use toInteger with MNat
instance Integral MNat where
quotRem x y = (fromInteger $ quot x' y', fromInteger $ rem x' y')
where (x', y') = (toInteger x, toInteger y)
toInteger = toInteger . fromMNat
-- | Allows to generate lists
instance Enum MNat where
toEnum = mnat
fromEnum = fromMNat
注意:
答案 0 :(得分:7)
您可以使用类型级文字在GHC 7.8中执行此操作:
{-# LANGUAGE DataKinds, PolyKinds, ScopedTypeVariables #-}
module SO26723035 where
import GHC.TypeLits
import Data.Proxy
newtype MNat (n :: Nat) = MakeMNat Int deriving (Eq, Ord, Show)
instance KnownNat n => Bounded (MNat n) where
minBound = MakeMNat 0
maxBound = MakeMNat . fromInteger $ natVal (Proxy :: Proxy n)
ghci> maxBound :: MNat 5
MakeMNat 5
您可以使用类型同义词来修复单个类型。代码的其余部分可以通过机械更改来编译这个多态MNat
。您必须在任何地方添加KnownNat
上下文,并在ScopedTypeVariables
中使用mnat
。