module MeterF where
import AllFudgets
import Data.Ratio
meterF :: RealFrac v => InF v (Ratio Int)
meterF :: forall v. RealFrac v => InF v (Ratio Int)
meterF = forall {e}.
RealFrac e =>
(GraphicsF FlexibleDrawing -> GraphicsF FlexibleDrawing)
-> F e (InputMsg (Ratio Int))
meterF' forall a. Customiser a
standard
meterF' :: (GraphicsF FlexibleDrawing -> GraphicsF FlexibleDrawing)
-> F e (InputMsg (Ratio Int))
meterF' GraphicsF FlexibleDrawing -> GraphicsF FlexibleDrawing
pm =
forall {a}. SP (GfxEvent a) (InputMsg (Ratio Int))
post forall a b e. SP a b -> F e a -> F e b
>^^=< forall {a} {b}. Bool -> Int -> F a b -> F (Either Bool a) b
border3dF Bool
True Int
1 (forall gfx.
Graphic gfx =>
Customiser (GraphicsF gfx) -> F (GfxFCmd gfx) GfxFEvent
graphicsDispF' GraphicsF FlexibleDrawing -> GraphicsF FlexibleDrawing
params) forall c d e. F c d -> (e -> c) -> F e d
>=^< forall {a} {a}. e -> Either a (GfxCommand [a] FlexibleDrawing)
pre
where
params :: GraphicsF FlexibleDrawing -> GraphicsF FlexibleDrawing
params = GraphicsF FlexibleDrawing -> GraphicsF FlexibleDrawing
pm forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall {xxx} {p}.
(HasBgColorSpec xxx, Show p, ColorGen p) =>
p -> Customiser xxx
setBgColor ColorSpec
meterBg forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall xxx. HasFgColorSpec xxx => ColorSpec -> Customiser xxx
setFgColorSpec ColorSpec
meterFg forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall xxx. HasBorderWidth xxx => Int -> Customiser xxx
setBorderWidth Int
0
pre :: e -> Either a (GfxCommand [a] FlexibleDrawing)
pre = forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {gfx} {a}. gfx -> GfxCommand [a] gfx
replaceAllGfx forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {p}. RealFrac p => p -> FlexibleDrawing
meterD
post :: SP (GfxEvent a) (InputMsg (Ratio Int))
post = forall {t} {b}. (t -> Maybe b) -> SP t b
mapFilterSP forall {a}. GfxEvent a -> Maybe (InputMsg (Ratio Int))
pick
pick :: GfxEvent a -> Maybe (InputMsg (Ratio Int))
pick (GfxButtonEvent {gfxType :: forall path. GfxEvent path -> Pressed
gfxType=Pressed
Pressed,gfxPaths :: forall path. GfxEvent path -> [(path, (Point, Rect))]
gfxPaths=(a, (Point, Rect))
p:[(a, (Point, Rect))]
_}) = forall {a}. (a, (Point, Rect)) -> Maybe (InputMsg (Ratio Int))
change (a, (Point, Rect))
p
pick (GfxButtonEvent {gfxType :: forall path. GfxEvent path -> Pressed
gfxType=Pressed
Released,gfxPaths :: forall path. GfxEvent path -> [(path, (Point, Rect))]
gfxPaths=(a, (Point, Rect))
p:[(a, (Point, Rect))]
_}) = forall {a}. (a, (Point, Rect)) -> Maybe (InputMsg (Ratio Int))
done (a, (Point, Rect))
p
pick (GfxMotionEvent {gfxPaths :: forall path. GfxEvent path -> [(path, (Point, Rect))]
gfxPaths=(a, (Point, Rect))
p:[(a, (Point, Rect))]
_}) = forall {a}. (a, (Point, Rect)) -> Maybe (InputMsg (Ratio Int))
change (a, (Point, Rect))
p
pick GfxEvent a
_ = forall a. Maybe a
Nothing
change :: (a, (Point, Rect)) -> Maybe (InputMsg (Ratio Int))
change = forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a}. a -> InputMsg a
inputChange forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a}. (a, (Point, Rect)) -> Ratio Int
extr
done :: (a, (Point, Rect)) -> Maybe (InputMsg (Ratio Int))
done = forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a}. a -> InputMsg a
inputMsg forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a}. (a, (Point, Rect)) -> Ratio Int
extr
extr :: (a, (Point, Rect)) -> Ratio Int
extr (a
_,(Point
p,Rect Point
p0 Point
s)) = Point -> Int
xcoord (Point
pforall a. Num a => a -> a -> a
-Point
p0) forall a. Integral a => a -> a -> Ratio a
% Point -> Int
xcoord Point
s
meterD :: p -> FlexibleDrawing
meterD p
r = Point -> Bool -> Bool -> (Rect -> [DrawCommand]) -> FlexibleDrawing
FlexD (Int -> Int -> Point
Point Int
50 Int
5) Bool
False Bool
True Rect -> [DrawCommand]
drawfun
where
drawfun :: Rect -> [DrawCommand]
drawfun (Rect Point
p (Point Int
w Int
h)) = [Rect -> DrawCommand
FillRectangle (Point -> Point -> Rect
Rect Point
p (Int -> Int -> Point
Point Int
w' Int
h))]
where w' :: Int
w' = forall {a1} {b} {a2}.
(RealFrac a1, Integral b, Integral a2) =>
a1 -> a2 -> b
scale p
r Int
w
meterFg :: ColorSpec
meterFg = forall {a}. (Show a, ColorGen a) => a -> ColorSpec
colorSpec forall a b. (a -> b) -> a -> b
$ [Char] -> [[Char]] -> [[Char]]
argKeyList [Char]
"meterfg" [[Char]
"blue2",[Char]
fgColor,[Char]
"black"]
meterBg :: ColorSpec
meterBg = forall {a}. (Show a, ColorGen a) => a -> ColorSpec
colorSpec forall a b. (a -> b) -> a -> b
$ [Char] -> [[Char]] -> [[Char]]
argKeyList [Char]
"meterbg" [[Char]
bgColor,[Char]
"white"]