{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module FULE.Container.Clipped
( Clipped
, clipped
) where
import FULE.Component
import FULE.Container
newtype Clipped c = Clipped c
instance (Container c k m) => Container (Clipped c) k m where
minWidth :: Clipped c -> Proxy k -> m (Maybe Int)
minWidth (Clipped c
c) = c -> Proxy k -> m (Maybe Int)
forall c k (m :: * -> *).
Container c k m =>
c -> Proxy k -> m (Maybe Int)
minWidth c
c
minHeight :: Clipped c -> Proxy k -> m (Maybe Int)
minHeight (Clipped c
c) = c -> Proxy k -> m (Maybe Int)
forall c k (m :: * -> *).
Container c k m =>
c -> Proxy k -> m (Maybe Int)
minHeight c
c
addToLayout :: Clipped c -> Proxy k -> Bounds -> Maybe Int -> LayoutOp k m ()
addToLayout (Clipped c
c) Proxy k
proxy Bounds
bounds =
c -> Proxy k -> Bounds -> Maybe Int -> LayoutOp k m ()
forall c k (m :: * -> *).
Container c k m =>
c -> Proxy k -> Bounds -> Maybe Int -> LayoutOp k m ()
addToLayout c
c Proxy k
proxy Bounds
bounds{ clippingOf = Just bounds }
clipped :: c -> Clipped c
clipped :: forall c. c -> Clipped c
clipped = c -> Clipped c
forall c. c -> Clipped c
Clipped