module FRP.Peakachu.Program
( Program(..), AppendProgram(..)
, scanlP, emptyP, takeWhileP, loopbackP, singleValueP, lstP, lstPs, delayP
, withAppendProgram1, withAppendProgram2
) where
import Control.FilterCategory (FilterCategory(..), genericFlattenC)
import Data.ADT.Getters (mkADTGetters)
import Data.Newtype (mkWithNewtypeFuncs)
import Control.Applicative (Applicative(..), (<$>), liftA2)
import Control.Category (Category(..))
import Control.Monad (MonadPlus(..), ap)
import Data.DeriveTH (derive, makeFunctor)
import Data.List (genericDrop, genericTake)
import Data.Maybe (mapMaybe, catMaybes)
import Data.Monoid (Monoid(..))
import Prelude hiding ((.), id)
data Program a b = Program
{ progVals :: [b]
, progMore :: Maybe (a -> Program a b)
}
$(derive makeFunctor ''Program)
instance Category Program where
id =
Program [] (Just f)
where
f x = Program [x] (Just f)
left . right =
Program (catMaybes stuff >>= progVals) more
where
Program rightStart rightMore = right
stuff = scanl step (Just left) rightStart
step l valRight = do
Program _ moreLeft <- l
moreFunc <- moreLeft
return $ moreFunc valRight
more = do
moreFunc <- rightMore
lastStuff <- last stuff
return $ (.) (Program [] (progMore lastStuff)) . moreFunc
instance FilterCategory Program where
flattenC =
f []
where
f = (`Program` Just f)
arrC = (<$> id)
$(mkADTGetters ''Either)
scanlP :: (b -> a -> b) -> b -> Program a b
scanlP step start = Program [start] $ Just (scanlP step . step start)
emptyP :: Program a b
emptyP = Program [] Nothing
takeWhileP :: (a -> Bool) -> Program a a
takeWhileP cond =
Program [] (Just f)
where
f x
| cond x = Program [x] (Just f)
| otherwise = Program [] Nothing
loopbackP :: Program a (Either a b) -> Program a b
loopbackP program =
Program
{ progVals = stuff >>= mapMaybe gRight . progVals
, progMore = (fmap . fmap) loopbackP . progMore . last $ stuff
}
where
stuff =
scanl step program
. mapMaybe gLeft . progVals $ program
step prev val =
maybe emptyP ($ val) (progMore prev)
singleValueP :: Program a ()
singleValueP = scanlP const () . emptyP
delayP :: Integral i => i -> Program a a
delayP n =
flattenC . arrC (genericDrop n) . scanlP step []
where
step xs = (: genericTake n xs)
instance Monoid (Program a b) where
mempty = Program mempty mempty
mappend left right =
Program
{ progVals = mappend (progVals left) (progVals right)
, progMore = mappend (progMore left) (progMore right)
}
instance Applicative (Program a) where
pure x =
Program
{ progVals = pure x
, progMore = (pure . pure) (pure x)
}
left <*> right =
Program
{ progVals = progVals left <*> progVals right
, progMore = (liftA2 . liftA2) (<*>) (progMore left) (progMore right)
}
newtype AppendProgram a b = AppendProg
{ runAppendProg :: Program a b
} deriving (Category, FilterCategory, Functor)
$(mkWithNewtypeFuncs [1,2] ''AppendProgram)
instance Monoid (AppendProgram a b) where
mempty = AppendProg emptyP
mappend (AppendProg left) (AppendProg right) =
AppendProg $
case progMore left of
Nothing -> Program
{ progVals = progVals left ++ progVals right
, progMore = progMore right
}
Just more -> Program
{ progVals = progVals left
, progMore = Just $ flip (withAppendProgram2 mappend) right <$> more
}
instance Monad (AppendProgram a) where
return x = AppendProg $ Program [x] Nothing
AppendProg left >>= right =
mconcat $ map right (progVals left) ++ [rest]
where
rest =
AppendProg Program
{ progVals = []
, progMore =
(fmap . fmap . withAppendProgram1)
(>>= right) (progMore left)
}
instance MonadPlus (AppendProgram a) where
mzero = mempty
mplus = mappend
instance Applicative (AppendProgram a) where
pure = return
(<*>) = ap
lstPs :: Maybe b -> (a -> Maybe b) -> Program a b
lstPs start f =
genericFlattenC . scanlP (flip mplus) start . arrC f
lstP :: (a -> Maybe b) -> Program a b
lstP = lstPs Nothing