-- 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 . {-# LANGUAGE ExistentialQuantification, RankNTypes, DeriveDataTypeable, NoMonomorphismRestriction, FlexibleContexts, ScopedTypeVariables #-} {-# LANGUAGE OverloadedStrings #-} module Manatee.Core.Interactive where import Data.Text.Lazy (Text) -- | Parse interactive string. -- Return error reason if parse failed. parseInteractiveString :: String -> Either Text [(String, String)] parseInteractiveString interactiveStr | null prompts = Left "Empty interactive string." | any null prompts = Left "Have null line in interactive string." | any (`notElem` "cdfsn") types = Left "Have invalid type character in interactive string." | otherwise = Right $ map (\x -> (interactiveCandidateName (head x), tail x)) prompts where prompts = lines interactiveStr types = map head prompts -- | Get candidate name for type character. interactiveCandidateName :: Char -> String interactiveCandidateName 'c' = "InteractiveChar" interactiveCandidateName 'd' = "InteractiveDirectory" interactiveCandidateName 'f' = "InteractiveFile" interactiveCandidateName 'n' = "InteractiveNumber" interactiveCandidateName 's' = "InteractiveString"