Skip to content

Commit

Permalink
Merge branch 'develop' into old-cpp
Browse files Browse the repository at this point in the history
  • Loading branch information
alexfmpe authored Jan 21, 2025
2 parents 454a517 + e4db4ac commit 1e288e5
Show file tree
Hide file tree
Showing 20 changed files with 33 additions and 34 deletions.
2 changes: 0 additions & 2 deletions .ghci

This file was deleted.

2 changes: 1 addition & 1 deletion .github/workflows/haskell.yml
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ jobs:
build:
strategy:
matrix:
ghc: ['8.4.4', '8.6.5', '8.8.4', '8.10.7', '9.0.2', '9.2.5', '9.4.5', '9.6.1', '9.8.2', '9.10.1']
ghc: ['8.4.4', '8.6.5', '8.8.4', '8.10.7', '9.0.2', '9.2.5', '9.4.5', '9.6.1', '9.8.2', '9.10.1', '9.12.1']
os: ['ubuntu-latest', 'macos-latest']
runs-on: ${{ matrix.os }}

Expand Down
5 changes: 5 additions & 0 deletions ChangeLog.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,10 @@
# Revision history for reflex

## 0.9.3.3

* Add support for GHC 9.12
* Loosen version bounds

## 0.9.3.2

* Add support for witherable 0.5
Expand Down
12 changes: 6 additions & 6 deletions reflex.cabal
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
Name: reflex
Version: 0.9.3.2
Version: 0.9.3.3
Synopsis: Higher-order Functional Reactive Programming
Description:
Interactive programs without callbacks or side-effects.
Expand Down Expand Up @@ -28,7 +28,7 @@ extra-source-files:
ChangeLog.md

tested-with:
GHC ==8.4.4 || ==8.6.5 || ==8.8.1 || ==8.10.7 || ==9.0.1 || ==9.2.5 || ==9.4.5 || ==9.6.1 || ==9.8.2 || ==9.10.1,
GHC ==8.4.4 || ==8.6.5 || ==8.8.1 || ==8.10.7 || ==9.0.1 || ==9.2.5 || ==9.4.5 || ==9.6.1 || ==9.8.2 || ==9.10.1 || ==9.12.1,
GHCJS ==8.6 || ==8.10

flag use-reflex-optimizer
Expand Down Expand Up @@ -71,14 +71,14 @@ library
hs-source-dirs: src
build-depends:
MemoTrie == 0.6.*,
base >= 4.11 && < 4.21,
base >= 4.11 && < 4.22,
bifunctors >= 5.2 && < 5.7,
comonad >= 5.0.4 && < 5.1,
commutative-semigroups >= 0.1 && <0.3,
constraints >= 0.10 && <0.15,
constraints-extras >= 0.3 && < 0.5,
containers >= 0.6 && < 0.8,
data-default >= 0.5 && < 0.8,
data-default >= 0.5 && < 0.9,
dependent-map >= 0.3 && < 0.5,
dependent-sum >= 0.6 && < 0.8,
exceptions >= 0.10 && < 0.11,
Expand All @@ -97,7 +97,7 @@ library
semigroupoids >= 4.0 && < 7,
stm >= 2.4 && < 2.6,
syb >= 0.5 && < 0.8,
time >= 1.4 && < 1.13,
time >= 1.4 && < 1.15,
transformers >= 0.5 && < 0.7,
unbounded-delays >= 0.1.0.0 && < 0.2,
witherable >= 0.4 && < 0.6
Expand Down Expand Up @@ -189,7 +189,7 @@ library
build-depends:
haskell-src-exts >= 1.16 && < 1.24,
haskell-src-meta >= 0.6 && < 0.9,
template-haskell >= 2.9 && < 2.23
template-haskell >= 2.9 && < 2.24
exposed-modules:
Reflex.Dynamic.TH
other-extensions: TemplateHaskell
Expand Down
2 changes: 1 addition & 1 deletion src/Reflex/BehaviorWriter/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ Description: Implementation of BehaviorWriter
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE StandaloneDeriving #-}
#ifdef USE_REFLEX_OPTIMIZER
Expand All @@ -25,7 +26,6 @@ import Control.Monad
import Control.Monad.Catch (MonadMask, MonadThrow, MonadCatch)
import Control.Monad.Exception
import Control.Monad.Fix
import Control.Monad.Identity
import Control.Monad.IO.Class
import Control.Monad.Morph
import Control.Monad.Reader
Expand Down
1 change: 0 additions & 1 deletion src/Reflex/Collection.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,6 @@ import Data.Zip (Zip (..))

