Skip to content

Commit

Permalink
Replaced all occurences of 'AFRP' with 'Yampa'. Refs ivanperez-keera#223
Browse files Browse the repository at this point in the history
  • Loading branch information
archit singhal committed Jun 11, 2022
1 parent c01d3b0 commit a958e8c
Show file tree
Hide file tree
Showing 8 changed files with 24 additions and 24 deletions.
2 changes: 1 addition & 1 deletion yampa/examples/TailgatingDetector/TailgatingDetector.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE Arrows #-}
-- |
-- Module : TailgatingDetector
-- Description : AFRP Expressitivity Test
-- Description : Yampa Expressitivity Test
-- Copyright : Yale University, 2003
-- Authors : Henrik Nilsson

Expand Down
4 changes: 2 additions & 2 deletions yampa/src/FRP/Yampa/Delays.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,7 @@ pre :: SF a a
pre = sscanPrim f uninit uninit
where
f c a = Just (a, c)
uninit = usrErr "AFRP" "pre" "Uninitialized pre operator."
uninit = usrErr "Yampa" "pre" "Uninitialized pre operator."

-- | Initialized delay operator.
--
Expand All @@ -66,7 +66,7 @@ b0 `fby` sf = b0 --> sf >>> pre
-- | Delay a signal by a fixed time 't', using the second parameter
-- to fill in the initial 't' seconds.
delay :: Time -> a -> SF a a
delay q a_init | q < 0 = usrErr "AFRP" "delay" "Negative delay."
delay q a_init | q < 0 = usrErr "Yampa" "delay" "Negative delay."
| q == 0 = identity
| otherwise = SF {sfTF = tf0}
where
Expand Down
6 changes: 3 additions & 3 deletions yampa/src/FRP/Yampa/Event.hs
Original file line number Diff line number Diff line change
Expand Up @@ -124,7 +124,7 @@ instance NFData a => NFData (Event a) where

-- * Internal utilities for event construction

-- These utilities are to be considered strictly internal to AFRP for the
-- These utilities are to be considered strictly internal to Yampa for the
-- time being.

-- | Convert a maybe value into a event ('Event' is isomorphic to 'Maybe').
Expand All @@ -142,7 +142,7 @@ event _ f (Event b) = f b
-- | Extract the value from an event. Fails if there is no event.
fromEvent :: Event a -> a
fromEvent (Event a) = a
fromEvent NoEvent = usrErr "AFRP" "fromEvent" "Not an event."
fromEvent NoEvent = usrErr "Yampa" "fromEvent" "Not an event."

-- | Tests whether the input represents an actual event.
isEvent :: Event a -> Bool
Expand Down Expand Up @@ -186,7 +186,7 @@ rMerge = flip (<|>)

-- | Unbiased event merge: simultaneous occurrence is an error.
merge :: Event a -> Event a -> Event a
merge = mergeBy (usrErr "AFRP" "merge" "Simultaneous event occurrence.")
merge = mergeBy (usrErr "Yampa" "merge" "Simultaneous event occurrence.")

-- | Event merge parameterized by a conflict resolution function.
--
Expand Down
10 changes: 5 additions & 5 deletions yampa/src/FRP/Yampa/EventS.hs
Original file line number Diff line number Diff line change
Expand Up @@ -94,7 +94,7 @@ after q x = afterEach [(q,x)]
-- point in time.
repeatedly :: Time -> b -> SF a (Event b)
repeatedly q x | q > 0 = afterEach qxs
| otherwise = usrErr "AFRP" "repeatedly" "Non-positive period."
| otherwise = usrErr "Yampa" "repeatedly" "Non-positive period."
where
qxs = (q,x):qxs

Expand All @@ -110,7 +110,7 @@ afterEach qxs = afterEachCat qxs >>> arr (fmap head)
afterEachCat :: [(Time,b)] -> SF a (Event [b])
afterEachCat [] = never
afterEachCat ((q,x):qxs)
| q < 0 = usrErr "AFRP" "afterEachCat" "Negative period."
| q < 0 = usrErr "Yampa" "afterEachCat" "Negative period."
| otherwise = SF {sfTF = tf0}
where
tf0 _ = if q <= 0
Expand All @@ -119,7 +119,7 @@ afterEachCat ((q,x):qxs)

