Re: [Haskell-cafe] How to determine correct dependency versions for a library?

2012-11-12 Thread eyal.lo...@gmail.com
Especially in the case of base, not sure how upper bounds help at all:

If incompatible, you break with or without upper bounds. Actually getting 
errors related to Num instances is more informative IMO. 
If compatible, you just get false negatives and errors. 
In either case cabal can't install an older base to make the build work, so 
what do you gain? ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Open unqualified imports

2009-01-16 Thread eyal.lo...@gmail.com
Hi,

I would like to suggest a change to Haskell prime's handling of
imports.

First, let me define a few terms:

Qualified import:
import qualified Data.Map [as Map]

Closed-unqualified import:
import Data.Map(Map, lookup)

Open-unqualified import:
import Data.Map

I believe that the last type, open-unqualified is a really bad idea,
and should be discouraged or even disallowed. It should definitely not
be the default, like it is today.

These are my reasons:

A) Most importantly, reading code that has even a few open unqualified
imports makes deciphering where names are coming from really
difficult.  The other two forms make it really easy.  Code is read
more often than it is written -- lets optimize for the reading case.

B) Code that has open unqualified imports may break when new symbols
are added to the libraries its importing.  This means that libraries
cannot even be considered backwards compatible if they retain
semantics, but add new exported names.

C) In my experience, Haskell modules can map their semantics to
standard type-classes such as Monoid, Functor, Applicative, etc.  This
means that many Haskell modules can do without exporting many names.
Sometimes, they can export no names at all (Only instances).  This
means that closed-unqualified imports often do just fine.  When there
are many exported names, qualified imports are good.

-

I think currently many modules are designed to be imported
unqualified, and this is unfortunate. Haskell' libraries can fix
this.  For example, the various Monadic counterparts such as mapM,
replicateM, etc could do without the M in their names, and one could
use:

import qualified Control.Monad as M

M.for
M.map

and so on.

Additionally, I think there are some strong sentiments against the
choice of the function-composition dot as the qualified module name
lookup symbol.  It discourages people from using qualified imports.
Some other symbol ought to be used, but its not clear which symbol is
free.  Perhaps if unicode operators are allowed, then function
composition can move to the right symbol.

I believe qualified imports should probably have this syntax:

import Control.Monad as M

Closed-qualified imports can remain in the same syntax.
Open-qualified imports should probably be discouraged with a syntax
like:

import unqualified Control.Monad

And symbol clashes with these should probably just always choose the
overriding name.

Additionally, it would be nice if open unqualified imported were
considered quickdirty enough for -Wall to warn that they generate
name clashes or are more difficult to read, to further discourage
them.

Eyal
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: How to simplify this code?

2009-01-15 Thread eyal.lo...@gmail.com
Very nice series of refactorings!

I'd like to add that it might be a better argument order to replace:

JSON a = MyData - String - a - MyData

with:

JSON a = String - a - MyData - MyData

Just so you can get a (MyData - MyData) transformer, which is often
useful.

Eyal

