{-| Module : Task Description : Example usage of library Copyright : (c) Anton Marchenko, Mansur Ziatdinov, 2016-2017 License : BSD-3 Maintainer : gltronred@gmail.com Stability : experimental Portability : POSIX This module provides example of 'task'. This task is the following one. <> Part 'alpha' adds 5 to each list element. Part 'beta' has two variants: it either sums all list elements or computes product. Part 'gamma' takes a list and a number and multiplies every list element to this number. Part 'delta' is either sum or product of given list. -} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeOperators #-} module Task ( task , Input , Output , inputVariants , printTask ) where import Task.Pretty import Task.Types import Data.Invertible.Bijection import Prelude (Integer, (+), (-), (*), ($)) import qualified Prelude as P import Data.Invertible.List --------------------------------------------------------------------- -- EXAMPLE OF TAGLESS FINAL APPROACH --------------------------------------------------------------------- import Test.Multivariant.Classes type P prog a b = (WithDescription prog, WithCornerCases prog) => prog a b -- TASK DESCRIPTION BEGINS HERE -- | Part alpha. Adds 5 to each list element -- -- > step (Inv.map $ (\x -> x+5) :<->: (\x -> x-5)) -- -- We use 'Data.Invertible.List.map' and 'Data.Invertible.Bijection.(:<->:)' alpha :: P prog [Integer] [Integer] alpha = step (map $ (\x -> x+5) :<->: (\x -> x-5)) `withCornerCases` ([[],[-1,5],[5,4]], []) `withDescription` "Add 5 to each element of the list" -- | Part beta. Either sum or product of given list -- -- > step (sum :<->: (\x -> [x,0])) -- -- 'Prelude.sum' is not invertible, so we use a (right) inverse. beta :: P prog [Integer] Integer beta = oneof [beta1, beta2] where beta1 = step (P.sum :<->: (\x -> [x,0])) `withCornerCases` ([[],[3,2]], [0]) `withDescription` "Compute sum of elements of list" beta2 = step (P.product :<->: (\p -> [p,1])) `withDescription` "Compute product of elements of list" `withCornerCases` ([[],[0]], []) -- | Part gamma. -- -- > step ((\(xs,y) -> map (*y) xs) :<->: (\ys -> (ys,1))) -- -- We use a (right) inverse @(\ys -> (ys,1))@. gamma :: P prog ([Integer],Integer) [Integer] gamma = step ((\(xs,y) -> P.map (*y) xs) :<->: (\ys -> (ys,1))) `withCornerCases` ([ ([],1), ([1,2],0), ([],0), ([1,2],2)], [ ]) `withDescription` "Multiply each element of result of first operation to result of second operation" -- | Part delta. -- -- Either sum or product of list delta :: P prog [Integer] Integer delta = delta1 <+++> delta2 where delta1 = step (P.product :<->: (\p -> [p,1])) `withDescription` "Compute product of elements of list" `withCornerCases` ([[],[0]], []) delta2 = step (P.sum :<->: (\s -> [s,0])) `withDescription` "Compute sum of elements of list" `withCornerCases` ([[]], [0]) -- | Combined task task :: P prog Input Output task = (alpha <***> beta) ~> gamma ~> delta -- TASK DESCRIPTION ENDS HERE -- | Inputs to be fed to example solution (see 'Task.Pretty.printTask') inputVariants :: [Input] inputVariants = [ ([1,2,3], [1,2]) , ([1,-1], [1,2]) , ([], [1,2,1,4]) , ([0,1,2], [1,-1]) ]