X-Git-Url: http://gitweb.michael.orlitzky.com/?a=blobdiff_plain;f=src%2FCardinal.hs;h=3bff38f206c5983cb29ac9f80ef99275f6a88e4c;hb=c954154b379c5bd444d527298c33142fb150711b;hp=42b1260bb13f72f530bd725fd89943da1c1d004f;hpb=084d6e31ba1eda1e7c206ff8ff23e8567e2339ce;p=spline3.git diff --git a/src/Cardinal.hs b/src/Cardinal.hs index 42b1260..3bff38f 100644 --- a/src/Cardinal.hs +++ b/src/Cardinal.hs @@ -1,12 +1,14 @@ -- | The Cardinal module contains the Cardinal data type, representing --- a cardinal direction (one of the 27 directions surrounding the --- center of a cube. In addition to those 27 directions, we also +-- a cardinal direction (one of the 26 directions surrounding the +-- center of a cube. In addition to those 26 directions, we also -- include the interior point and a number of composite types that -- allow us to perform arithmetic on directions. module Cardinal where +import Control.Monad (liftM, liftM2) import Prelude hiding (LT) +import Test.QuickCheck (Arbitrary(..), oneof) data Cardinal = F -- ^ Front | B -- ^ Back @@ -46,7 +48,7 @@ data Cardinal = F -- ^ Front deriving (Show, Eq) --- | By making Cardinal an instance of Num, we gain the ability to +-- | By making Cardinal an instance of 'Num', we gain the ability to -- add, subtract, and multiply directions. The results of these -- operations are never actually calculated; the types just keep -- track of which operations were performed in which order. @@ -54,20 +56,60 @@ instance Num Cardinal where x + y = Sum x y x - y = Difference x y x * y = Product x y - negate x = Product (Scalar (-1)) x + negate = Product (Scalar (-1)) abs x = x signum x = x fromInteger x = Scalar (fromIntegral x) --- | Like the Num instance, the Fractional instance allows us to +-- | Like the Num instance, the 'Fractional' instance allows us to -- take quotients of directions. instance Fractional Cardinal where x / y = Quotient x y - recip x = Quotient (Scalar 1) x + recip = Quotient (Scalar 1) fromRational x = Scalar (fromRational x) + +instance Arbitrary Cardinal where + arbitrary = oneof [f,b,l,r,d,t,fl,fr,fd,ft,bl,br,bd,bt,ld,lt, + rd,rt,fld,flt,frd,frt,bld,blt,brd,brt,i, + scalar,csum,cdiff,cprod,cquot] + where + f = return F + b = return B + l = return L + r = return R + d = return D + t = return T + fl = return FL + fr = return FR + fd = return FD + ft = return FT + bl = return BL + br = return BR + bd = return BD + bt = return BT + ld = return LD + lt = return LT + rd = return RD + rt = return RT + fld = return FLD + flt = return FLT + frd = return FRD + frt = return FRT + bld = return BLD + blt = return BLT + brd = return BRD + brt = return BRT + i = return I + scalar = liftM Scalar arbitrary + csum = liftM2 Sum arbitrary arbitrary + cdiff = liftM2 Difference arbitrary arbitrary + cprod = liftM2 Product arbitrary arbitrary + cquot = liftM2 Quotient arbitrary arbitrary + + -- | Rotate a cardinal direction counter-clockwise about the x-axis. ccwx :: Cardinal -> Cardinal ccwx F = F @@ -150,32 +192,32 @@ cwy = ccwy . ccwy . ccwy -- | Rotate a cardinal direction counter-clockwise about the z-axis. ccwz :: Cardinal -> Cardinal -ccwz F = L -ccwz B = R -ccwz L = B -ccwz R = F +ccwz F = R +ccwz B = L +ccwz L = F +ccwz R = B ccwz D = D ccwz T = T -ccwz FL = BL -ccwz FR = FL -ccwz FD = LD -ccwz FT = LT -ccwz BL = BR -ccwz BR = FR -ccwz BD = RD -ccwz BT = RT -ccwz LD = BD -ccwz LT = BT -ccwz RD = FD -ccwz RT = FT -ccwz FLD = BLD -ccwz FLT = BLT -ccwz FRD = FLD -ccwz FRT = FLT -ccwz BLD = BRD -ccwz BLT = BRT -ccwz BRD = FRD -ccwz BRT = FRT +ccwz FL = FR +ccwz FR = BR +ccwz FD = RD +ccwz FT = RT +ccwz BL = FL +ccwz BR = BL +ccwz BD = LD +ccwz BT = LT +ccwz LD = FD +ccwz LT = FT +ccwz RD = BD +ccwz RT = BT +ccwz FLD = FRD +ccwz FLT = FRT +ccwz FRD = BRD +ccwz FRT = BRT +ccwz BLD = FLD +ccwz BLT = FLT +ccwz BRD = BLD +ccwz BRT = BLT ccwz I = I ccwz (Scalar s) = (Scalar s) ccwz (Sum c0 c1) = Sum (ccwz c0) (ccwz c1)