{-# LANGUAGE GADTSyntax #-}
{-# LANGUAGE KindSignatures #-}
{-# OPTIONS_GHC -Wno-deprecations -Wno-star-is-type #-}

{-
  Copyright 2020 The CodeWorld Authors. All rights reserved.

  Licensed under the Apache License, Version 2.0 (the "License");
  you may not use this file except in compliance with the License.
  You may obtain a copy of the License at

      http://www.apache.org/licenses/LICENSE-2.0

  Unless required by applicable law or agreed to in writing, software
  distributed under the License is distributed on an "AS IS" BASIS,
  WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
  See the License for the specific language governing permissions and
  limitations under the License.
-}

module CodeWorld.App2
  {-# WARNING "This is an experimental API.  It can change at any time." #-}
  ( Application,
    defaultApplication,
    withEventHandler,
    withPicture,
    withMultiEventHandler,
    withMultiPicture,
    subapplication,
    applicationOf,
  )
where

import CodeWorld

data Application :: * -> * where
  App ::
    state ->
    (Int -> Event -> state -> state) ->
    (Int -> state -> Picture) ->
    Application state

defaultApplication :: state -> Application state
defaultApplication :: forall state. state -> Application state
defaultApplication state
s =
  forall state.
state
-> (Int -> Event -> state -> state)
-> (Int -> state -> Picture)
-> Application state
App state
s (forall a b. a -> b -> a
const (forall a b. a -> b -> a
const forall a. a -> a
id)) (forall a b. a -> b -> a
const (forall a b. a -> b -> a
const HasCallStack => Picture
blank))

withEventHandler ::
  (Event -> state -> state) ->
  Application state ->
  Application state
withEventHandler :: forall state.
(Event -> state -> state) -> Application state -> Application state
withEventHandler Event -> state -> state
f (App state
initial Int -> Event -> state -> state
event Int -> state -> Picture
picture) =
  forall state.
state
-> (Int -> Event -> state -> state)
-> (Int -> state -> Picture)
-> Application state
App state
initial (\Int
k Event
ev -> Event -> state -> state
f Event
ev forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Event -> state -> state
event Int
k Event
ev) Int -> state -> Picture
picture

withPicture :: (state -> Picture) -> Application state -> Application state
withPicture :: forall state.
(state -> Picture) -> Application state -> Application state
withPicture state -> Picture
f (App state
initial Int -> Event -> state -> state
event Int -> state -> Picture
picture) =
  forall state.
state
-> (Int -> Event -> state -> state)
-> (Int -> state -> Picture)
-> Application state
App state
initial Int -> Event -> state -> state
event (\Int
k state
s -> state -> Picture
f state
s HasCallStack => Picture -> Picture -> Picture
& Int -> state -> Picture
picture Int
k state
s)

withMultiEventHandler ::
  (Int -> Event -> state -> state) ->
  Application state ->
  Application state
withMultiEventHandler :: forall state.
(Int -> Event -> state -> state)
-> Application state -> Application state
withMultiEventHandler Int -> Event -> state -> state
f (App state
initial Int -> Event -> state -> state
event Int -> state -> Picture
picture) =
  forall state.
state
-> (Int -> Event -> state -> state)
-> (Int -> state -> Picture)
-> Application state
App state
initial (\Int
k Event
ev -> Int -> Event -> state -> state
f Int
k Event
ev forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Event -> state -> state
event Int
k Event
ev) Int -> state -> Picture
picture

withMultiPicture ::
  (Int -> state -> Picture) ->
  Application state ->
  Application state
withMultiPicture :: forall state.
(Int -> state -> Picture) -> Application state -> Application state
withMultiPicture Int -> state -> Picture
f (App state
initial Int -> Event -> state -> state
event Int -> state -> Picture
picture) =
  forall state.
state
-> (Int -> Event -> state -> state)
-> (Int -> state -> Picture)
-> Application state
App state
initial Int -> Event -> state -> state
event (\Int
k state
s -> Int -> state -> Picture
f Int
k state
s HasCallStack => Picture -> Picture -> Picture
& Int -> state -> Picture
picture Int
k state
s)

subapplication ::
  (a -> b) ->
  (b -> a -> a) ->
  Application b ->
  (b -> a) ->
  Application a
subapplication :: forall a b.
(a -> b)
-> (b -> a -> a) -> Application b -> (b -> a) -> Application a
subapplication a -> b
getter b -> a -> a
setter (App b
initial Int -> Event -> b -> b
event Int -> b -> Picture
picture) b -> a
f =
  forall state.
state
-> (Int -> Event -> state -> state)
-> (Int -> state -> Picture)
-> Application state
App
    (b -> a
f b
initial)
    (\Int
k Event
ev a
s -> b -> a -> a
setter (Int -> Event -> b -> b
event Int
k Event
ev (a -> b
getter a
s)) a
s)
    (\Int
k -> Int -> b -> Picture
picture Int
k forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
getter)

applicationOf :: Application world -> IO ()
applicationOf :: forall world. Application world -> IO ()
applicationOf (App world
initial Int -> Event -> world -> world
event Int -> world -> Picture
picture) =
  forall world.
world -> (Event -> world -> world) -> (world -> Picture) -> IO ()
activityOf world
initial (Int -> Event -> world -> world
event Int
0) (Int -> world -> Picture
picture Int
0)