import Control.Monad
import Control.Monad.Fix
import Control.Monad.Identity
import Data.Align
import Data.Functor.Misc
import Data.Map (Map)
Expand Down
2 changes: 1 addition & 1 deletion src/Reflex/Dynamic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -96,7 +96,7 @@ import Data.Maybe
import Data.These
import Data.Type.Equality ((:~:) (..))

import Debug.Trace hiding (traceEventWith)
import Debug.Trace (trace)

-- | Map a sampling function over a 'Dynamic'.
mapDynM :: forall t m a b. (Reflex t, MonadHold t m) => (forall m'. MonadSample t m' => a -> m' b) -> Dynamic t a -> m (Dynamic t b)
Expand Down
2 changes: 1 addition & 1 deletion src/Reflex/DynamicWriter/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE StandaloneDeriving #-}
#ifdef USE_REFLEX_OPTIMIZER
Expand All @@ -23,7 +24,6 @@ import Control.Monad
import Control.Monad.Catch (MonadMask, MonadThrow, MonadCatch)
import Control.Monad.Exception
import Control.Monad.Fix
import Control.Monad.Identity
import Control.Monad.IO.Class
import Control.Monad.Morph
import Control.Monad.Primitive
Expand Down
1 change: 1 addition & 0 deletions src/Reflex/Host/Class.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@
{-# LANGUAGE RoleAnnotations #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
#ifdef USE_REFLEX_OPTIMIZER
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}
Expand Down
1 change: 1 addition & 0 deletions src/Reflex/Host/Headless.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}

module Reflex.Host.Headless where

Expand Down
1 change: 1 addition & 0 deletions src/Reflex/NotReady/Class.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
#ifdef USE_REFLEX_OPTIMIZER
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}
Expand Down
11 changes: 4 additions & 7 deletions src/Reflex/PerformEvent/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,6 @@ import Control.Lens
import Control.Monad.Catch (MonadMask, MonadThrow, MonadCatch)
import Control.Monad.Exception
import Control.Monad.Fix
import Control.Monad.Identity
import Control.Monad.Primitive
import Control.Monad.Reader
import Control.Monad.Ref
Expand Down Expand Up @@ -80,7 +79,7 @@ instance (Monad (HostFrame t), ReflexHost t, Ref m ~ Ref IO) => PerformEvent t (
{-# INLINABLE performEvent #-}
performEvent = PerformEventT . requestingIdentity

instance (ReflexHost t, PrimMonad (HostFrame t)) => Adjustable t (PerformEventT t m) where
instance ReflexHost t => Adjustable t (PerformEventT t m) where
runWithReplace outerA0 outerA' = PerformEventT $ runWithReplaceRequesterTWith f (coerce outerA0) (coerceEvent outerA')
where f :: HostFrame t a -> Event t (HostFrame t b) -> RequesterT t (HostFrame t) Identity (HostFrame t) (a, Event t b)
f a0 a' = do
Expand All @@ -91,7 +90,7 @@ instance (ReflexHost t, PrimMonad (HostFrame t)) => Adjustable t (PerformEventT
traverseDMapWithKeyWithAdjust f outerDm0 outerDm' = PerformEventT $ traverseDMapWithKeyWithAdjustRequesterTWith (defaultAdjustBase traversePatchDMapWithKey) mapPatchDMap weakenPatchDMapWith patchMapNewElementsMap mergeMapIncremental (\k v -> unPerformEventT $ f k v) (coerce outerDm0) (coerceEvent outerDm')
traverseDMapWithKeyWithAdjustWithMove f outerDm0 outerDm' = PerformEventT $ traverseDMapWithKeyWithAdjustRequesterTWith (defaultAdjustBase traversePatchDMapWithMoveWithKey) mapPatchDMapWithMove weakenPatchDMapWithMoveWith patchMapWithMoveNewElementsMap mergeMapIncrementalWithMove (\k v -> unPerformEventT $ f k v) (coerce outerDm0) (coerceEvent outerDm')