On Jan 16, 1:52 am, Ryan Ingram ryani.s...@gmail.com wrote:
 Here's a series of refactorings that I feel gets to the essence of the code.

 For reference, here's the original.

  add :: JSON a = MyData - String - a - MyData
  add m k v = fromJust $ (return $ json m) = jsObj = (return .
  fromJSObject) = (return . ((k, showJSON v):)) = (return .
  toJSObject) = (return . showJSON) = \js - (return $ m { json = js
  })

 -- turn into do notation
 add :: JSON a = MyData - String - a - MyData
 add m k v = fromJust $ do
         t1 - return $ json m
         t2 - jsObj t1
         t3 - return $ fromJSObject t2
         t4 - return ( (k, showJSON v) : t3 )
         t5 - return $ toJSObject t4
         js - return $ showJSON t5
         t6 - return $ m { json = js }
         return t6

 -- replace var - return exp with let var = exp
 add :: JSON a = MyData - String - a - MyData
 add m k v = fromJust $ do
         let t1 = json m
         t2 - jsObj t1
         let t3 = fromJSObject t2
         let t4 = (k, showJSON v) : t3
         let t5 = toJSObject t4
         let js = showJSON t5
         let t6 = m { json = js }
         return t6

 -- inline some small definitions
 add m k v = fromJust $ do
         t2 - jsObj (json m)
         let js = showJSON $ toJSObject ((k, showJSON v) : fromJSObject t2)
         let t6 = m { json = js }
         return t6

 -- there's only one real Maybe object in here, and we fromJust afterwards,
 -- so put the can't fail assumption in the right place.
 --
 -- This is the only refactoring that I felt was at all tricky to figure out.
 add m k v =
         let t2 = fromJust $ jsObj (json m)
             js = showJSON $ toJSObject ((k, showJSON v) : fromJSObject t2)
             t6 = m { json = js }
         in t6

 -- sugar let, inline t6
 add m k v = m { json = js } where
     t2 = fromJust $ jsObj (json m)
     js = showJSON $ toJSObject ((k, showJSON v) : fromJSObject t2)

 -- inline t2
 add m k v = m { json = js } where
     js = showJSON $ toJSObject ((k, showJSON v) : fromJSObject
 (fromJust $ jsObj (json m)))

 -- uninline dictionary entry
 add m k v = m { json = js } where
     js = showJSON $ toJSObject (newEntry : fromJSObject (fromJust $
 jsObj (json m)))
     newEntry = (k, showJSON v)

 -- factor out modification
 modifyJSON f m = m { json = f (json m) }
 add m k v = modifyJson go m where
     go js = showJSON $ toJSObject (newEntry : fromJSObject (fromJust $
 jsObj js))
     newEntry = (k, showJSON v)

 -- turn into pipeline
 modifyJSON f m = m { json = f (json m) }
 add m k v = modifyJSON go m where
     go js = showJSON $ toJSObject $ (newEntry :) $ fromJSObject $
 fromJust $ jsObj js
     newEntry = (k, showJSON v)

 -- pointless
 modifyJSON f m = m { json = f (json m) }
 add m k v = modifyJSON go m where
     go = showJSON . toJSObject . (newEntry :) . fromJSObject . fromJust . 
 jsObj
     newEntry = (k, showJSON v)

 Final result:

  modifyJSON f m = m { json = f (json m) }

  add m k v = modifyJSON go m where
      go = showJSON . toJSObject . (newEntry :) . fromJSObject . fromJust . 
  jsObj
      newEntry = (k, showJSON v)

 Some stylistic choices are debatable (pointless vs. not, inline vs.
 not), but I think this is a lot more readable than the = and liftM
 madness you had going.

 I also might refactor the (fromJSObject -- some transformation --
 toJSObject) path; this seems like a fundamental operation on MyData,
 but I don't know enough about the library you are using to suggest the
 direction to go with this.

   -- ryan

 On Thu, Jan 15, 2009 at 11:14 AM, Levi Greenspan

 greenspan.l...@googlemail.com wrote:
  Dear list members,

  I started looking into monadic programming in Haskell and I have some
  difficulties to come up with code that is concise, easy to read and
  easy on the eyes. In particular I would like to have a function add
  with following type signature: JSON a = MyData - String - a -
  MyData. MyData holds a JSValue and add should add a key and a value to
  this JSON object. here is what I came up with and I am far from
  satisfied. Maybe someone can help me to simplify this...

  module Test where

  import Text.JSON
  import Data.Maybe (isJust, fromJust)
  import Control.Monad

  data MyData = MyData { json :: JSValue } deriving (Read, Show)

  jsObj :: JSValue - Maybe (JSObject JSValue)
  jsObj (JSObject o) = Just o
  jsObj _ = Nothing

  add :: JSON a = MyData - String - a - MyData
  add m k v = fromJust $ (return $ json m) = jsObj = (return .
  fromJSObject) = (return . ((k, showJSON v):)) = (return .
  toJSObject) = (return . showJSON) = \js - (return $ m { json = js
  })

  add2 :: JSON a = MyData - String - a - MyData
  add2 m k v = fromJust $ (\js - m { json =