Wired-0.2: Wire-aware hardware descriptionSource codeContentsIndex
Layout.Internal
Documentation
data Alignment Source
Constructors
BottomLeft
TopRight
show/hide Instances
newtype Elasticity Source
Constructors
Elasticity Int
show/hide Instances
data Distance Source
Constructors
Dist Length
show/hide Instances
data Block spaceSize s b Source
Constructors
Space spaceSize (Maybe s)
Box Size Orientation Name b
show/hide Instances
Transformable (RelBlock s b)
(Eq spaceSize, Eq s, Eq b) => Eq (Block spaceSize s b)
(Show spaceSize, Show s, Show b) => Show (Block spaceSize s b)
type RelBlock s b = Block Distance s bSource
type AbsBlock s b = Block (Angle, Length) s bSource
data Placement Source
Constructors
Unspecified
Stack Alignment Alignment
Row Direction Alignment
show/hide Instances
data Floorplan s b Source
Constructors
Block (RelBlock s b)
Comb Placement [Floorplan s b]
show/hide Instances
(Eq s, Eq b) => Eq (Floorplan s b)
(Show s, Show b) => Show (Floorplan s b)
Transformable (Floorplan s b)
type AbsFloorplan s b = [(Position, AbsBlock s b)]Source
class Transformable a whereSource
Methods
flipX :: a -> aSource
flipY :: a -> aSource
rotate_ :: Int -> a -> aSource
show/hide Instances
rotate :: Transformable a => Int -> a -> aSource
absolutizeBlock :: Placement -> RelBlock s b -> (AbsBlock s b, Size)Source
align :: Alignment -> Length -> Length -> LengthSource
translateBlocks :: Position -> AbsFloorplan s b -> AbsFloorplan s bSource
absolutize_ :: Placement -> Position -> Floorplan s b -> Writer (AbsFloorplan s b) SizeSource
absolutize :: Floorplan s b -> (AbsFloorplan s b, Size)Source
blockCenter :: (Position, AbsBlock s b) -> PositionSource
type Color = (Float, Float, Float)Source
white :: ColorSource
grey :: ColorSource
red :: ColorSource
green :: ColorSource
blue :: ColorSource
black :: ColorSource
type Postscript = ShowSSource
class Show a => PSShow a whereSource
Methods
psShow :: a -> PostscriptSource
show/hide Instances
absToPS :: AbsFloorplan s b -> PostscriptSource
floorplanToPS :: Floorplan s b -> (Postscript, Size)Source
linesToPS :: [([(Position, Position)], Color)] -> PostscriptSource
renderFloorplan_ :: Length -> Name -> Floorplan s b -> [([(Position, Position)], Color)] -> IO ()Source
renderFloorplan :: Name -> Floorplan s b -> IO ()Source
ps1 :: PostscriptSource
ps2 :: PostscriptSource
ps3 :: PostscriptSource
newtype Layout s b a Source
Constructors
Layout (ReaderT Placement (Writer [Floorplan s b]) a)
show/hide Instances
newtype LayoutT s b m a Source
Constructors
LayoutT (ReaderT Placement (WriterT [Floorplan s b] m) a)
show/hide Instances
Monad m => MonadLayout s b (LayoutT s b m)
MonadLava lib m => MonadLava lib (LayoutT s b m)
MonadTrans (LayoutT s b)
Monad m => Monad (LayoutT s b m)
MonadFix m => MonadFix (LayoutT s b m)
runLayout :: Layout s b a -> (a, Floorplan s b)Source
runLayoutT :: Monad m => LayoutT s b m a -> m (a, Floorplan s b)Source
renderLayout :: Name -> Layout s b a -> IO ()Source
renderLayoutT :: Monad m => (forall a. m a -> a) -> Name -> LayoutT s b m a -> IO ()Source
class Monad m => MonadLayout s b m | m -> s b whereSource
Methods
currentPlacement :: m PlacementSource
space_ :: Length -> Maybe s -> m ()Source
block_ :: Width -> Height -> Name -> b -> m ()Source
subLayout :: Placement -> m a -> m aSource
transformFloorplan :: (Floorplan s b -> Floorplan s b) -> m a -> m aSource
show/hide Instances
MonadLayout s b (Layout s b)
Monad m => MonadLayout s b (LayoutT s b m)
space :: MonadLayout s b m => Length -> a -> m aSource
block :: MonadLayout s b m => Width -> Height -> Name -> b -> a -> m aSource
rightwards :: MonadLayout s b m => m a -> m aSource
leftwards :: MonadLayout s b m => m a -> m aSource
upwards :: MonadLayout s b m => m a -> m aSource
downwards :: MonadLayout s b m => m a -> m aSource
rightwards' :: MonadLayout s b m => m a -> m aSource
leftwards' :: MonadLayout s b m => m a -> m aSource
upwards' :: MonadLayout s b m => m a -> m aSource
downwards' :: MonadLayout s b m => m a -> m aSource
unplaced :: MonadLayout s b m => m a -> m aSource
stacked :: MonadLayout s b m => m a -> m aSource
translate :: MonadLayout s bl m => XPos -> YPos -> m a -> m aSource
Produced by Haddock version 2.4.2