Skip to content

Commit

Permalink
wip
Browse files Browse the repository at this point in the history
  • Loading branch information
Ryan Trinkle committed Oct 12, 2016
1 parent 2bb2332 commit 8c7653e
Show file tree
Hide file tree
Showing 13 changed files with 21 additions and 3 deletions.
6 changes: 5 additions & 1 deletion reflex.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -28,8 +28,8 @@ library
lens >= 4.7 && < 5,
monad-control >= 1.0.1 && < 1.1,
mtl >= 2.1 && < 2.3,
primitive >= 0.5 && < 0.7,
prim-uniq >= 0.1.0.1 && < 0.2,
primitive >= 0.5 && < 0.7,
ref-tf == 0.4.*,
semigroupoids >= 4.0 && < 6,
semigroups >= 0.16 && < 0.19,
Expand Down Expand Up @@ -57,6 +57,10 @@ library
Reflex.Spider,
Reflex.Spider.Internal

if !impl(ghcjs)
build-depends: ghc
exposed-modules: Reflex.Optimizer

other-extensions: TemplateHaskell
ghc-options: -Wall -fwarn-tabs -funbox-strict-fields -O2
ghc-prof-options: -auto-all
Expand Down
1 change: 1 addition & 0 deletions src/Data/Functor/Misc.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}
-- | This module provides types and functions with no particular theme, but
-- which are relevant to the use of 'Functor'-based datastructures like
-- 'Data.Dependent.Map.DMap'.
Expand Down
1 change: 1 addition & 0 deletions src/Data/WeakBag.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}
-- | This module defines the 'WeakBag' type, which represents a mutable
-- collection of items that does not cause the items to be retained in memory.
-- This is useful for situations where a value needs to be inspected or modified
Expand Down
7 changes: 5 additions & 2 deletions src/Reflex/Class.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}

-- | This module contains the Reflex interface, as well as a variety of
-- convenience functions for working with 'Event's, 'Behavior's, and other
Expand Down Expand Up @@ -141,8 +142,6 @@ import Debug.Trace (trace)
class ( MonadHold t (PushM t)
, MonadSample t (PullM t)
, MonadFix (PushM t)
, Functor (Event t)
, Functor (Behavior t)
, Functor (Dynamic t)
, Applicative (Dynamic t) -- Necessary for GHC <= 7.8
, Monad (Dynamic t)
Expand Down Expand Up @@ -507,9 +506,11 @@ instance Reflex t => Bind (Event t) where
join = coincidence

instance Reflex t => Functor (Event t) where
{-# INLINE fmap #-}
fmap f = fmapMaybe $ Just . f

instance Reflex t => FunctorMaybe (Event t) where
{-# INLINE fmapMaybe #-}
fmapMaybe f = push $ return . f

-- | Never: @'zero' = 'never'@.
Expand Down Expand Up @@ -645,6 +646,7 @@ instance (Semigroup a, Reflex t) => Monoid (Event t a) where
-- | Create a new 'Event' that occurs if at least one of the 'Event's in the
-- list occurs. If multiple occur at the same time they are folded from the left
-- with the given function.
{-# INLINE mergeWith #-}
mergeWith :: Reflex t => (a -> a -> a) -> [Event t a] -> Event t a
mergeWith f es = fmap (Prelude.foldl1 f . map (\(Const2 _ :=> Identity v) -> v) . DMap.toList)
. merge
Expand All @@ -655,6 +657,7 @@ mergeWith f es = fmap (Prelude.foldl1 f . map (\(Const2 _ :=> Identity v) -> v)
-- | Create a new 'Event' that occurs if at least one of the 'Event's in the
-- list occurs. If multiple occur at the same time the value is the value of the
-- leftmost event.
{-# INLINE leftmost #-}
leftmost :: Reflex t => [Event t a] -> Event t a
leftmost = mergeWith const

Expand Down
1 change: 1 addition & 0 deletions src/Reflex/Dynamic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}
-- | This module contains various functions for working with 'Dynamic' values.
-- 'Dynamic' and its primitives have been moved to the 'Reflex' class.
module Reflex.Dynamic
Expand Down
1 change: 1 addition & 0 deletions src/Reflex/Dynamic/TH.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}
-- | Template Haskell helper functions for building complex 'Dynamic' values.
module Reflex.Dynamic.TH (qDyn, unqDyn, mkDyn) where

Expand Down
1 change: 1 addition & 0 deletions src/Reflex/Dynamic/Uniq.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}
-- | This module provides a variation of 'Dynamic' values that uses cheap
-- pointer equality checks to reduce the amount of signal propagation needed.
module Reflex.Dynamic.Uniq
Expand Down
1 change: 1 addition & 0 deletions src/Reflex/DynamicWriter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}
module Reflex.DynamicWriter where

import Control.Monad.Exception
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 @@ -9,6 +9,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}
-- | This module provides the interface for hosting 'Reflex' engines. This
-- should only be necessary if you're writing a binding or some other library
-- that provides a core event loop.
Expand Down
1 change: 1 addition & 0 deletions src/Reflex/PerformEvent/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}
module Reflex.PerformEvent.Base where

import Reflex.Class
Expand Down
1 change: 1 addition & 0 deletions src/Reflex/PerformEvent/Class.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}
module Reflex.PerformEvent.Class where

import Reflex.Class
Expand Down
1 change: 1 addition & 0 deletions src/Reflex/PostBuild/Class.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}
module Reflex.PostBuild.Class where

import Control.Monad.Exception
Expand Down
1 change: 1 addition & 0 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 #-}
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}

-- There are two expected orphan instances in this module:
-- * MonadSample (Pure t) ((->) t)
Expand Down

0 comments on commit 8c7653e

Please sign in to comment.