-- Author: Andy Stewart -- Maintainer: Andy Stewart -- -- Copyright (C) 2010 Andy Stewart, all rights reserved. -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . module Text.Morse ( toMorseCode, fromMorseCode, isMorseChar, ) where import Data.Char import Data.Map (Map) import qualified Data.Map as M -- | Morse Code convert map. morseCode :: Map Char String morseCode = M.fromList [('a', ".-") ,('b', "-...") ,('c', "-.-.") ,('d', "-..") ,('e', ".") ,('f', "..-.") ,('g', "--.") ,('h', "....") ,('i', "..") ,('j', ".---") ,('k', "-.-") ,('l', ".-..") ,('m', "--") ,('n', "-.") ,('o', "---") ,('p', ".--.") ,('q', "--.-") ,('r', ".-.") ,('s', "...") ,('t', "-") ,('u', "..-") ,('v', "...-") ,('w', ".--") ,('x', "-..-") ,('y', "-.--") ,('z', "--..") ,('=', "-...-") ,('?', "..--..") ,('/', "-..-.") ,(',', "--..--") ,('.', ".-.-.-") ,(':', "---...") ,('\'', ".----.") ,('-', "-....-") ,('(', "-.--.-") ,(')', "-.--.-") ,('0', "-----") ,('1', ".----") ,('2', "..---") ,('3', "...--") ,('4', "....-") ,('5', ".....") ,('6', "-....") ,('7', "--...") ,('8', "---..") ,('9', "----.") ,('@', ".--.-.")] -- | Convert String to Morse Code. -- And ignore invliad Morse character. toMorseCode :: String -> String toMorseCode = concatMap (\x -> case findMinMatch morseCode (\ k _ -> k == toLower x) of -- Add blank after Morse Code. Just (_, morse) -> morse ++ " " Nothing -> -- Replace blank with '/' -- or ignore invalid character. if x == ' ' then "/" else "") -- | Get string from Morse Code. -- Throw error if find invalid Morse Code. fromMorseCode :: String -> String fromMorseCode str = fromMorseCode' str "" fromMorseCode' :: String -> String -> String fromMorseCode' [] _ = [] fromMorseCode' (x:xs) str | x == '.' = fromMorseCode' xs (str ++ [x]) | x == '-' = fromMorseCode' xs (str ++ [x]) | x == ' ' = let char = case findMinMatch morseCode (\ _ v -> v == str) of Just (c, _) -> c Nothing -> error (str ++ " is not valid Morse Code.") in char : fromMorseCode' xs "" | x == '/' = ' ' : fromMorseCode' xs "" | otherwise = error ("'" ++ [x] ++ "' is not valid Morse Code.") -- | Whether character is valid Morse Character. isMorseChar :: Char -> Bool isMorseChar char = case findMinMatch morseCode (\ k _ -> k == char) of Just _ -> True Nothing -> False -- | Find min match one. findMinMatch :: Ord k => Map k a -> (k -> a -> Bool) -> Maybe (k, a) findMinMatch map fun = match where filterMap = M.filterWithKey fun map match = if M.null filterMap then Nothing else Just $ M.findMin filterMap