ruff-0.4.0.1: relatively useful fractal functions

Copyright(c) Claude Heiland-Allen 2015
LicenseBSD3
Maintainerclaude@mathr.co.uk
Stabilityunstable
PortabilityTypeFamilies
Safe HaskellSafe
LanguageHaskell98

Fractal.RUFF.Types.Ratio

Description

Rational numbers with ruff-specific operations.

Synopsis

Documentation

class Q r where Source #

Rational numbers with ruff-specific operations.

Minimal complete definition

(%), numerator, denominator

Associated Types

type Z r Source #

Methods

(%) :: Z r -> Z r -> r infixl 7 Source #

smart constuctor

numerator :: r -> Z r Source #

extract numerator

denominator :: r -> Z r Source #

extract denominator

(%!) :: Z r -> Z r -> r infixl 7 Source #

unsafe constructor

zero :: Integral (Z r) => r Source #

0

half :: Integral (Z r) => r Source #

1/2

one :: Integral (Z r) => r Source #

1

fromQ :: Integral (Z r) => r -> Rational Source #

convert to Prelude.Rational

toQ :: Integral (Z r) => Rational -> r Source #

convert from Prelude.Rational

wrap :: Integral (Z r) => r -> r Source #

wrap into [0,1)

doubleWrap :: Integral (Z r) => r -> r Source #

doubling map to [0,1)

double :: Integral (Z r) => r -> r Source #

doubling map from [0,1) to [0,1)

doubleOdd :: Integral (Z r) => r -> r Source #

doubling map from [0,1) to [0,1) for odd denominator

preimages :: Integral (Z r) => r -> (r, r) Source #

doubling map preimages from [0,1) to [0,1)x[0,1)

Instances

Integral a => Q (Ratio a) Source # 

Associated Types

type Z (Ratio a) :: * Source #

Integral a => Q (Ratio a) Source # 

Associated Types

type Z (Ratio a) :: * Source #

data Ratio a Source #

Ratio data structure

Constructors

!a :% !a 

Instances

Eq a => Eq (Ratio a) Source # 

Methods

(==) :: Ratio a -> Ratio a -> Bool #

(/=) :: Ratio a -> Ratio a -> Bool #

Data a => Data (Ratio a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ratio a -> c (Ratio a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ratio a) #

toConstr :: Ratio a -> Constr #

dataTypeOf :: Ratio a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Ratio a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ratio a)) #

gmapT :: (forall b. Data b => b -> b) -> Ratio a -> Ratio a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ratio a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ratio a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Ratio a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ratio a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ratio a -> m (Ratio a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ratio a -> m (Ratio a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ratio a -> m (Ratio a) #

Integral a => Ord (Ratio a) Source # 

Methods

compare :: Ratio a -> Ratio a -> Ordering #

(<) :: Ratio a -> Ratio a -> Bool #

(<=) :: Ratio a -> Ratio a -> Bool #

(>) :: Ratio a -> Ratio a -> Bool #

(>=) :: Ratio a -> Ratio a -> Bool #

max :: Ratio a -> Ratio a -> Ratio a #

min :: Ratio a -> Ratio a -> Ratio a #

(Integral a, Read a) => Read (Ratio a) Source # 
(Integral a, Show a) => Show (Ratio a) Source # 

Methods

showsPrec :: Int -> Ratio a -> ShowS #

show :: Ratio a -> String #

showList :: [Ratio a] -> ShowS #

Integral a => Q (Ratio a) Source # 

Associated Types

type Z (Ratio a) :: * Source #

type Z (Ratio a) Source # 
type Z (Ratio a) = a

type Rational = Ratio Integer Source #

Rational type