\begin{code} -- | -- Maintainer : silva.samuel@alumni.uminho.pt -- Stability : experimental -- Portability: portable -- This module implements common types module Music.Analysis.Base where import Data.Char (String) import Data.Bool (Bool) import Data.Int (Int) import Data.Maybe (Maybe(..)) import Data.Ratio (Ratio, (%)) import Prelude (Double, truncate) \end{code} This types are simple redefinitions. We explicit Double as Number. This Number is a Real Number. Delta is a number that means increment/decrement. Also explicit String as Text. This wrapper get Integer number from Real Number. Invariant class allows check properties to datatypes. \begin{code} -- * Types -- | Number is Double type Number = Double -- | Delta type is a number type Delta = Number -- | Text is String type Text = String -- | Integer Number definition type IntegerNumber = Int -- | Ratio Number definition type RatioNumber = Ratio IntegerNumber -- | wrapper to get Integer Number toInteger :: Number -> IntegerNumber toInteger = truncate -- | wrapper to get Ratio Number toRatio :: IntegerNumber -> RatioNumber toRatio i = i % 1 -- | Invariant class specification class Invariant a where invariant :: a -> Bool \end{code} \begin{nocode} -- || wrapper to get Integer Number toRatio :: Number -> RatioNumber toRatio = flip (%) 1 -- || Ratio Number definition type RatioNumber = Ratio Number \end{nocode} We also presents utilitary functions, such zip and unzip in Maybe version. \begin{code} -- * Auxiliary functions -- | like @unzip@ unzipMaybe :: [Maybe (a,b)] -> ([Maybe a],[Maybe b]) unzipMaybe [] = ([],[]) unzipMaybe (Just (a1,a2):as) = let (x,y) = unzipMaybe as in (Just a1:x, Just a2:y) unzipMaybe (Nothing:as) = let (x,y) = unzipMaybe as in (Nothing:x, Nothing:y) -- | like @zip@ zipMaybe :: ([Maybe a], [Maybe b]) -> [Maybe (a,b)] zipMaybe ([],[]) = [] zipMaybe (Just x:xs,Just y:ys) = Just (x,y):zipMaybe (xs,ys) zipMaybe (Nothing:xs,Nothing:ys) = Nothing:zipMaybe (xs,ys) zipMaybe _ = [] \end{code}