-- This file is part of Diohsc -- Copyright (C) 2020 Martin Bays -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of version 3 of the GNU General Public License as -- published by the Free Software Foundation, or any later version. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see http://www.gnu.org/licenses/. {-# LANGUAGE Safe #-} module Alias where import Data.Bifunctor (second) import Data.List (isPrefixOf) import Safe (headMay) import CommandLine data Alias = Alias String CommandLine deriving (Eq,Ord,Show) type Aliases = [(String,Alias)] emptyAliases :: Aliases emptyAliases = [] defaultAliases :: Aliases defaultAliases = second aliasOf <$> [ ("back", "<") , ("forward", ">") , ("next", "~") ] where aliasOf s = let Right cl = parseCommandLine s in Alias s cl lookupAlias :: String -> Aliases -> Maybe Alias lookupAlias s aliases = headMay [ alias | (a,alias) <- aliases, s `isPrefixOf` a ] insertAlias :: String -> Alias -> Aliases -> Aliases insertAlias a alias = (++ [(a, alias)]) deleteAlias :: String -> Aliases -> Aliases deleteAlias a = filter $ (/= a) . fst