----------------------------------------------------------------------------- -- | -- Module : Entry -- Copyright : (C) Peter Robinson 2010-2013 -- License : GPL-2 -- -- Maintainer : Peter Robinson -- Stability : experimental -- Portability : portable -- ----------------------------------------------------------------------------- module Entry where import Data.Maybe import Data.List(intercalate) import Data.Text.Lazy(Text) import qualified Data.Text.Lazy as T data Entry = Entry { entryName :: Text , entryGraduationInfo :: [GraduationInfo] , entryAdvisors :: [(Text,Text)] } deriving(Ord,Eq) urlAdvisors :: Entry -> [Text] urlAdvisors = map (T.pack . (++) "http://genealogy.math.ndsu.nodak.edu/" . T.unpack . snd) . entryAdvisors data GraduationInfo = GraduationInfo { gradDegree :: Maybe Text , gradUniversity :: Maybe Text , gradYear :: Maybe Text , gradThesis :: Maybe Text } deriving(Ord,Eq) entryToText :: Entry -> Text entryToText e = entryName e `T.append` (T.concat $ map graduationInfoToText (entryGraduationInfo e)) `T.append` (T.concat $ map fst (entryAdvisors e)) instance Show Entry where show e = let ginfos = concatMap show (entryGraduationInfo e) in T.unpack (entryName e) ++ if ginfos /= [] then "\n" ++ ginfos else "" where maybeShow (Just g) = "\\n" ++ show g maybeShow Nothing = "" instance Show GraduationInfo where show g = let ls = map T.unpack $ catMaybes [gradDegree g, gradUniversity g, gradYear g] in intercalate ", " ls ++ "\\n" ++ maybeShow (gradThesis g) where maybeShow (Just gi) = T.unpack gi maybeShow Nothing = "" graduationInfoToText :: GraduationInfo -> Text graduationInfoToText g = let ls = catMaybes [gradDegree g, gradUniversity g, gradYear g] in T.intercalate (T.pack ", ") ls `T.append` (T.pack "\\n") `T.append` (maybeText (gradThesis g)) where maybeText (Just gi) = gi maybeText Nothing = T.pack "" removeThesis :: Entry -> Entry removeThesis e = e{ entryGraduationInfo = map (\g -> g{ gradThesis = Nothing }) $ entryGraduationInfo e } -- e{ entryGraduationInfo = case entryGraduationInfo e of -- Nothing -> Nothing -- Just g -> Just g{gradThesis = Nothing}}