{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE UndecidableSuperClasses #-}
{-# LANGUAGE PolyKinds #-}

module IHaskell.Display.Widgets.Interactive
  ( interactive
  , uncurryHList
  , Rec (..)
  , Argument(..)
  ) where

import           Data.Text
import           Data.Proxy

#if MIN_VERSION_vinyl(0,9,0)
import           Data.Vinyl.Core (Rec(..))
import           Data.Vinyl.Recursive (recordToList, rmap, rtraverse)
#else
import           Data.Vinyl.Core (Rec(..), recordToList, rmap, rtraverse)
#endif
import           Data.Vinyl.Functor (Identity(..), Const(..))
import           Data.Vinyl.Derived (HList)
import           Data.Vinyl.Lens (type (∈))
import           Data.Vinyl.TypeLevel (RecAll)

import           IHaskell.Display

import           IHaskell.Display.Widgets.Types
import           IHaskell.Display.Widgets.Common
import qualified IHaskell.Display.Widgets.Singletons as S (SField, Field(..))

import           IHaskell.Display.Widgets.Box.Box
import           IHaskell.Display.Widgets.Bool.CheckBox
import           IHaskell.Display.Widgets.String.Text
import           IHaskell.Display.Widgets.Int.BoundedInt.IntSlider
import           IHaskell.Display.Widgets.Float.BoundedFloat.FloatSlider
import           IHaskell.Display.Widgets.Output


data WidgetConf a where
        WidgetConf ::
            (RecAll Attr (WidgetFields (SuitableWidget a)) ToPairs,
             FromWidget a) =>
            WrappedWidget (SuitableWidget a) (SuitableHandler a)
              (SuitableField a)
              a
              -> WidgetConf a


type family WithTypes (ts :: [*]) (r :: *) :: * where
        WithTypes '[] r = r
        WithTypes (x ': xs) r = (x -> WithTypes xs r)

uncurryHList :: WithTypes ts r -> HList ts -> r
uncurryHList :: forall (ts :: [*]) r. WithTypes ts r -> HList ts -> r
uncurryHList WithTypes ts r
f Rec Identity ts
RNil = WithTypes ts r
f
uncurryHList WithTypes ts r
f (Identity r
x :& Rec Identity rs
xs) = forall (ts :: [*]) r. WithTypes ts r -> HList ts -> r
uncurryHList (WithTypes ts r
f r
x) Rec Identity rs
xs

-- Consistent type variables are required to make things play nicely with vinyl

data Constructor a where
        Constructor ::
            RecAll Attr (WidgetFields (SuitableWidget a)) ToPairs =>
            IO (IPythonWidget (SuitableWidget a)) -> Constructor a

newtype Getter a = Getter (IPythonWidget (SuitableWidget a) -> IO a)

newtype EventSetter a = EventSetter (IPythonWidget (SuitableWidget a) -> IO () -> IO ())

newtype Initializer a = Initializer (IPythonWidget (SuitableWidget a) -> Argument a -> IO ())


data RequiredWidget a where
        RequiredWidget ::
            RecAll Attr (WidgetFields (SuitableWidget a)) ToPairs =>
            IPythonWidget (SuitableWidget a) -> RequiredWidget a

-- Zipping vinyl records in various ways
applyGetters :: Rec Getter ts -> Rec RequiredWidget ts -> IO (HList ts)
applyGetters :: forall (ts :: [*]).
Rec Getter ts -> Rec RequiredWidget ts -> IO (HList ts)
applyGetters Rec Getter ts
RNil Rec RequiredWidget ts
RNil = forall (m :: * -> *) a. Monad m => a -> m a
return forall {u} (a :: u -> *). Rec a '[]
RNil
applyGetters (Getter IPythonWidget (SuitableWidget r) -> IO r
getter :& Rec Getter rs
gs) (RequiredWidget IPythonWidget (SuitableWidget r)
widget :& Rec RequiredWidget rs
ws) = do
  r
val <- IPythonWidget (SuitableWidget r) -> IO r
getter IPythonWidget (SuitableWidget r)
widget
  HList rs
rest <- forall (ts :: [*]).
Rec Getter ts -> Rec RequiredWidget ts -> IO (HList ts)
applyGetters Rec Getter rs
gs Rec RequiredWidget rs
ws
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Identity a
Identity r
val forall {u} (a :: u -> *) (r :: u) (rs :: [u]).
a r -> Rec a rs -> Rec a (r : rs)
:& HList rs
rest

applyEventSetters :: Rec EventSetter ts -> Rec RequiredWidget ts -> IO () -> IO ()
applyEventSetters :: forall (ts :: [*]).
Rec EventSetter ts -> Rec RequiredWidget ts -> IO () -> IO ()
applyEventSetters Rec EventSetter ts
RNil Rec RequiredWidget ts
RNil IO ()
_ = forall (m :: * -> *) a. Monad m => a -> m a
return ()
applyEventSetters (EventSetter IPythonWidget (SuitableWidget r) -> IO () -> IO ()
setter :& Rec EventSetter rs
xs) (RequiredWidget IPythonWidget (SuitableWidget r)
widget :& Rec RequiredWidget rs
ws) IO ()
handler = do
  IPythonWidget (SuitableWidget r) -> IO () -> IO ()
setter IPythonWidget (SuitableWidget r)
widget IO ()
handler
  forall (ts :: [*]).
Rec EventSetter ts -> Rec RequiredWidget ts -> IO () -> IO ()
applyEventSetters Rec EventSetter rs
xs Rec RequiredWidget rs
ws IO ()
handler

setInitialValues :: Rec Initializer ts -> Rec RequiredWidget ts -> Rec Argument ts -> IO ()
setInitialValues :: forall (ts :: [*]).
Rec Initializer ts
-> Rec RequiredWidget ts -> Rec Argument ts -> IO ()
setInitialValues Rec Initializer ts
RNil Rec RequiredWidget ts
RNil Rec Argument ts
RNil = forall (m :: * -> *) a. Monad m => a -> m a
return ()
setInitialValues (Initializer IPythonWidget (SuitableWidget r) -> Argument r -> IO ()
initialize :& Rec Initializer rs
fs) (RequiredWidget IPythonWidget (SuitableWidget r)
widget :& Rec RequiredWidget rs
ws) (Argument r
argument :& Rec Argument rs
vs) = do
  IPythonWidget (SuitableWidget r) -> Argument r -> IO ()
initialize IPythonWidget (SuitableWidget r)
widget Argument r
argument
  forall (ts :: [*]).
Rec Initializer ts
-> Rec RequiredWidget ts -> Rec Argument ts -> IO ()
setInitialValues Rec Initializer rs
fs Rec RequiredWidget rs
ws Rec Argument rs
vs

extractConstructor :: WidgetConf x -> Constructor x
extractConstructor :: forall x. WidgetConf x -> Constructor x
extractConstructor (WidgetConf WrappedWidget
  (SuitableWidget x) (SuitableHandler x) (SuitableField x) x
wr) = forall a.
RecAll Attr (WidgetFields (SuitableWidget a)) ToPairs =>
IO (IPythonWidget (SuitableWidget a)) -> Constructor a
Constructor forall a b. (a -> b) -> a -> b
$ forall (w :: WidgetType) (h :: Field) (f :: Field) a.
WrappedWidget w h f a -> IO (IPythonWidget w)
construct WrappedWidget
  (SuitableWidget x) (SuitableHandler x) (SuitableField x) x
wr

extractGetter :: WidgetConf x -> Getter x
extractGetter :: forall x. WidgetConf x -> Getter x
extractGetter (WidgetConf WrappedWidget
  (SuitableWidget x) (SuitableHandler x) (SuitableField x) x
wr) = forall a. (IPythonWidget (SuitableWidget a) -> IO a) -> Getter a
Getter forall a b. (a -> b) -> a -> b
$ forall (w :: WidgetType) (h :: Field) (f :: Field) a.
WrappedWidget w h f a -> IPythonWidget w -> IO a
getValue WrappedWidget
  (SuitableWidget x) (SuitableHandler x) (SuitableField x) x
wr

extractEventSetter :: WidgetConf x -> EventSetter x
extractEventSetter :: forall x. WidgetConf x -> EventSetter x
extractEventSetter (WidgetConf WrappedWidget
  (SuitableWidget x) (SuitableHandler x) (SuitableField x) x
wr) = forall a.
(IPythonWidget (SuitableWidget a) -> IO () -> IO ())
-> EventSetter a
EventSetter forall a b. (a -> b) -> a -> b
$ forall (w :: WidgetType) (h :: Field) (f :: Field) a.
WrappedWidget w h f a -> IPythonWidget w -> IO () -> IO ()
setEvent WrappedWidget
  (SuitableWidget x) (SuitableHandler x) (SuitableField x) x
wr

extractInitializer :: WidgetConf x -> Initializer x
extractInitializer :: forall x. WidgetConf x -> Initializer x
extractInitializer WidgetConf{} = forall a.
(IPythonWidget (SuitableWidget a) -> Argument a -> IO ())
-> Initializer a
Initializer forall a.
FromWidget a =>
IPythonWidget (SuitableWidget a) -> Argument a -> IO ()
initializer

createWidget :: Constructor a -> IO (RequiredWidget a)
createWidget :: forall a. Constructor a -> IO (RequiredWidget a)
createWidget (Constructor IO (IPythonWidget (SuitableWidget a))
con) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a.
RecAll Attr (WidgetFields (SuitableWidget a)) ToPairs =>
IPythonWidget (SuitableWidget a) -> RequiredWidget a
RequiredWidget IO (IPythonWidget (SuitableWidget a))
con

mkChildren :: Rec RequiredWidget a -> [ChildWidget]
mkChildren :: forall (a :: [*]). Rec RequiredWidget a -> [ChildWidget]
mkChildren Rec RequiredWidget a
widgets =
  let childRecord :: Rec (Const ChildWidget) a
childRecord = forall {u} (f :: u -> *) (g :: u -> *) (rs :: [u]).
(forall (x :: u). f x -> g x) -> Rec f rs -> Rec g rs
rmap (\(RequiredWidget IPythonWidget (SuitableWidget x)
w) -> forall k a (b :: k). a -> Const a b
Const (forall (w :: WidgetType).
RecAll Attr (WidgetFields w) ToPairs =>
IPythonWidget w -> ChildWidget
ChildWidget IPythonWidget (SuitableWidget x)
w)) Rec RequiredWidget a
widgets
  in forall {u} a (rs :: [u]). Rec (Const a) rs -> [a]
recordToList Rec (Const ChildWidget) a
childRecord

class MakeConfs (ts :: [*]) where
  mkConfs :: proxy ts -> Rec WidgetConf ts

instance MakeConfs '[] where
  mkConfs :: forall (proxy :: [*] -> *). proxy '[] -> Rec WidgetConf '[]
mkConfs proxy '[]
_ = forall {u} (a :: u -> *). Rec a '[]
RNil

instance (FromWidget t, MakeConfs ts) => MakeConfs (t ': ts) where
  mkConfs :: forall (proxy :: [*] -> *).
proxy (t : ts) -> Rec WidgetConf (t : ts)
mkConfs proxy (t : ts)
_ = forall a.
(RecAll Attr (WidgetFields (SuitableWidget a)) ToPairs,
 FromWidget a) =>
WrappedWidget
  (SuitableWidget a) (SuitableHandler a) (SuitableField a) a
-> WidgetConf a
WidgetConf forall a.
FromWidget a =>
WrappedWidget
  (SuitableWidget a) (SuitableHandler a) (SuitableField a) a
wrapped forall {u} (a :: u -> *) (r :: u) (rs :: [u]).
a r -> Rec a rs -> Rec a (r : rs)
:& forall (ts :: [*]) (proxy :: [*] -> *).
MakeConfs ts =>
proxy ts -> Rec WidgetConf ts
mkConfs (forall {k} (t :: k). Proxy t
Proxy :: Proxy ts)

interactive :: (IHaskellDisplay r, MakeConfs ts)
            => (HList ts -> r) -> Rec Argument ts -> IO Box
interactive :: forall r (ts :: [*]).
(IHaskellDisplay r, MakeConfs ts) =>
(HList ts -> r) -> Rec Argument ts -> IO Box
interactive HList ts -> r
func =
  let confs :: Rec WidgetConf ts
confs = forall (ts :: [*]) (proxy :: [*] -> *).
MakeConfs ts =>
proxy ts -> Rec WidgetConf ts
mkConfs forall {k} (t :: k). Proxy t
Proxy
  in forall r (ts :: [*]).
IHaskellDisplay r =>
(HList ts -> r) -> Rec WidgetConf ts -> Rec Argument ts -> IO Box
liftToWidgets HList ts -> r
func Rec WidgetConf ts
confs

-- | Transform a function (HList ts -> r) to one which: 1) Uses widgets to accept the arguments 2)
-- Accepts initial values for the arguments 3) Creates a compound Box widget with an embedded
-- OutputWidget for display
liftToWidgets :: IHaskellDisplay r
              => (HList ts -> r) -> Rec WidgetConf ts -> Rec Argument ts -> IO Box
liftToWidgets :: forall r (ts :: [*]).
IHaskellDisplay r =>
(HList ts -> r) -> Rec WidgetConf ts -> Rec Argument ts -> IO Box
liftToWidgets HList ts -> r
func Rec WidgetConf ts
rc Rec Argument ts
initvals = do
  let constructors :: Rec Constructor ts
constructors = forall {u} (f :: u -> *) (g :: u -> *) (rs :: [u]).
(forall (x :: u). f x -> g x) -> Rec f rs -> Rec g rs
rmap forall x. WidgetConf x -> Constructor x
extractConstructor Rec WidgetConf ts
rc
      getters :: Rec Getter ts
getters = forall {u} (f :: u -> *) (g :: u -> *) (rs :: [u]).
(forall (x :: u). f x -> g x) -> Rec f rs -> Rec g rs
rmap forall x. WidgetConf x -> Getter x
extractGetter Rec WidgetConf ts
rc
      eventSetters :: Rec EventSetter ts
eventSetters = forall {u} (f :: u -> *) (g :: u -> *) (rs :: [u]).
(forall (x :: u). f x -> g x) -> Rec f rs -> Rec g rs
rmap forall x. WidgetConf x -> EventSetter x
extractEventSetter Rec WidgetConf ts
rc
      initializers :: Rec Initializer ts
initializers = forall {u} (f :: u -> *) (g :: u -> *) (rs :: [u]).
(forall (x :: u). f x -> g x) -> Rec f rs -> Rec g rs
rmap forall x. WidgetConf x -> Initializer x
extractInitializer Rec WidgetConf ts
rc

  Box
bx <- IO Box
mkBox
  OutputWidget
out <- IO OutputWidget
mkOutput

  -- Create a list of widgets
  Rec RequiredWidget ts
widgets <- forall {u} (h :: * -> *) (f :: u -> *) (g :: u -> *) (rs :: [u]).
Applicative h =>
(forall (x :: u). f x -> h (g x)) -> Rec f rs -> h (Rec g rs)
rtraverse forall a. Constructor a -> IO (RequiredWidget a)
createWidget Rec Constructor ts
constructors

  let handler :: IO ()
handler = do
        HList ts
vals <- forall (ts :: [*]).
Rec Getter ts -> Rec RequiredWidget ts -> IO (HList ts)
applyGetters Rec Getter ts
getters Rec RequiredWidget ts
widgets
        forall a. IHaskellDisplay a => OutputWidget -> a -> IO ()
replaceOutput OutputWidget
out forall a b. (a -> b) -> a -> b
$ HList ts -> r
func HList ts
vals

  -- Apply handler to all widgets
  forall (ts :: [*]).
Rec EventSetter ts -> Rec RequiredWidget ts -> IO () -> IO ()
applyEventSetters Rec EventSetter ts
eventSetters Rec RequiredWidget ts
widgets IO ()
handler

  -- Set initial values for all widgets
  forall (ts :: [*]).
Rec Initializer ts
-> Rec RequiredWidget ts -> Rec Argument ts -> IO ()
setInitialValues Rec Initializer ts
initializers Rec RequiredWidget ts
widgets Rec Argument ts
initvals
  -- applyValueSetters valueSetters widgets $ getList defvals
  -- setField out Width 500
  -- TODO This can't be set right now since we switched FlexBox to a regular
  --      Box. This is a styling/layout parameter now but these haven't been implemented yet.
  -- setField bx Orientation VerticalOrientation

  -- Set children for the Box
  let children :: [ChildWidget]
children = forall (a :: [*]). Rec RequiredWidget a -> [ChildWidget]
mkChildren Rec RequiredWidget ts
widgets
  forall (f :: Field) (w :: WidgetType).
(f ∈ WidgetFields w, IHaskellWidget (IPythonWidget w),
 ToPairs (Attr f)) =>
IPythonWidget w -> SField f -> FieldType f -> IO ()
setField Box
bx forall {a :: Field}. (a ~ 'Children) => SField a
Children forall a b. (a -> b) -> a -> b
$ [ChildWidget]
children forall a. [a] -> [a] -> [a]
++ [forall (w :: WidgetType).
RecAll Attr (WidgetFields w) ToPairs =>
IPythonWidget w -> ChildWidget
ChildWidget OutputWidget
out]

  forall (m :: * -> *) a. Monad m => a -> m a
return Box
bx


data WrappedWidget w h f a where
        WrappedWidget ::
            (FieldType h ~ IO (), FieldType f ~ a, h  WidgetFields w,
             f  WidgetFields w, ToPairs (Attr h),
             IHaskellWidget (IPythonWidget w), ToPairs (Attr f)) =>
            IO (IPythonWidget w) ->
              S.SField h -> S.SField f -> WrappedWidget w h f a

construct :: WrappedWidget w h f a -> IO (IPythonWidget w)
construct :: forall (w :: WidgetType) (h :: Field) (f :: Field) a.
WrappedWidget w h f a -> IO (IPythonWidget w)
construct (WrappedWidget IO (IPythonWidget w)
cs SField h
_ SField f
_) = IO (IPythonWidget w)
cs

getValue :: WrappedWidget w h f a -> IPythonWidget w -> IO a
getValue :: forall (w :: WidgetType) (h :: Field) (f :: Field) a.
WrappedWidget w h f a -> IPythonWidget w -> IO a
getValue (WrappedWidget IO (IPythonWidget w)
_ SField h
_ SField f
field) IPythonWidget w
widget = forall (f :: Field) (w :: WidgetType).
(f ∈ WidgetFields w) =>
IPythonWidget w -> SField f -> IO (FieldType f)
getField IPythonWidget w
widget SField f
field

setEvent :: WrappedWidget w h f a -> IPythonWidget w -> IO () -> IO ()
setEvent :: forall (w :: WidgetType) (h :: Field) (f :: Field) a.
WrappedWidget w h f a -> IPythonWidget w -> IO () -> IO ()
setEvent (WrappedWidget IO (IPythonWidget w)
_ SField h
h SField f
_) IPythonWidget w
widget = forall (f :: Field) (w :: WidgetType).
(f ∈ WidgetFields w, IHaskellWidget (IPythonWidget w),
 ToPairs (Attr f)) =>
IPythonWidget w -> SField f -> FieldType f -> IO ()
setField IPythonWidget w
widget SField h
h

class RecAll Attr (WidgetFields (SuitableWidget a)) ToPairs => FromWidget a where
  type SuitableWidget a :: WidgetType
  type SuitableHandler a :: S.Field
  type SuitableField a :: S.Field
  data Argument a
  initializer :: IPythonWidget (SuitableWidget a) -> Argument a -> IO ()
  wrapped :: WrappedWidget (SuitableWidget a) (SuitableHandler a) (SuitableField a) a

instance FromWidget Bool where
  type SuitableWidget Bool = 'CheckBoxType
  type SuitableHandler Bool = 'S.ChangeHandler
  type SuitableField Bool = 'S.BoolValue
  data Argument Bool = BoolVal Bool
  initializer :: IPythonWidget (SuitableWidget Bool) -> Argument Bool -> IO ()
initializer IPythonWidget (SuitableWidget Bool)
w (BoolVal Bool
b) = forall (f :: Field) (w :: WidgetType).
(f ∈ WidgetFields w, IHaskellWidget (IPythonWidget w),
 ToPairs (Attr f)) =>
IPythonWidget w -> SField f -> FieldType f -> IO ()
setField IPythonWidget (SuitableWidget Bool)
w forall {a :: Field}. (a ~ 'BoolValue) => SField a
BoolValue Bool
b
  wrapped :: WrappedWidget
  (SuitableWidget Bool)
  (SuitableHandler Bool)
  (SuitableField Bool)
  Bool
wrapped = forall (h :: Field) (f :: Field) a (w :: WidgetType).
(FieldType h ~ IO (), FieldType f ~ a, h ∈ WidgetFields w,
 f ∈ WidgetFields w, ToPairs (Attr h),
 IHaskellWidget (IPythonWidget w), ToPairs (Attr f)) =>
IO (IPythonWidget w)
-> SField h -> SField f -> WrappedWidget w h f a
WrappedWidget IO (IPythonWidget 'CheckBoxType)
mkCheckBox forall {a :: Field}. (a ~ 'ChangeHandler) => SField a
ChangeHandler forall {a :: Field}. (a ~ 'BoolValue) => SField a
BoolValue

instance FromWidget Text where
  type SuitableWidget Text = 'TextType
  type SuitableHandler Text = 'S.SubmitHandler
  type SuitableField Text = 'S.StringValue
  data Argument Text = TextVal Text
  initializer :: IPythonWidget (SuitableWidget Text) -> Argument Text -> IO ()
initializer IPythonWidget (SuitableWidget Text)
w (TextVal Text
txt) = forall (f :: Field) (w :: WidgetType).
(f ∈ WidgetFields w, IHaskellWidget (IPythonWidget w),
 ToPairs (Attr f)) =>
IPythonWidget w -> SField f -> FieldType f -> IO ()
setField IPythonWidget (SuitableWidget Text)
w forall {a :: Field}. (a ~ 'StringValue) => SField a
StringValue Text
txt
  wrapped :: WrappedWidget
  (SuitableWidget Text)
  (SuitableHandler Text)
  (SuitableField Text)
  Text
wrapped = forall (h :: Field) (f :: Field) a (w :: WidgetType).
(FieldType h ~ IO (), FieldType f ~ a, h ∈ WidgetFields w,
 f ∈ WidgetFields w, ToPairs (Attr h),
 IHaskellWidget (IPythonWidget w), ToPairs (Attr f)) =>
IO (IPythonWidget w)
-> SField h -> SField f -> WrappedWidget w h f a
WrappedWidget IO (IPythonWidget 'TextType)
mkText forall {a :: Field}. (a ~ 'SubmitHandler) => SField a
SubmitHandler forall {a :: Field}. (a ~ 'StringValue) => SField a
StringValue

instance FromWidget Integer where
  type SuitableWidget Integer = 'IntSliderType
  type SuitableHandler Integer = 'S.ChangeHandler
  type SuitableField Integer = 'S.IntValue
  data Argument Integer = IntVal Integer
                      | IntRange (Integer, Integer, Integer)
  wrapped :: WrappedWidget
  (SuitableWidget Integer)
  (SuitableHandler Integer)
  (SuitableField Integer)
  Integer
wrapped = forall (h :: Field) (f :: Field) a (w :: WidgetType).
(FieldType h ~ IO (), FieldType f ~ a, h ∈ WidgetFields w,
 f ∈ WidgetFields w, ToPairs (Attr h),
 IHaskellWidget (IPythonWidget w), ToPairs (Attr f)) =>
IO (IPythonWidget w)
-> SField h -> SField f -> WrappedWidget w h f a
WrappedWidget IO (IPythonWidget 'IntSliderType)
mkIntSlider forall {a :: Field}. (a ~ 'ChangeHandler) => SField a
ChangeHandler forall {a :: Field}. (a ~ 'IntValue) => SField a
IntValue
  initializer :: IPythonWidget (SuitableWidget Integer) -> Argument Integer -> IO ()
initializer IPythonWidget (SuitableWidget Integer)
w (IntVal Integer
int) = forall (f :: Field) (w :: WidgetType).
(f ∈ WidgetFields w, IHaskellWidget (IPythonWidget w),
 ToPairs (Attr f)) =>
IPythonWidget w -> SField f -> FieldType f -> IO ()
setField IPythonWidget (SuitableWidget Integer)
w forall {a :: Field}. (a ~ 'IntValue) => SField a
IntValue Integer
int
  initializer IPythonWidget (SuitableWidget Integer)
w (IntRange (Integer
v, Integer
l, Integer
u)) = do
    forall (f :: Field) (w :: WidgetType).
(f ∈ WidgetFields w, IHaskellWidget (IPythonWidget w),
 ToPairs (Attr f)) =>
IPythonWidget w -> SField f -> FieldType f -> IO ()
setField IPythonWidget (SuitableWidget Integer)
w forall {a :: Field}. (a ~ 'IntValue) => SField a
IntValue Integer
v
    forall (f :: Field) (w :: WidgetType).
(f ∈ WidgetFields w, IHaskellWidget (IPythonWidget w),
 ToPairs (Attr f)) =>
IPythonWidget w -> SField f -> FieldType f -> IO ()
setField IPythonWidget (SuitableWidget Integer)
w forall {a :: Field}. (a ~ 'MinInt) => SField a
MinInt Integer
l
    forall (f :: Field) (w :: WidgetType).
(f ∈ WidgetFields w, IHaskellWidget (IPythonWidget w),
 ToPairs (Attr f)) =>
IPythonWidget w -> SField f -> FieldType f -> IO ()
setField IPythonWidget (SuitableWidget Integer)
w forall {a :: Field}. (a ~ 'MaxInt) => SField a
MaxInt Integer
u

instance FromWidget Double where
  type SuitableWidget Double = 'FloatSliderType
  type SuitableHandler Double = 'S.ChangeHandler
  type SuitableField Double = 'S.FloatValue
  data Argument Double = FloatVal Double
                     | FloatRange (Double, Double, Double)
  wrapped :: WrappedWidget
  (SuitableWidget Double)
  (SuitableHandler Double)
  (SuitableField Double)
  Double
wrapped = forall (h :: Field) (f :: Field) a (w :: WidgetType).
(FieldType h ~ IO (), FieldType f ~ a, h ∈ WidgetFields w,
 f ∈ WidgetFields w, ToPairs (Attr h),
 IHaskellWidget (IPythonWidget w), ToPairs (Attr f)) =>
IO (IPythonWidget w)
-> SField h -> SField f -> WrappedWidget w h f a
WrappedWidget IO (IPythonWidget 'FloatSliderType)
mkFloatSlider forall {a :: Field}. (a ~ 'ChangeHandler) => SField a
ChangeHandler forall {a :: Field}. (a ~ 'FloatValue) => SField a
FloatValue
  initializer :: IPythonWidget (SuitableWidget Double) -> Argument Double -> IO ()
initializer IPythonWidget (SuitableWidget Double)
w (FloatVal Double
d) = forall (f :: Field) (w :: WidgetType).
(f ∈ WidgetFields w, IHaskellWidget (IPythonWidget w),
 ToPairs (Attr f)) =>
IPythonWidget w -> SField f -> FieldType f -> IO ()
setField IPythonWidget (SuitableWidget Double)
w forall {a :: Field}. (a ~ 'FloatValue) => SField a
FloatValue Double
d
  initializer IPythonWidget (SuitableWidget Double)
w (FloatRange (Double
v, Double
l, Double
u)) = do
    forall (f :: Field) (w :: WidgetType).
(f ∈ WidgetFields w, IHaskellWidget (IPythonWidget w),
 ToPairs (Attr f)) =>
IPythonWidget w -> SField f -> FieldType f -> IO ()
setField IPythonWidget (SuitableWidget Double)
w forall {a :: Field}. (a ~ 'FloatValue) => SField a
FloatValue Double
v
    forall (f :: Field) (w :: WidgetType).
(f ∈ WidgetFields w, IHaskellWidget (IPythonWidget w),
 ToPairs (Attr f)) =>
IPythonWidget w -> SField f -> FieldType f -> IO ()
setField IPythonWidget (SuitableWidget Double)
w forall {a :: Field}. (a ~ 'MinFloat) => SField a
MinFloat Double
l
    forall (f :: Field) (w :: WidgetType).
(f ∈ WidgetFields w, IHaskellWidget (IPythonWidget w),
 ToPairs (Attr f)) =>
IPythonWidget w -> SField f -> FieldType f -> IO ()
setField IPythonWidget (SuitableWidget Double)
w forall {a :: Field}. (a ~ 'MaxFloat) => SField a
MaxFloat Double
u