<div dir="ltr"><div class="gmail_extra"><div class="gmail_quote">On Wed, Aug 13, 2014 at 4:21 PM, Tom Ellis <span dir="ltr"><<a href="mailto:tom-lists-haskell-cafe-2013@jaguarpaw.co.uk" target="_blank">tom-lists-haskell-cafe-2013@jaguarpaw.co.uk</a>></span> wrote:<br>
</div><div class="gmail_quote"><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div class="HOEnZb"><div class="h5">On Wed, Aug 13, 2014 at 10:31:31PM +0200, Wojtek Narczyński wrote:<br>

> On 13.08.2014 12:37, Tom Ellis wrote:<br>
> >On Tue, Aug 12, 2014 at 12:46:05PM +0200, Wojtek Narczyński wrote:<br>
> >>Continuing my VAT Invoice example, let us say a LineItem that does<br>
> >>not have a product description (missing value), but it does have all<br>
> >>the numeric fields filled in.  It is partly erroneous, but it can be<br>
> >>included in calculation of the total. How would you handle it with<br>
> >>Either [Error] Invoice style code?<br>
> >What sort of functionality are you looking for exactly?  What's your<br>
> >objection to (for example)<br>
> ><br>
> >     data LineItemGeneral a = LineItem { price :: Price<br>
> >                                       , quantity :: Quantity<br>
> >                                       , description :: a }<br>
> ><br>
> >     type LineItem = LineItemGeneral String<br>
> >     type LineItemPossiblyIncomplete = LineItemGeneral (Maybe String)<br>
> >     type LineItemWithoutDescription = LineItemGeneral ()<br>
> ><br>
> >     totalValue :: LineItemGeneral a -> Value<br>
> >     totalValue lineItem = price lineItem * quantity lineItem<br>
> ><br>
> >`totalValue` works for all sorts of line items, whether they have a<br>
> >description or not.<br>
><br>
> Let's say the user entered:<br>
><br>
> No, Name, Qty, Price<br>
> --------------------------------------------<br>
> 1. [        ]   [99] [10]<br>
> 2. [Water] [    ] [10]<br>
> 3. [Juice]   [  1] [    ]<br>
><br>
> The GUI should display total of 990, and signal four errors: three<br>
> missing values (ideally different color of the input fields), and<br>
> the whole invoice incomplete. The Either [Error] Invoice type does<br>
> not work, because can either display the errors or calculate total<br>
> from a correct invoice, never both. And you can't even create<br>
> LineItem for 2. and 3. Well, maybe you can with laziness, but how<br>
> would total work then?<br>
><br>
> That's why I asked in my original post, whether I'd need two types,<br>
> one for correct complete invoice, and another for the invoice "in<br>
> statu nascendi". And how to obtain them, lazily, and I mean the<br>
> person, not the language.<br>
<br>
</div></div>Perhaps I don't grasp exactly what you're getting at, but this seems easy.<br>
Please let me know where my proposed solution fails to provide what you<br>
need.<br>
<br>
I do see that you originally said "In Haskell you'd need two data types: the<br>
<div class="">usual proper Haskell data type, and another which wraps every field in<br>
</div>Maybe, facilitates editing, validation, etc.".  You don't actually *need*<br>
the version without the Maybe, but you can provide it if you want some<br>
additional type safety.  If you'd like to see an example of making that<br>
nice and easy with minimal boilerplate please ask.<br>
<br>
<br>
    import Control.Applicative<br>
    import Data.Maybe<br>
    import Control.Arrow<br>
<br>
    type Quantity = Double<br>
    type Price = Double<br>
    type Value = Double<br>
<br>
    data LineItem = LineItem { name :: Maybe String<br>
                             , quantity :: Maybe Quantity<br>
                             , price :: Maybe Price }<br></blockquote><div><br></div><div><br></div><div>Rather than this definition, what about something like:</div><div><br></div><div>    data LineItemF f = LineItem</div>
