diagrams-lib-1.4.5.3: Embedded domain-specific language for declarative graphics
Copyright(c) 2014 diagrams-lib team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Diagrams.Size

Description

Utilities for working with sizes of objects.

Synopsis

Size spec

data SizeSpec v n Source #

A SizeSpec is a way of specifying a size without needed lengths for all the dimensions.

Instances

Instances details
Functor v => Functor (SizeSpec v) Source # 
Instance details

Defined in Diagrams.Size

Methods

fmap :: (a -> b) -> SizeSpec v a -> SizeSpec v b #

(<$) :: a -> SizeSpec v b -> SizeSpec v a #

Generic (SizeSpec v n) Source # 
Instance details

Defined in Diagrams.Size

Associated Types

type Rep (SizeSpec v n) :: Type -> Type #

Methods

from :: SizeSpec v n -> Rep (SizeSpec v n) x #

to :: Rep (SizeSpec v n) x -> SizeSpec v n #

Show (v n) => Show (SizeSpec v n) Source # 
Instance details

Defined in Diagrams.Size

Methods

showsPrec :: Int -> SizeSpec v n -> ShowS #

show :: SizeSpec v n -> String #

showList :: [SizeSpec v n] -> ShowS #

Eq (v n) => Eq (SizeSpec v n) Source # 
Instance details

Defined in Diagrams.Size

Methods

(==) :: SizeSpec v n -> SizeSpec v n -> Bool #

(/=) :: SizeSpec v n -> SizeSpec v n -> Bool #

Hashable (v n) => Hashable (SizeSpec v n) Source # 
Instance details

Defined in Diagrams.Size

Methods

hashWithSalt :: Int -> SizeSpec v n -> Int #

hash :: SizeSpec v n -> Int #

type Rep (SizeSpec v n) Source # 
Instance details

Defined in Diagrams.Size

type Rep (SizeSpec v n) = D1 ('MetaData "SizeSpec" "Diagrams.Size" "diagrams-lib-1.4.5.3-5lFW0nwrh4pCIrNKqpNeIG" 'True) (C1 ('MetaCons "SizeSpec" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (v n))))
type N (SizeSpec v n) Source # 
Instance details

Defined in Diagrams.Size

type N (SizeSpec v n) = n
type V (SizeSpec v n) Source # 
Instance details

Defined in Diagrams.Size

type V (SizeSpec v n) = v

Making size spec

mkSizeSpec :: (Functor v, Num n) => v (Maybe n) -> SizeSpec v n Source #

Make a SizeSpec from a vector of maybe values. Any negative values will be ignored. For 2D SizeSpecs see mkWidth and mkHeight from Diagrams.TwoD.Size.

dims :: v n -> SizeSpec v n Source #

Make a SizeSpec from a vector. Any negative values will be ignored.

absolute :: (Additive v, Num n) => SizeSpec v n Source #

A size spec with no hints to the size.

Extracting size specs

getSpec :: (Functor v, Num n, Ord n) => SizeSpec v n -> v (Maybe n) Source #

Retrieve a size spec as a vector of maybe values. Only positive sizes are returned.

specToSize :: (Foldable v, Functor v, Num n, Ord n) => n -> SizeSpec v n -> v n Source #

specToSize n spec extracts a size from a SizeSpec sz. Any values not specified in the spec are replaced by the smallest of the values that are specified. If there are no specified values (i.e. absolute) then n is used.

Functions on size specs

requiredScale :: (Additive v, Foldable v, Fractional n, Ord n) => SizeSpec v n -> v n -> n Source #

requiredScale spec sz returns the largest scaling factor to make something of size sz fit the requested size spec without changing the aspect ratio. sz should be non-zero (otherwise a scale of 1 is returned). For non-uniform scaling see boxFit.

requiredScaling :: (Additive v, Foldable v, Fractional n, Ord n) => SizeSpec v n -> v n -> Transformation v n Source #

Return the Transformation calcuated from requiredScale.

sized :: (InSpace v n a, HasLinearMap v, Transformable a, Enveloped a) => SizeSpec v n -> a -> a Source #

Uniformly scale any enveloped object so that it fits within the given size. For non-uniform scaling see boxFit.

sizedAs :: (InSpace v n a, SameSpace a b, HasLinearMap v, Transformable a, Enveloped a, Enveloped b) => b -> a -> a Source #

Uniformly scale an enveloped object so that it "has the same size as" (fits within the width and height of) some other object.

sizeAdjustment :: (Additive v, Foldable v, OrderedField n) => SizeSpec v n -> BoundingBox v n -> (v n, Transformation v n) Source #

Get the adjustment to fit a BoundingBox in the given SizeSpec. The vector is the new size and the transformation to position the lower corner at the origin and scale to the size spec.