{-|
    A Grapefruit example which demonstrates the use of feedback loops.

    A button with one star is shown. Each time, the user clicks on the button, one star is added to
    the caption of the button. The interesting thing about this is that the button’s input
    depends on the button’s output. So you need the 'ArrowLoop' instance of 'UICircuit'.
-}
module Examples.Grapefruit.Simple (

    mainCircuit

) where

    -- Control
    import Control.Applicative as Applicative
#if __GLASGOW_HASKELL__ >= 610
    import Control.Arrow       as Arrow
#else
    import Control.Arrow       as Arrow       hiding (pure)
#endif

    -- FRP.Grapefruit
    import FRP.Grapefruit.Signal.Discrete  as DSignal
    import FRP.Grapefruit.Signal.Segmented as SSignal
    import FRP.Grapefruit.Record           as Record

    -- Graphics.UI.Grapefruit
    import Graphics.UI.Grapefruit.Comp        as UIComp
    import Graphics.UI.Grapefruit.Item        as UIItem
    import Graphics.UI.Grapefruit.Circuit     as UICircuit
    import Graphics.UI.Grapefruit.Backend.Std as StdUIBackend

    -- |The circuit describing the whole application.
    mainCircuit :: (StdUIBackend uiBackend) => UICircuit Window uiBackend era () (DSignal era ())
    mainCircuit = proc () -> do
        rec let

                title = pure "Simple"

                text  = SSignal.scan "*" (const . ('*' :)) push

            X :& Closure ::= closure `With` X :& Push ::= push
                <- window `with` just pushButton
                    -< X :& Title ::= title `With` X :& Text ::= text
        returnA -< closure