defaultAdjustBase :: forall t v v2 k' p. (Monad (HostFrame t), PrimMonad (HostFrame t), Reflex t)
defaultAdjustBase :: forall t v v2 k' p. (Monad (HostFrame t), Reflex t)
=> ((forall a. k' a -> v a -> HostFrame t (v2 a)) -> p k' v -> HostFrame t (p k' v2))
-> (forall a. k' a -> v a -> HostFrame t (v2 a))
-> DMap k' v
Expand All @@ -102,7 +101,7 @@ defaultAdjustBase traversePatchWithKey f' dm0 dm' = do
result' <- requestingIdentity $ ffor dm' $ traversePatchWithKey f'
return (result0, result')

defaultAdjustIntBase :: forall t v v2 p. (Monad (HostFrame t), PrimMonad (HostFrame t), Reflex t)
defaultAdjustIntBase :: forall t v v2 p. (Monad (HostFrame t), Reflex t)
=> ((IntMap.Key -> v -> HostFrame t v2) -> p v -> HostFrame t (p v2))
-> (IntMap.Key -> v -> HostFrame t v2)
-> IntMap v
Expand All @@ -124,9 +123,7 @@ instance ReflexHost t => MonadReflexCreateTrigger t (PerformEventT t m) where
-- at the appropriate time.
{-# INLINABLE hostPerformEventT #-}
hostPerformEventT :: forall t m a.
( Monad m
, MonadSubscribeEvent t m
, MonadReflexHost t m
( MonadReflexHost t m
, MonadRef m
, Ref m ~ Ref IO
)
Expand Down
1 change: 0 additions & 1 deletion src/Reflex/PerformEvent/Class.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,6 @@ module Reflex.PerformEvent.Class
) where

import Control.Monad
import Control.Monad.Fix
import Control.Monad.Reader
import Control.Monad.Trans.Maybe (MaybeT (..))

Expand Down
1 change: 0 additions & 1 deletion src/Reflex/PostBuild/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,6 @@ import Control.Applicative (liftA2)
import Control.Monad.Catch (MonadMask, MonadThrow, MonadCatch)
import Control.Monad.Exception
import Control.Monad.Fix
import Control.Monad.Identity
import Control.Monad.Primitive
import Control.Monad.Reader
import Control.Monad.Ref
Expand Down
4 changes: 1 addition & 3 deletions src/Reflex/Pure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE PolyKinds #-}

Expand Down Expand Up @@ -212,6 +213,3 @@ instance (Enum t, HasTrie t, Ord t) => MonadHold (Pure t) ((->) t) where

headE = slowHeadE
now t = Event $ guard . (t ==)



1 change: 1 addition & 0 deletions src/Reflex/Requester/Class.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE RecursiveDo #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
#ifdef USE_REFLEX_OPTIMIZER
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}
Expand Down
6 changes: 3 additions & 3 deletions src/Reflex/Spider/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@ import Control.Monad hiding (forM, forM_, mapM, mapM_)
import Control.Monad.Catch (MonadMask, MonadThrow, MonadCatch)
import Control.Monad.Exception
import Control.Monad.Fix
import Control.Monad.Identity hiding (forM, forM_, mapM, mapM_)
import Control.Monad.Identity
import Control.Monad.Primitive
import Control.Monad.Reader.Class
import Control.Monad.IO.Class
Expand Down Expand Up @@ -290,7 +290,7 @@ subscribeAndReadHead e sub = do
return (subscription, occ)

--TODO: Make this lazy in its input event
headE :: (MonadIO m, Defer (SomeMergeInit x) m) => Event x a -> m (Event x a)
headE :: (Defer (SomeMergeInit x) m) => Event x a -> m (Event x a)
headE originalE = do
parent <- liftIO $ newIORef $ Just originalE
defer $ SomeMergeInit $ do --TODO: Rename SomeMergeInit appropriately
Expand All @@ -315,7 +315,7 @@ nowSpiderEventM :: (HasSpiderTimeline x) => EventM x (R.Event (SpiderTimeline x)
nowSpiderEventM =
SpiderEvent <$> now

now :: (MonadIO m, Defer (Some Clear) m) => m (Event x ())
now :: (Defer (Some Clear) m) => m (Event x ())
now = do
nowOrNot <- liftIO $ newIORef $ Just ()
scheduleClear nowOrNot
Expand Down
7 changes: 3 additions & 4 deletions src/Reflex/Time.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,6 @@ import Data.Sequence (Seq, (|>))
import qualified Data.Sequence as Seq
import Data.These
import Data.Time.Clock
import Data.Typeable
import GHC.Generics (Generic)
import System.Random

Expand All @@ -50,7 +49,7 @@ data TickInfo
, _tickInfo_alreadyElapsed :: NominalDiffTime
-- ^ Amount of time that has elapsed in the current tick period.
}
deriving (Eq, Ord, Show, Typeable)
deriving (Eq, Ord, Show)

-- | Fires an 'Event' once every time provided interval elapses, approximately.
-- The provided 'UTCTime' is used bootstrap the determination of how much time has elapsed with each tick.
Expand Down Expand Up @@ -283,13 +282,13 @@ throttle t e = do
data ThrottleState b
= ThrottleState_Immediate
| ThrottleState_Buffered (ThrottleBuffer b)
deriving (Eq, Ord, Show, Functor, Foldable, Traversable, Generic, Data, Typeable)
deriving (Eq, Ord, Show, Functor, Foldable, Traversable, Generic, Data)

data ThrottleBuffer b
= ThrottleBuffer_Empty -- Empty conflicts with lens, and hiding it would require turning
-- on PatternSynonyms
| ThrottleBuffer_Full b
deriving (Eq, Ord, Show, Functor, Foldable, Traversable, Generic, Data, Typeable)
deriving (Eq, Ord, Show, Functor, Foldable, Traversable, Generic, Data)

instance Semigroup b => Semigroup (ThrottleBuffer b) where
x <> y = case x of
Expand Down
1 change: 1 addition & 0 deletions src/Reflex/TriggerEvent/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Reflex.TriggerEvent.Base
( TriggerEventT (..)
, runTriggerEventT
Expand Down
4 changes: 2 additions & 2 deletions src/Reflex/Workflow.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,13 +30,13 @@ import Reflex.PostBuild.Class
newtype Workflow t m a = Workflow { unWorkflow :: m (a, Event t (Workflow t m a)) }

-- | Runs a 'Workflow' and returns the 'Dynamic' result of the 'Workflow' (i.e., a 'Dynamic' of the value produced by the current 'Workflow' node, and whose update 'Event' fires whenever one 'Workflow' is replaced by another).
workflow :: forall t m a. (Reflex t, Adjustable t m, MonadFix m, MonadHold t m) => Workflow t m a -> m (Dynamic t a)
workflow :: forall t m a. (Adjustable t m, MonadFix m, MonadHold t m) => Workflow t m a -> m (Dynamic t a)
workflow w0 = do
rec eResult <- networkHold (unWorkflow w0) $ fmap unWorkflow $ switch $ snd <$> current eResult
return $ fmap fst eResult

-- | Similar to 'workflow', but outputs an 'Event' that fires at post-build time and whenever the current 'Workflow' is replaced by the next 'Workflow'.
workflowView :: forall t m a. (Reflex t, NotReady t m, Adjustable t m, MonadFix m, MonadHold t m, PostBuild t m) => Workflow t m a -> m (Event t a)
workflowView :: forall t m a. (NotReady t m, Adjustable t m, MonadFix m, MonadHold t m, PostBuild t m) => Workflow t m a -> m (Event t a)
workflowView w0 = do
rec eResult <- networkView . fmap unWorkflow =<< holdDyn w0 eReplace
eReplace <- fmap switch $ hold never $ fmap snd eResult
Expand Down

0 comments on commit 1e288e5

Please sign in to comment.