ENH use all parameters where appropriate

This commit is contained in:
Nathan Dwarshuis 2022-07-08 20:01:35 -04:00
parent bdab449be7
commit 7ad7b8960e
9 changed files with 89 additions and 70 deletions

View File

@ -178,43 +178,46 @@ type BarFeature = Sometimes CmdSpec
-- TODO what if I don't have a wireless card? -- TODO what if I don't have a wireless card?
getWireless :: BarFeature getWireless :: BarFeature
getWireless = sometimes1 "wireless status indicator" "sysfs path" getWireless = Sometimes "wireless status indicator" xpfWireless
$ IORoot wirelessCmd $ Only readWireless [Subfeature (IORoot wirelessCmd $ Only readWireless) "sysfs path"]
getEthernet :: Maybe Client -> BarFeature getEthernet :: Maybe Client -> BarFeature
getEthernet cl = iconDBus "ethernet status indicator" root tree getEthernet cl = iconDBus "ethernet status indicator" (const True) root tree
where where
root useIcon tree' = DBusRoot (const . ethernetCmd useIcon) tree' cl root useIcon tree' = DBusRoot (const . ethernetCmd useIcon) tree' cl
tree = And1 (Only readEthernet) (Only_ devDep) tree = And1 (Only readEthernet) (Only_ devDep)
getBattery :: BarFeature getBattery :: BarFeature
getBattery = iconIO_ "battery level indicator" root tree getBattery = iconIO_ "battery level indicator" xpfBattery root tree
where where
root useIcon = IORoot_ (batteryCmd useIcon) root useIcon = IORoot_ (batteryCmd useIcon)
tree = Only_ $ IOTest_ "Test if battery is present" $ fmap (Msg Error) <$> hasBattery tree = Only_ $ IOTest_ "Test if battery is present" $ fmap (Msg Error) <$> hasBattery
getVPN :: Maybe Client -> BarFeature getVPN :: Maybe Client -> BarFeature
getVPN cl = iconDBus_ "VPN status indicator" root $ toAnd_ vpnDep test getVPN cl = iconDBus_ "VPN status indicator" xpfVPN root $ toAnd_ vpnDep test
where where
root useIcon tree = DBusRoot_ (const $ vpnCmd useIcon) tree cl root useIcon tree = DBusRoot_ (const $ vpnCmd useIcon) tree cl
test = DBusIO $ IOTest_ "Use nmcli to test if VPN is present" vpnPresent test = DBusIO $ IOTest_ "Use nmcli to test if VPN is present" vpnPresent
getBt :: Maybe Client -> BarFeature getBt :: Maybe Client -> BarFeature
getBt = xmobarDBus "bluetooth status indicator" btDep btCmd getBt = xmobarDBus "bluetooth status indicator" xpfBluetooth btDep btCmd
getAlsa :: BarFeature getAlsa :: BarFeature
getAlsa = iconIO_ "volume level indicator" root $ Only_ $ sysExe "alsactl" getAlsa = iconIO_ "volume level indicator" (const True) root
$ Only_ $ sysExe "alsactl"
where where
root useIcon = IORoot_ (alsaCmd useIcon) root useIcon = IORoot_ (alsaCmd useIcon)
getBl :: Maybe Client -> BarFeature getBl :: Maybe Client -> BarFeature
getBl = xmobarDBus "Intel backlight indicator" intelBacklightSignalDep blCmd getBl = xmobarDBus "Intel backlight indicator" xpfIntelBacklight
intelBacklightSignalDep blCmd
getCk :: Maybe Client -> BarFeature getCk :: Maybe Client -> BarFeature
getCk = xmobarDBus "Clevo keyboard indicator" clevoKeyboardSignalDep ckCmd getCk = xmobarDBus "Clevo keyboard indicator" xpfClevoBacklight
clevoKeyboardSignalDep ckCmd
getSs :: Maybe Client -> BarFeature getSs :: Maybe Client -> BarFeature
getSs = xmobarDBus "screensaver indicator" ssSignalDep ssCmd getSs = xmobarDBus "screensaver indicator" (const True) ssSignalDep ssCmd
getLock :: Always CmdSpec getLock :: Always CmdSpec
getLock = always1 "lock indicator" "icon indicator" root $ lockCmd fontifyAlt getLock = always1 "lock indicator" "icon indicator" root $ lockCmd fontifyAlt
@ -224,27 +227,27 @@ getLock = always1 "lock indicator" "icon indicator" root $ lockCmd fontifyAlt
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- | bar feature constructors -- | bar feature constructors
xmobarDBus :: String -> DBusDependency_ -> (Fontifier -> CmdSpec) xmobarDBus :: String -> XPQuery -> DBusDependency_ -> (Fontifier -> CmdSpec)
-> Maybe Client -> BarFeature -> Maybe Client -> BarFeature
xmobarDBus n dep cmd cl = iconDBus_ n root (Only_ dep) xmobarDBus n q dep cmd cl = iconDBus_ n q root (Only_ dep)
where where
root useIcon tree = DBusRoot_ (const $ cmd useIcon) tree cl root useIcon tree = DBusRoot_ (const $ cmd useIcon) tree cl
iconIO_ :: String -> (Fontifier -> IOTree_ -> Root CmdSpec) -> IOTree_ iconIO_ :: String -> XPQuery -> (Fontifier -> IOTree_ -> Root CmdSpec)
-> BarFeature -> IOTree_ -> BarFeature
iconIO_ = iconSometimes' And_ Only_ iconIO_ = iconSometimes' And_ Only_
iconDBus :: String -> (Fontifier -> DBusTree p -> Root CmdSpec) iconDBus :: String -> XPQuery -> (Fontifier -> DBusTree p -> Root CmdSpec)
-> DBusTree p -> BarFeature -> DBusTree p -> BarFeature
iconDBus = iconSometimes' And1 $ Only_ . DBusIO iconDBus = iconSometimes' And1 $ Only_ . DBusIO
iconDBus_ :: String -> (Fontifier -> DBusTree_ -> Root CmdSpec) -> DBusTree_ iconDBus_ :: String -> XPQuery -> (Fontifier -> DBusTree_ -> Root CmdSpec)
-> BarFeature -> DBusTree_ -> BarFeature
iconDBus_ = iconSometimes' And_ $ Only_ . DBusIO iconDBus_ = iconSometimes' And_ $ Only_ . DBusIO
iconSometimes' :: (t -> t_ -> t) -> (IODependency_ -> t_) -> String iconSometimes' :: (t -> t_ -> t) -> (IODependency_ -> t_) -> String -> XPQuery
-> (Fontifier -> t -> Root CmdSpec) -> t -> BarFeature -> (Fontifier -> t -> Root CmdSpec) -> t -> BarFeature
iconSometimes' c d n r t = Sometimes n (const True) iconSometimes' c d n q r t = Sometimes n q
[ Subfeature icon "icon indicator" [ Subfeature icon "icon indicator"
, Subfeature text "text indicator" , Subfeature text "text indicator"
] ]

