{-# LANGUAGE CPP #-}
module FDefaults(module FDefaults,module Alignment,fromMaybe) where
import Fudget
import CompOps
import Xtypes
import Alignment(Alignment(..))
import Data.Maybe(fromMaybe)
import Sizing(Sizing)
import GCAttrs
#include "defaults.h"
type Customiser a = a -> a
cust :: (a->a) -> Customiser a
cust :: forall a. (a -> a) -> a -> a
cust = forall a. a -> a
id
type PF p a b = F (Either (Customiser p) a) b
type PK p a b = K (Either (Customiser p) a) b
getpar :: (t -> Maybe c) -> [t] -> c
getpar t -> Maybe c
pp = forall a. a -> Maybe a -> a
fromMaybe (forall a. HasCallStack => [Char] -> a
error [Char]
"getpar:: missing default") forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {t} {a}. (t -> Maybe a) -> [t] -> Maybe a
getparMaybe t -> Maybe c
pp
getparMaybe :: (t -> Maybe a) -> [t] -> Maybe a
getparMaybe t -> Maybe a
pp [] = forall a. Maybe a
Nothing
getparMaybe t -> Maybe a
pp (t
p:[t]
ps) =
case t -> Maybe a
pp t
p of
Just a
a -> forall a. a -> Maybe a
Just a
a
Maybe a
Nothing -> (t -> Maybe a) -> [t] -> Maybe a
getparMaybe t -> Maybe a
pp [t]
ps
noPF :: PF p a b -> F a b
noPF :: forall p a b. PF p a b -> F a b
noPF PF p a b
f = PF p a b
f forall c d e. F c d -> (e -> c) -> F e d
>=^< forall a b. b -> Either a b
Right
standard :: Customiser a
standard :: forall a. a -> a
standard = forall a. a -> a
id
parameter_class(FontSpec,FontSpec)
setFont :: a -> Customiser xxx
setFont a
f = forall xxx. HasFontSpec xxx => FontSpec -> Customiser xxx
setFontSpec (forall {a}. (Show a, FontGen a) => a -> FontSpec
fontSpec a
f)
parameter_class(Keys,[(ModState,KeySym)])
parameter_class(WinAttr,[WindowAttributes])
parameter_class(BorderWidth,Int)
parameter_class(BgColorSpec,ColorSpec)
parameter_class(FgColorSpec,ColorSpec)
setBgColor :: p -> Customiser xxx
setBgColor p
c = forall xxx. HasBgColorSpec xxx => ColorSpec -> Customiser xxx
setBgColorSpec forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a}. (Show a, ColorGen a) => a -> ColorSpec
colorSpec forall a b. (a -> b) -> a -> b
$ p
c
setFgColor :: p -> Customiser xxx
setFgColor p
c = forall xxx. HasFgColorSpec xxx => ColorSpec -> Customiser xxx
setFgColorSpec forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a}. (Show a, ColorGen a) => a -> ColorSpec
colorSpec forall a b. (a -> b) -> a -> b
$ p
c
parameter_class(Margin,Int)
parameter_class(Align,Alignment)
parameter_class1(InitSize)
parameter_class1(InitDisp)
parameter_class(Stretchable,(Bool,Bool))
parameter_class(InitText,[String])
parameter_class(Sizing,Sizing)