Add NotReady

This commit is contained in:
Ali Abrar 2018-02-27 14:47:23 -05:00
parent e387279b7b
commit ebff8c65d0
3 changed files with 22 additions and 0 deletions

View File

@ -12,6 +12,7 @@ cabal-version: >=1.10
library library
exposed-modules: Reflex.Vty exposed-modules: Reflex.Vty
other-modules: Reflex.Spider.Orphans
build-depends: build-depends:
base, base,
dependent-sum, dependent-sum,

View File

@ -0,0 +1,17 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Reflex.Spider.Orphans where
import Reflex
import Reflex.NotReady.Class
import Reflex.Spider.Internal
-- TODO move this to reflex
instance NotReady (SpiderTimeline x) (SpiderHost x) where
notReadyUntil _ = pure ()
notReady = pure ()
instance HasSpiderTimeline x => NotReady (SpiderTimeline x) (PerformEventT (SpiderTimeline x) (SpiderHost x)) where
notReadyUntil _ = pure ()
notReady = pure ()

View File

@ -1,4 +1,5 @@
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-} {-# LANGUAGE RankNTypes #-}
@ -27,6 +28,8 @@ import Data.Maybe (catMaybes)
import Reflex import Reflex
import Reflex.Host.Class import Reflex.Host.Class
import Reflex.NotReady.Class
import Reflex.Spider.Orphans ()
import qualified Graphics.Vty as V import qualified Graphics.Vty as V
-- | The output of a 'VtyApp'. -- | The output of a 'VtyApp'.
@ -49,6 +52,7 @@ type VtyApp t m =
, Ref m ~ IORef , Ref m ~ IORef
, Ref (HostFrame t) ~ IORef , Ref (HostFrame t) ~ IORef
, MonadRef (HostFrame t) , MonadRef (HostFrame t)
, NotReady t (PerformEventT t m)
) )
=> Event t (V.Event) => Event t (V.Event)
-- ^ Vty input events. -- ^ Vty input events.