-- -- Copyright (c) 2009-2010, ERICSSON AB All rights reserved. -- -- Redistribution and use in source and binary forms, with or without -- modification, are permitted provided that the following conditions are met: -- -- * Redistributions of source code must retain the above copyright notice, -- this list of conditions and the following disclaimer. -- * Redistributions in binary form must reproduce the above copyright -- notice, this list of conditions and the following disclaimer in the -- documentation and/or other materials provided with the distribution. -- * Neither the name of the ERICSSON AB nor the names of its contributors -- may be used to endorse or promote products derived from this software -- without specific prior written permission. -- -- THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" -- AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE -- IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE -- ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS -- BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, -- OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -- SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -- INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -- CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -- ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF -- THE POSSIBILITY OF SUCH DAMAGE. -- -- | Helper functions for producing Haskell code module Feldspar.Haskell where import Data.List -- | Types that can represent Haskell types (as source code strings) class HaskellType a where -- | Gives the Haskell type denoted by the argument. haskellType :: a -> String -- | Types that can represent Haskell values (as source code strings) class HaskellValue a where -- | Gives the Haskell code denoted by the argument. haskellValue :: a -> String instance HaskellValue String where haskellValue = id instance HaskellValue Int where haskellValue = show -- | Like 'Data.List.unlines', but no trailing @\'\\n\'@. unlinesNoTrail :: [String] -> String unlinesNoTrail = intercalate "\n" -- | Indents a string the given number of columns. indent :: Int -> String -> String indent n = unlinesNoTrail . map (spc ++) . lines where spc = replicate n ' ' newline :: String newline = "\n" -- | Application (-$-) :: HaskellValue a => String -> a -> String fun -$- inp = unwords [fun, haskellValue inp] -- | Binary operator application opApp :: (HaskellValue a, HaskellValue b) => String -> a -> b -> String opApp op a b = unwords [haskellValue a, op, haskellValue b] -- | Definition (-=-) :: (HaskellValue patt, HaskellValue def) => patt -> def -> String patt -=- def = unwords [haskellValue patt, "=", haskellValue def] -- Places the second string as a local block to the first string. local :: String -> String -> String local def "" = def local def defs = def ++ newline ++ indent 2 "where" ++ newline ++ indent 4 defs infixl 8 -$- infix 7 -=- infixr 6 `local` ifThenElse :: (HaskellValue c, HaskellValue t, HaskellValue e) => c -> t -> e -> String ifThenElse c t e = unwords ["if", haskellValue c, "then", haskellValue t, "else", haskellValue e]