{-| Module: Referees.Types.Internal Copyright : (c) Pablo Couto 2014 License : GPL-3 Maintainer : pablo@infty.in Stability : experimental Types and constructors for use in "Referees". -} {-# LANGUAGE FlexibleInstances #-} module Referees.Types.Internal where import Referees.Solver.Types ( Capacity ) import Control.Applicative ( pure, (<$>), (<*>) ) import Control.Monad ( mzero ) import qualified Data.ByteString.Char8 as BC ( split, unpack ) import Data.Csv ( FromField(..), FromRecord(..), Parser, runParser, (.!) ) import Data.Vector as V ( length ) -- * Core types type Name = String type Language = String type Area = String type Subarea = String data Entry subtype = Entry { _name :: Name , _capacity :: Maybe Capacity , _languages :: [Language] , _areas :: [(Area, [Subarea])] } deriving (Eq, Show) -- ** Subtypes data Referee = Referee data Proposal = Proposal -- ** Others type Match = (Entry Referee, [Entry Proposal]) -- * For parsing -- | For warning about issues that may take place during parsing. -- data CSV_Warning = DifferingCapacities Name newtype StringListParse sep = StrLstP { _strLstP :: [String] } deriving (Eq, Show) data Semicolon = Semicolon newtype MaybeCapacityParse = MaybeCapP { _maybeCapP :: Maybe Capacity } deriving (Eq, Show) -- | This type and its 'FromField' instance declarations are used to describe -- the parsing rules for reconstruction of 'Entry' values from CSV files. -- -- The two 'FromField' instance declarations here (vid. source) enable silent -- conditional parsing of the second field in a CSV file with 4 fields. In this -- scenario, if the second field is parseable as 'Int', it is parsed as -- 'MaybeCapacityParse' (a wrapper for 'Maybe' 'Capacity'); otherwise, as -- 'StringListParse' 'Semicolon' (a wrapper for @['String']@). -- data CSVentry = CSVentry { _nameCSV :: !Name , _capacityCSV :: !MaybeCapacityParse , _languagesCSV :: !(StringListParse Semicolon) , _areaCSV :: !Area , _subareasCSV :: !(StringListParse Semicolon) } instance FromField (StringListParse Semicolon) where parseField s = either (const . pure . StrLstP . map BC.unpack . BC.split ';' $ s) (const . pure . StrLstP $ []) $ runParser (parseField s :: Parser Int) instance FromField MaybeCapacityParse where parseField s = either (const . pure $ MaybeCapP Nothing) (pure . MaybeCapP . Just) $ runParser (parseField s :: Parser Int) instance FromRecord CSVentry where parseRecord v | V.length v == 2 = CSVentry <$> v .! 0 <*> pure (MaybeCapP Nothing) <*> pure (StrLstP []) <*> v .! 1 <*> pure (StrLstP []) | V.length v == 3 = CSVentry <$> v .! 0 <*> pure (MaybeCapP Nothing) <*> pure (StrLstP []) <*> v .! 1 <*> v .! 2 | V.length v == 4 = CSVentry <$> v .! 0 <*> v .! 1 <*> -- conditional parsing; see the comment for -- this function (v .! 1 :: Parser (StringListParse Semicolon)) <*> v .! 2 <*> v .! 3 | V.length v == 5 = CSVentry <$> v .! 0 <*> v .! 1 <*> v .! 2 <*> v .! 3 <*> v .! 4 | otherwise = mzero