<div>        { name :: f String</div><div>        , quantity :: f Quantity</div><div>        , price :: f Price }</div><div><br></div><div>    type LineItemBuilder = LineItemF (Writer Error)</div><div>    type LineItem = LineItemF Identity</div>
<div><br></div><div>    newLineItemBuilder :: LineItemBuilder</div><div>    newLineItemBuilder = LineItemF</div><div>        {"Missing" <$ tell (Error 1 NameField)</div><div>        ,0 <$ tell (Error 2 QuantityField)</div>
<div>        ,0 <$ tell (Error 3 PriceField)}</div><div><br></div><div>    setName :: LineItemBuilder -> String -> LineItemBuilder</div><div>    setName li newName = if validName newName</div><div>        then li { name = pure newName }</div>
<div>        else li -- either leave the original, or add the new name and tell another error,</div><div>                  -- depending on use case</div><div><br></div><div>    -- quantity,price can be set similarly</div>
<div><br></div><div>    buildLineItem :: LineItemBuilder -> Either [Error] LineItem</div><div>    buildLineItem LineItemF{name, quantity,price} = case runWriter builder of</div><div>         (built,[]) -> Right built</div>
<div>         (_, errs) -> Left errs</div><div>      where</div><div>        builder = LineItemF <$> (pure <$> name)</div><div>                                     <*> (pure <$> quantity)</div><div>
                                     <*> (pure <$> price)</div><div><br></div><div>Now you have one type that represents a LineItem, and you can determine the state of the LineItem by which functor is used.  You'll probably be able to get some code re-use for any functions that don't need to know if a particular LineItem is valid or not, but there's still a type-level distinction between validated and unvalidated LineItems.  And if you're using lens, you can access the component fields with "name . _Wrapped" (or maybe _Unwrapped, depends on which version of lens you're using).</div>
<div><br></div><div>If you're taking arbitrary strings as user input, and they haven't been parsed as numbers yet (or otherwise validated), you can even handle that case by using an appropriate functor, such as "Constant String".  Then you could have a function like</div>
<div><br></div><div>    validate :: (String -> Either ValidationError a) -> Constant String a -> Either ValidationError a</div><div><br></div><div>that takes a parser and parses/validates the field.</div><div><br>
</div><div>John L.</div><div> </div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
<br>
    data Field = NameField | QuantityField | PriceField<br>
               deriving Show<br>
<br>
    data Error = Error { item :: Int<br>
                       , missing :: Field }<br>
               deriving Show<br>
<br>
    value :: LineItem -> Maybe Value<br>
    value l = (*) <$> price l <*> quantity l<br>
<br>
    totalValue :: [LineItem] -> Value<br>
    totalValue = sum . map (fromMaybe 0 . value)<br>
<br>
    missingFields :: LineItem -> [Field]<br>
    missingFields l = n ++ q ++ p<br>
      where n = if name l == Nothing then [NameField] else []<br>
            q = if quantity l == Nothing then [QuantityField] else []<br>
            p = if price l == Nothing then [PriceField] else []<br>
<br>
    errors :: [LineItem] -> [Error]<br>
    errors = concatMap (\(i, es) -> map (Error i) es)<br>
             . zip [1..]<br>
             . map missingFields<br>
<br>
    guiResponse :: [LineItem] -> (Value, [Error])<br>
    guiResponse = totalValue &&& errors<br>
<br>
    exampleData :: [LineItem]<br>
    exampleData = [ LineItem Nothing        (Just 99) (Just 10)<br>
                  , LineItem (Just "Water") Nothing   (Just 10)<br>
                  , LineItem (Just "Juice") (Just 1)  Nothing ]<br>
<br>
    -- *Main> guiResponse exampleData<br>
    -- (990.0, [ Error {item = 1, missing = NameField}<br>
    --         , Error {item = 2, missing = QuantityField}<br>
    --         , Error {item = 3, missing = PriceField}])<br>
<div class="HOEnZb"><div class="h5">_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
</div></div></blockquote></div><br></div></div>