module Synthesizer.Filter.Fix where import qualified Synthesizer.Filter.Graph as Graph {-| A 'Graph.T' with numbered nodes is not very comfortable. Better provide a 'Control.Monad.Fix.fix'-like function which allows to enter a graph this way: > fix $ \[v,w,y] -> > [a·(u + d·w), > b·(v + e·y), > c· w] -} type T filter t a v = [Channel filter t a v] -> [[(Channel filter t a v, filter t a v)]] type ChannelId = Int data Channel filter t a v = Channel {channelId :: ChannelId, channelInputs :: [(ChannelId, filter t a v)]} fix :: T filter t a v -> [Channel filter t a v] fix f = let cs = zipWith (\n inputs -> Channel n (map (\(c,filt) -> (channelId c, filt)) inputs)) [0 ..] (f cs) in cs toGraph :: T filter t a v -> Graph.T filter Int t a v toGraph = Graph.fromList . map (\(Channel n inputs) -> (n, inputs)) . fix