emitEventsScheduleNext _ xs [] = (sfNever, Event (reverse xs))
emitEventsScheduleNext t xs ((q,x):qxs)
| q < 0 = usrErr "AFRP" "afterEachCat" "Negative period."
| q < 0 = usrErr "Yampa" "afterEachCat" "Negative period."
| t' >= 0 = emitEventsScheduleNext t' (x:xs) qxs
| otherwise = (awaitNextEvent t' x qxs, Event (reverse xs))
where
Expand All @@ -133,14 +133,14 @@ afterEachCat ((q,x):qxs)

-- | Delay for events. (Consider it a triggered after, hence /basic/.)
delayEvent :: Time -> SF (Event a) (Event a)
delayEvent q | q < 0 = usrErr "AFRP" "delayEvent" "Negative delay."
delayEvent q | q < 0 = usrErr "Yampa" "delayEvent" "Negative delay."
| q == 0 = identity
| otherwise = delayEventCat q >>> arr (fmap head)

-- | Delay an event by a given delta and catenate events that occur so closely
-- so as to be /inseparable/.
delayEventCat :: Time -> SF (Event a) (Event [a])
delayEventCat q | q < 0 = usrErr "AFRP" "delayEventCat" "Negative delay."
delayEventCat q | q < 0 = usrErr "Yampa" "delayEventCat" "Negative delay."
| q == 0 = arr (fmap (:[]))
| otherwise = SF {sfTF = tf0}
where
Expand Down
6 changes: 3 additions & 3 deletions yampa/src/FRP/Yampa/InternalCore.hs
Original file line number Diff line number Diff line change
Expand Up @@ -286,7 +286,7 @@ vfyNoEv :: Event a -> b -> b
vfyNoEv NoEvent b = b
vfyNoEv _ _ =
usrErr
"AFRP"
"Yampa"
"vfyNoEv"
"Assertion failed: Functions on events must not map NoEvent to Event."

Expand Down Expand Up @@ -469,7 +469,7 @@ cpXX (SFEP _ f1 s1 bne) (SFEP _ f2 s2 cne) =
(s1', NoEvent, NoEvent) -> ((s1', s2, cne), cne, cne)
(s1', Event b, NoEvent) ->
let (s2', c, cne') = f2 s2 b in ((s1', s2', cne'), c, cne')
_ -> usrErr "AFRP" "cpXX" $
_ -> usrErr "Yampa" "cpXX" $
"Assertion failed: Functions on events must not map "
++ "NoEvent to Event."
cpXX sf1@(SFEP{}) (SFCpAXA _ (FDE f21 f21ne) sf22 fd23) =
Expand Down Expand Up @@ -660,7 +660,7 @@ cpXE sf1 f2 f2ne = cpXEAux (FDE f2 f2ne) f2 f2ne sf1
case f1 s a of
(s', NoEvent, NoEvent) -> (s', f2ne, f2ne)
(s', eb, NoEvent) -> (s', f2 eb, f2ne)
_ -> usrErr "AFRP" "cpXEAux" $
_ -> usrErr "Yampa" "cpXEAux" $
"Assertion failed: Functions on events must not "
++ "map NoEvent to Event."
cpXEAux fd2 _ _ (SFCpAXA _ fd11 sf12 fd13) =
Expand Down
6 changes: 3 additions & 3 deletions yampa/src/FRP/Yampa/Random.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,12 +41,12 @@ noiseR :: (RandomGen g, Random b) => (b,b) -> g -> SF a b
noiseR range g0 = streamToSF (randomRs range g0)

streamToSF :: [b] -> SF a b
streamToSF [] = intErr "AFRP" "streamToSF" "Empty list!"
streamToSF [] = intErr "Yampa" "streamToSF" "Empty list!"
streamToSF (b:bs) = SF {sfTF = tf0}
where
tf0 _ = (stsfAux bs, b)

stsfAux [] = intErr "AFRP" "streamToSF" "Empty list!"
stsfAux [] = intErr "Yampa" "streamToSF" "Empty list!"
-- Invarying since stsfAux [] is an error.
stsfAux (b:bs) = SF' tf -- True
where
Expand All @@ -60,7 +60,7 @@ streamToSF (b:bs) = SF {sfTF = tf0}

occasionally :: RandomGen g => g -> Time -> b -> SF a (Event b)
occasionally g t_avg x | t_avg > 0 = SF {sfTF = tf0}
| otherwise = usrErr "AFRP" "occasionally"
| otherwise = usrErr "Yampa" "occasionally"
"Non-positive average interval."
where
-- Generally, if events occur with an average frequency of f, the
Expand Down
8 changes: 4 additions & 4 deletions yampa/src/FRP/Yampa/Simulation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -185,11 +185,11 @@ embedSynch sf0 (a0, dtas) = SF {sfTF = tf0}

tf0 _ = (esAux 0 (zip tts bbs), b)

esAux _ [] = intErr "AFRP" "embedSynch" "Empty list!"
esAux _ [] = intErr "Yampa" "embedSynch" "Empty list!"
-- Invarying below since esAux [] is an error.
esAux tp_prev tbtbs = SF' tf -- True
where
tf dt r | r < 0 = usrErr "AFRP" "embedSynch" "Negative ratio."
tf dt r | r < 0 = usrErr "Yampa" "embedSynch" "Negative ratio."
| otherwise = let tp = tp_prev + dt * r
(b, tbtbs') = advance tp tbtbs
in (esAux tp tbtbs', b)
Expand All @@ -208,12 +208,12 @@ embedSynch sf0 (a0, dtas) = SF {sfTF = tf0}
-- unnecessary samples when the input has not changed since
-- the last sample.
deltaEncode :: Eq a => DTime -> [a] -> (a, [(DTime, Maybe a)])
deltaEncode _ [] = usrErr "AFRP" "deltaEncode" "Empty input list."
deltaEncode _ [] = usrErr "Yampa" "deltaEncode" "Empty input list."
deltaEncode dt aas@(_:_) = deltaEncodeBy (==) dt aas

-- | 'deltaEncode' parameterized by the equality test.
deltaEncodeBy :: (a -> a -> Bool) -> DTime -> [a] -> (a, [(DTime, Maybe a)])
deltaEncodeBy _ _ [] = usrErr "AFRP" "deltaEncodeBy" "Empty input list."
deltaEncodeBy _ _ [] = usrErr "Yampa" "deltaEncodeBy" "Empty input list."
deltaEncodeBy eq dt (a0:as) = (a0, zip (repeat dt) (debAux a0 as))
where
debAux _ [] = []
Expand Down
6 changes: 3 additions & 3 deletions yampa/src/FRP/Yampa/Task.hs
Original file line number Diff line number Diff line change
Expand Up @@ -74,14 +74,14 @@ runTask tk = (unTask tk) (constant . Right)
-- Convenience function for tasks which are known not to terminate.
runTask_ :: Task a b c -> SF a b
runTask_ tk = runTask tk
>>> arr (either id (usrErr "AFRPTask" "runTask_"
>>> arr (either id (usrErr "YampaTask" "runTask_"
"Task terminated!"))

-- | Creates an SF that represents an SF and produces an event
-- when the task terminates, and otherwise produces just an output.
taskToSF :: Task a b c -> SF a (b, Event c)
taskToSF tk = runTask tk
>>> (arr (either id (usrErr "AFRPTask" "runTask_"
>>> (arr (either id (usrErr "YampaTask" "runTask_"
"Task terminated!"))
&&& edgeBy isEdge (Left undefined))
where
Expand Down Expand Up @@ -152,7 +152,7 @@ sleepT t b = mkTask (constant b &&& after t ())
-- @snapT >> snapT = snapT@

snapT :: Task a b a
snapT = mkTask (constant (intErr "AFRPTask" "snapT" "Bad switch?") &&& snap)
snapT = mkTask (constant (intErr "YampaTask" "snapT" "Bad switch?") &&& snap)

-- * Basic tasks combinators

Expand Down

0 comments on commit a958e8c

Please sign in to comment.