{- |

Copyright   :  (c) Henning Thielemann 2008
License     :  GPL

Maintainer  :  synthesizer@henning-thielemann.de
Stability   :  provisional
Portability :  requires multi-parameter type classes (OccasionallyScalar)



Light-weight sample parameter inference which will fit most needs.
We only do \"poor man's inference\", only for sample rates.
The sample rate will be provided as an argument of a special type 'T'.
This argument will almost never be passed explicitly
but handled operators analogous to '($)' and '(.)'.

In contrast to the run-time inference approach,
we have the static guarantee that the sample rate is fixed
before passing a signal to the outside world.
-}
module Synthesizer.SampleRateContext.Rate (
      T(..),
      fromNumber, toNumber,
      loop, pure,
      ($:), ($::), ($^), ($#),
      (.:), (.^),
      liftP, liftP2, liftP3, liftP4,
   ) where

import Synthesizer.ApplicativeUtility

{-
import NumericPrelude
import PreludeBase as P
-}


{- |
This wraps a function which computes a sample rate dependent result.
Sample rate tells how many values per unit are stored
for representation of a signal.
-}
newtype T t t' = Cons {decons :: t'}
   deriving (Eq, Ord, Show)


fromNumber :: t' -> T t t'
fromNumber = Cons

toNumber :: T t t' -> t'
toNumber = decons


pure :: a -> T t t' -> a
pure = const


{-
{- |
The first argument will be a function like 'Synthesizer.SampleRateContext.Signal.toTimeScalar'.
If you use this function instead of 'Synthesizer.SampleRateContext.Signal.toTimeScalar' directly,
the type @t@ can be automatically infered.
-}
convertTimeParam :: (t' -> t' -> t) -> t' -> (t -> a) -> T t t' -> a
convertTimeParam convert t' f = Cons $ \sr ->
   f (convert sr t')
-}