View File

@ -255,10 +255,11 @@ gimpDynamicWorkspace = sometimesIO_ "gimp workspace" "gimp" tree dw
c = "Gimp-2.10" -- TODO I don't feel like changing the version long term c = "Gimp-2.10" -- TODO I don't feel like changing the version long term
vmDynamicWorkspace :: Sometimes DynWorkspace vmDynamicWorkspace :: Sometimes DynWorkspace
vmDynamicWorkspace = sometimes1 "virtualbox workspace" "windows 8 VM" root vmDynamicWorkspace = Sometimes "virtualbox workspace" xpfVirtualBox
[Subfeature root "windows 8 VM"]
where where
root = IORoot_ dw $ And_ (Only_ $ sysExe "VBoxManage") root = IORoot_ dw $ toAnd_ (sysExe "VBoxManage")
$ Only_ $ IOTest_ name $ vmExists vm $ IOTest_ name $ vmExists vm
name = unwords ["test if", vm, "exists"] name = unwords ["test if", vm, "exists"]
c = "VirtualBoxVM" c = "VirtualBoxVM"
vm = "win8raw" vm = "win8raw"
@ -271,18 +272,9 @@ vmDynamicWorkspace = sometimes1 "virtualbox workspace" "windows 8 VM" root
, dwCmd = Just $ spawnCmd "vbox-start" [vm] , dwCmd = Just $ spawnCmd "vbox-start" [vm]
} }
-- -- TODO this shell command is hilariously slow and kills my fast startup time
-- vmExists :: String -> IO (Maybe String)
-- vmExists vm =
-- go <$> tryIOError (readCreateProcessWithExitCode' pr "")
-- where
-- pr = proc' "VBoxManage" ["showvminfo", vm]
-- go (Right (ExitSuccess, _, _)) = Nothing
-- go (Right (ExitFailure _, _, _)) = Just $ "VM not found: " ++ vm
-- go (Left e) = Just $ show e
xsaneDynamicWorkspace :: Sometimes DynWorkspace xsaneDynamicWorkspace :: Sometimes DynWorkspace
xsaneDynamicWorkspace = sometimesIO_ "scanner workspace" "xsane" tree dw xsaneDynamicWorkspace = Sometimes "scanner workspace" xpfXSANE
[Subfeature (IORoot_ dw tree) "xsane"]
where where
tree = Only_ $ sysExe "xsane" tree = Only_ $ sysExe "xsane"
dw = DynWorkspace dw = DynWorkspace

View File

@ -95,13 +95,18 @@ runDevMenu = sometimesIO_ "device manager" "rofi devices" t x
-- TODO test that bluetooth interface exists -- TODO test that bluetooth interface exists
runBTMenu :: SometimesX runBTMenu :: SometimesX
runBTMenu = sometimesExeArgs "bluetooth selector" "rofi bluetooth" False runBTMenu = Sometimes "bluetooth selector" xpfBluetooth
myDmenuBluetooth $ "-c":themeArgs "#0044bb" [Subfeature (IORoot_ cmd tree) "rofi bluetooth"]
where
cmd = spawnCmd myDmenuBluetooth $ "-c":themeArgs "#0044bb"
tree = Only_ $ sysExe myDmenuBluetooth
runVPNMenu :: SometimesX runVPNMenu :: SometimesX
runVPNMenu = sometimesIO_ "VPN selector" "rofi VPN" tree $ spawnCmd myDmenuVPN runVPNMenu = Sometimes "VPN selector" xpfVPN
$ ["-c"] ++ themeArgs "#007766" ++ myDmenuMatchingArgs [Subfeature (IORoot_ cmd tree) "rofi VPN"]
where where
cmd = spawnCmd myDmenuVPN
$ ["-c"] ++ themeArgs "#007766" ++ myDmenuMatchingArgs
tree = toAnd_ (localExe myDmenuVPN) $ socketExists "expressVPN" tree = toAnd_ (localExe myDmenuVPN) $ socketExists "expressVPN"
$ return "/var/lib/expressvpn/expressvpnd.socket" $ return "/var/lib/expressvpn/expressvpnd.socket"

View File

@ -216,14 +216,15 @@ runNotificationContext =
-- this is required for some vpn's to work properly with network-manager -- this is required for some vpn's to work properly with network-manager
runNetAppDaemon :: Maybe Client -> Sometimes (IO ProcessHandle) runNetAppDaemon :: Maybe Client -> Sometimes (IO ProcessHandle)
runNetAppDaemon cl = sometimesDBus cl "network applet" "NM-applet" tree cmd runNetAppDaemon cl = Sometimes "network applet" xpfVPN
[Subfeature (DBusRoot_ cmd tree cl) "NM-applet"]
where where
tree = toAnd_ (DBusIO $ localExe "nm-applet") $ Bus networkManagerBus tree = toAnd_ (DBusIO $ localExe "nm-applet") $ Bus networkManagerBus
cmd _ = snd <$> spawnPipe "nm-applet" cmd _ = snd <$> spawnPipe "nm-applet"
runToggleBluetooth :: Maybe Client -> SometimesX runToggleBluetooth :: Maybe Client -> SometimesX
runToggleBluetooth cl = runToggleBluetooth cl = Sometimes "bluetooth toggle" xpfBluetooth
sometimesDBus cl "bluetooth toggle" "bluetoothctl" tree cmd [Subfeature (DBusRoot_ cmd tree cl) "bluetoothctl"]
where where
tree = And_ (Only_ $ DBusIO $ sysExe myBluetooth) (Only_ $ Bus btBus) tree = And_ (Only_ $ DBusIO $ sysExe myBluetooth) (Only_ $ Bus btBus)
cmd _ = spawn cmd _ = spawn

View File

@ -136,7 +136,8 @@ runOptimusPrompt' fb = do
#!&& "killall xmonad" #!&& "killall xmonad"
runOptimusPrompt :: SometimesX runOptimusPrompt :: SometimesX
runOptimusPrompt = Sometimes "graphics switcher" xpfOptimus [s] runOptimusPrompt = Sometimes "graphics switcher"
(\x -> xpfOptimus x && xpfBattery x) [s]
where where
s = Subfeature { sfData = r, sfName = "optimus manager" } s = Subfeature { sfData = r, sfName = "optimus manager" }
r = IORoot runOptimusPrompt' t r = IORoot runOptimusPrompt' t

View File

@ -117,11 +117,11 @@ clevoKeyboardSignalDep :: DBusDependency_
clevoKeyboardSignalDep = signalDep clevoKeyboardConfig clevoKeyboardSignalDep = signalDep clevoKeyboardConfig
exportClevoKeyboard :: Maybe Client -> SometimesIO exportClevoKeyboard :: Maybe Client -> SometimesIO
exportClevoKeyboard = exportClevoKeyboard = brightnessExporter xpfClevoBacklight
brightnessExporter [stateFileDep, brightnessFileDep] clevoKeyboardConfig [stateFileDep, brightnessFileDep] clevoKeyboardConfig
clevoKeyboardControls :: Maybe Client -> BrightnessControls clevoKeyboardControls :: Maybe Client -> BrightnessControls
clevoKeyboardControls = brightnessControls clevoKeyboardConfig clevoKeyboardControls = brightnessControls xpfClevoBacklight clevoKeyboardConfig
callGetBrightnessCK :: Client -> IO (Maybe Brightness) callGetBrightnessCK :: Client -> IO (Maybe Brightness)
callGetBrightnessCK = callGetBrightness clevoKeyboardConfig callGetBrightnessCK = callGetBrightness clevoKeyboardConfig

View File

@ -20,6 +20,7 @@ import DBus.Client
import DBus.Internal import DBus.Internal
import qualified DBus.Introspection as I import qualified DBus.Introspection as I
import XMonad.Core (io)
import XMonad.Internal.DBus.Common import XMonad.Internal.DBus.Common
import XMonad.Internal.Dependency import XMonad.Internal.Dependency
@ -51,8 +52,9 @@ data BrightnessControls = BrightnessControls
, bctlDec :: SometimesIO , bctlDec :: SometimesIO
} }
brightnessControls :: BrightnessConfig a b -> Maybe Client -> BrightnessControls brightnessControls :: XPQuery -> BrightnessConfig a b -> Maybe Client
brightnessControls bc client = -> BrightnessControls
brightnessControls q bc client =
BrightnessControls BrightnessControls
{ bctlMax = cb "max brightness" memMax { bctlMax = cb "max brightness" memMax
, bctlMin = cb "min brightness" memMin , bctlMin = cb "min brightness" memMin
@ -60,7 +62,7 @@ brightnessControls bc client =
, bctlDec = cb "decrease brightness" memDec , bctlDec = cb "decrease brightness" memDec
} }
where where
cb = callBacklight client bc cb = callBacklight q client bc
callGetBrightness :: Num c => BrightnessConfig a b -> Client -> IO (Maybe c) callGetBrightness :: Num c => BrightnessConfig a b -> Client -> IO (Maybe c)
callGetBrightness BrightnessConfig { bcPath = p, bcInterface = i } client = callGetBrightness BrightnessConfig { bcPath = p, bcInterface = i } client =
@ -85,12 +87,13 @@ matchSignal BrightnessConfig { bcPath = p, bcInterface = i } cb =
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- | Internal DBus Crap -- | Internal DBus Crap
brightnessExporter :: RealFrac b => [IODependency_] -> BrightnessConfig a b brightnessExporter :: RealFrac b => XPQuery -> [IODependency_]
-> Maybe Client -> SometimesIO -> BrightnessConfig a b -> Maybe Client -> SometimesIO
brightnessExporter deps bc@BrightnessConfig { bcName = n } client = brightnessExporter q deps bc@BrightnessConfig { bcName = n } cl =
sometimesDBus client n (n ++ " exporter") ds (exportBrightnessControls' bc) Sometimes (n ++ " DBus Interface") q [Subfeature root "exporter"]
where where
ds = listToAnds (Bus xmonadBusName) $ fmap DBusIO deps root = DBusRoot_ (exportBrightnessControls' bc) tree cl
tree = listToAnds (Bus xmonadBusName) $ fmap DBusIO deps
exportBrightnessControls' :: RealFrac b => BrightnessConfig a b -> Client -> IO () exportBrightnessControls' :: RealFrac b => BrightnessConfig a b -> Client -> IO ()
exportBrightnessControls' bc client = do exportBrightnessControls' bc client = do
@ -127,12 +130,15 @@ emitBrightness BrightnessConfig{ bcPath = p, bcInterface = i } client cur =
where where
sig = signal p i memCur sig = signal p i memCur
callBacklight :: Maybe Client -> BrightnessConfig a b -> String -> MemberName callBacklight :: XPQuery -> Maybe Client -> BrightnessConfig a b -> String
-> SometimesIO -> MemberName -> SometimesIO
callBacklight client BrightnessConfig { bcPath = p callBacklight q cl BrightnessConfig { bcPath = p
, bcInterface = i , bcInterface = i
, bcName = n } controlName m = , bcName = n } controlName m =
sometimesEndpoint n (unwords [n, controlName]) xmonadBusName p i m client Sometimes (unwords [n, controlName]) q [Subfeature root "method call"]
where
root = DBusRoot_ cmd (Only_ $ Endpoint xmonadBusName p i $ Method_ m) cl
cmd c = io $ void $ callMethod c xmonadBusName p i m
bodyGetBrightness :: Num a => [Variant] -> Maybe a bodyGetBrightness :: Num a => [Variant] -> Maybe a
bodyGetBrightness [b] = fromIntegral <$> (fromVariant b :: Maybe Int32) bodyGetBrightness [b] = fromIntegral <$> (fromVariant b :: Maybe Int32)

View File

@ -99,11 +99,11 @@ intelBacklightSignalDep :: DBusDependency_
intelBacklightSignalDep = signalDep intelBacklightConfig intelBacklightSignalDep = signalDep intelBacklightConfig
exportIntelBacklight :: Maybe Client -> SometimesIO exportIntelBacklight :: Maybe Client -> SometimesIO
exportIntelBacklight = exportIntelBacklight = brightnessExporter xpfIntelBacklight
brightnessExporter [curFileDep, maxFileDep] intelBacklightConfig [curFileDep, maxFileDep] intelBacklightConfig
intelBacklightControls :: Maybe Client -> BrightnessControls intelBacklightControls :: Maybe Client -> BrightnessControls
intelBacklightControls = brightnessControls intelBacklightConfig intelBacklightControls = brightnessControls xpfIntelBacklight intelBacklightConfig
callGetBrightnessIB :: Client -> IO (Maybe Brightness) callGetBrightnessIB :: Client -> IO (Maybe Brightness)
callGetBrightnessIB = callGetBrightness intelBacklightConfig callGetBrightnessIB = callGetBrightness intelBacklightConfig

View File

@ -30,6 +30,7 @@ module XMonad.Internal.Dependency
-- configuration -- configuration
, XParams(..) , XParams(..)
, XPFeatures(..) , XPFeatures(..)
, XPQuery
-- dependency tree types -- dependency tree types
, Root(..) , Root(..)
@ -187,12 +188,14 @@ printMsg :: FMsg -> FIO ()
printMsg (FMsg fn n (Msg ll m)) = do printMsg (FMsg fn n (Msg ll m)) = do
xl <- asks xpLogLevel xl <- asks xpLogLevel
p <- io getProgName p <- io getProgName
io $ when (ll <= xl) $ putStrLn $ unwords [ bracket p io $ when (ll <= xl) $ putStrLn $ unwords $ s p
where
s p = [ bracket p
, bracket $ show ll , bracket $ show ll
, bracket fn , bracket fn
, bracket $ fromMaybe "<toplevel>" n
, m
] ]
++ maybe [] ((:[]) . bracket) n
++ [m]
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- | Feature status -- | Feature status
@ -263,7 +266,7 @@ data FallbackStack p = FallbackBottom (Always p)
-- | Feature that might not be present -- | Feature that might not be present
-- This is like an Always except it doesn't fall back on a guaranteed monadic -- This is like an Always except it doesn't fall back on a guaranteed monadic
-- action -- action
data Sometimes a = Sometimes String (XPFeatures -> Bool) (Sometimes_ a) data Sometimes a = Sometimes String XPQuery (Sometimes_ a)
-- | Feature that might not be present (inner data) -- | Feature that might not be present (inner data)
type Sometimes_ a = [SubfeatureRoot a] type Sometimes_ a = [SubfeatureRoot a]
@ -485,6 +488,7 @@ data XPFeatures = XPFeatures
, xpfBluetooth :: Bool , xpfBluetooth :: Bool
, xpfIntelBacklight :: Bool , xpfIntelBacklight :: Bool
, xpfClevoBacklight :: Bool , xpfClevoBacklight :: Bool
, xpfBattery :: Bool
} }
instance FromJSON XPFeatures where instance FromJSON XPFeatures where
@ -497,6 +501,7 @@ instance FromJSON XPFeatures where
<*> o .:+ "bluetooth" <*> o .:+ "bluetooth"
<*> o .:+ "intel_backlight" <*> o .:+ "intel_backlight"
<*> o .:+ "clevo_backlight" <*> o .:+ "clevo_backlight"
<*> o .:+ "battery"
defParams :: XParams defParams :: XParams
defParams = XParams defParams = XParams
@ -510,12 +515,16 @@ defXPFeatures = XPFeatures
, xpfVirtualBox = False , xpfVirtualBox = False
, xpfXSANE = False , xpfXSANE = False
, xpfWireless = False , xpfWireless = False
-- TODO this might be broken down into different flags (expressvpn, etc)
, xpfVPN = False , xpfVPN = False
, xpfBluetooth = False , xpfBluetooth = False
, xpfIntelBacklight = False , xpfIntelBacklight = False
, xpfClevoBacklight = False , xpfClevoBacklight = False
, xpfBattery = False
} }
type XPQuery = XPFeatures -> Bool
data Cache = Cache data Cache = Cache
{ --cIO :: forall p. Memoizable p => H.HashMap (IODependency p) (Result p) { --cIO :: forall p. Memoizable p => H.HashMap (IODependency p) (Result p)
cIO_ :: H.HashMap IODependency_ Result_ cIO_ :: H.HashMap IODependency_ Result_
@ -555,12 +564,14 @@ infix .:+
evalSometimesMsg :: Sometimes a -> FIO (Either [FMsg] (a, [FMsg])) evalSometimesMsg :: Sometimes a -> FIO (Either [FMsg] (a, [FMsg]))
evalSometimesMsg (Sometimes n u xs) = do evalSometimesMsg (Sometimes n u xs) = do
r <- asks (u . xpFeatures) r <- asks (u . xpFeatures)
if not r then return $ Left [FMsg n Nothing (Msg Debug "disabled")] else do if not r then return $ Left [dis n] else do
PostSometimes { psSuccess = s, psFailed = fs } <- testSometimes xs PostSometimes { psSuccess = s, psFailed = fs } <- testSometimes xs
let fs' = failedMsgs n fs let fs' = failedMsgs n fs
return $ case s of return $ case s of
(Just p) -> Right $ second (++ fs') $ passActMsg n p (Just p) -> Right $ second (++ fs') $ passActMsg n p
_ -> Left fs' _ -> Left fs'
where
dis name = FMsg name Nothing (Msg Debug "feature disabled")
evalAlwaysMsg :: Always a -> FIO (a, [FMsg]) evalAlwaysMsg :: Always a -> FIO (a, [FMsg])
evalAlwaysMsg (Always n x) = do evalAlwaysMsg (Always n x) = do
@ -932,7 +943,7 @@ ioRoot (DBusRoot_ a t cl) = DBusRoot_ (io . a) t cl
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- | Feature constructors -- | Feature constructors
sometimes1_ :: (XPFeatures -> Bool) -> String -> String -> Root a -> Sometimes a sometimes1_ :: XPQuery -> String -> String -> Root a -> Sometimes a
sometimes1_ x fn n t = Sometimes fn x sometimes1_ x fn n t = Sometimes fn x
[Subfeature{ sfData = t, sfName = n }] [Subfeature{ sfData = t, sfName = n }]