[Haskell-cafe] The Good, the Bad and the GUI

Tom Ellis tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk
Wed Aug 13 23:21:56 UTC 2014


On Wed, Aug 13, 2014 at 10:31:31PM +0200, Wojtek Narczyński wrote:
> On 13.08.2014 12:37, Tom Ellis wrote:
> >On Tue, Aug 12, 2014 at 12:46:05PM +0200, Wojtek Narczyński wrote:
> >>Continuing my VAT Invoice example, let us say a LineItem that does
> >>not have a product description (missing value), but it does have all
> >>the numeric fields filled in.  It is partly erroneous, but it can be
> >>included in calculation of the total. How would you handle it with
> >>Either [Error] Invoice style code?
> >What sort of functionality are you looking for exactly?  What's your
> >objection to (for example)
> >
> >     data LineItemGeneral a = LineItem { price :: Price
> >                                       , quantity :: Quantity
> >                                       , description :: a }
> >
> >     type LineItem = LineItemGeneral String
> >     type LineItemPossiblyIncomplete = LineItemGeneral (Maybe String)
> >     type LineItemWithoutDescription = LineItemGeneral ()
> >
> >     totalValue :: LineItemGeneral a -> Value
> >     totalValue lineItem = price lineItem * quantity lineItem
> >
> >`totalValue` works for all sorts of line items, whether they have a
> >description or not.
>
> Let's say the user entered:
> 
> No, Name, Qty, Price
> --------------------------------------------
> 1. [        ]   [99] [10]
> 2. [Water] [    ] [10]
> 3. [Juice]   [  1] [    ]
> 
> The GUI should display total of 990, and signal four errors: three
> missing values (ideally different color of the input fields), and
> the whole invoice incomplete. The Either [Error] Invoice type does
> not work, because can either display the errors or calculate total
> from a correct invoice, never both. And you can't even create
> LineItem for 2. and 3. Well, maybe you can with laziness, but how
> would total work then?
> 
> That's why I asked in my original post, whether I'd need two types,
> one for correct complete invoice, and another for the invoice "in
> statu nascendi". And how to obtain them, lazily, and I mean the
> person, not the language.

Perhaps I don't grasp exactly what you're getting at, but this seems easy. 
Please let me know where my proposed solution fails to provide what you
need.  

I do see that you originally said "In Haskell you'd need two data types: the
usual proper Haskell data type, and another which wraps every field in
Maybe, facilitates editing, validation, etc.".  You don't actually *need*
the version without the Maybe, but you can provide it if you want some
additional type safety.  If you'd like to see an example of making that
nice and easy with minimal boilerplate please ask.


    import Control.Applicative
    import Data.Maybe
    import Control.Arrow
    
    type Quantity = Double
    type Price = Double
    type Value = Double
    
    data LineItem = LineItem { name :: Maybe String
                             , quantity :: Maybe Quantity
                             , price :: Maybe Price }
    
    data Field = NameField | QuantityField | PriceField
               deriving Show
    
    data Error = Error { item :: Int
                       , missing :: Field }
               deriving Show
    
    value :: LineItem -> Maybe Value
    value l = (*) <$> price l <*> quantity l
    
    totalValue :: [LineItem] -> Value
    totalValue = sum . map (fromMaybe 0 . value)
    
    missingFields :: LineItem -> [Field]
    missingFields l = n ++ q ++ p
      where n = if name l == Nothing then [NameField] else []
            q = if quantity l == Nothing then [QuantityField] else []
            p = if price l == Nothing then [PriceField] else []
    
    errors :: [LineItem] -> [Error]
    errors = concatMap (\(i, es) -> map (Error i) es)   
             . zip [1..]
             . map missingFields    
    
    guiResponse :: [LineItem] -> (Value, [Error])
    guiResponse = totalValue &&& errors
    
    exampleData :: [LineItem]
    exampleData = [ LineItem Nothing        (Just 99) (Just 10)
                  , LineItem (Just "Water") Nothing   (Just 10)
                  , LineItem (Just "Juice") (Just 1)  Nothing ]
                  
    -- *Main> guiResponse exampleData 
    -- (990.0, [ Error {item = 1, missing = NameField}
    --         , Error {item = 2, missing = QuantityField}
    --         , Error {item = 3, missing = PriceField}])


More information about the Haskell-Cafe mailing list