[Haskell-cafe] Polymorphic Type Safe URL building -- I need advice on my project

2012-11-16 Thread Kyle Hanson
Hello,

So I started working on a project involving polymorphic type safe urls. I
know there are other type-safe url's out there, but I want some advice
before I start reorganizing it.

It is located here: https://github.com/dracule/web-scatter

One might ask why you would want polymorphic types in your URL. Current
implementation of type-safe URLs use a single type and then have it pattern
match on the constructors.

However, It is a pretty common occurrence that you might want to use a type
from other parts of code. Where this becomes prevalent is in IxSet and
AcidState. For IxSet your Index keys all have to have separate types . So
with this, you can convert your url into your index key's type and then
just make your handler like this:

  myHandler :: BlogId -> SomeWebHandler

I know my code probably has some terrible inefficiencies or something, so I
am looking for some feedback on some jarring problems.

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


Re: [Haskell-cafe] Polymorphic type

2006-06-22 Thread Sara Kenedy

Thanks all. I think for my function, I only need to throw an error
message for the out of range index. But through this, I know more some
ways to deal with the polymorphic type.


On 6/22/06, Brian Hulley <[EMAIL PROTECTED]> wrote:

Sara Kenedy wrote:
> Hello all,
>
> Now I am trying with the function of polymorphic type: This function
> returns the Nth element of list with type a. I try it as below.
>
> getNthElem :: Int -> [a] -> Maybe a
> getNthElemt _ [] = Nothing
> getNthElem 0 _ = Nothing
> getNthElem n s
>> n > length s = Nothing
>> otherwise = Just ((drop (n-1) (take n s))!!0)
>
>> getNthElem 2 ["a","b","c"]
> Just "b"
>
> However, I do not satisfy with this function because I want to return
> the Nth element of type a, not (Maybe a). For example, I want this
> function:
> getNthElem :: Int -> [a] ->  a
>
> But, I do not know how to define the empty element of type a.
>
> getNthElemt _ [] = 
> getNthElem 0 _ =  
>
> If you have some ideas about this, please give me some clues. Thanks
> a lot.

You might find it's always a lot easier to start counting from zero rather
than 1, so that "a" is the 0th element, "b" is the 1st element etc. Just
like a building with 2 floors has a ground floor and a first floor, and if
you want to find what day of the week it is in 46 days from today you just
use (today + 46) `mod` 7 instead of (((today - 1) + 46) `mod` 7) + 1

That aside, why not just throw an error when the function is called with an
index that's out of range?

getNthElemt _ [] = error "getNthElemt"

Regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com



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


Re: [Haskell-cafe] Polymorphic type

2006-06-22 Thread Brian Hulley

Sara Kenedy wrote:

Hello all,

Now I am trying with the function of polymorphic type: This function
returns the Nth element of list with type a. I try it as below.

getNthElem :: Int -> [a] -> Maybe a
getNthElemt _ [] = Nothing
getNthElem 0 _ = Nothing
getNthElem n s

n > length s = Nothing
otherwise = Just ((drop (n-1) (take n s))!!0)



getNthElem 2 ["a","b","c"]

Just "b"

However, I do not satisfy with this function because I want to return
the Nth element of type a, not (Maybe a). For example, I want this
function:
getNthElem :: Int -> [a] ->  a

But, I do not know how to define the empty element of type a.

getNthElemt _ [] = 
getNthElem 0 _ =  

If you have some ideas about this, please give me some clues. Thanks
a lot.


You might find it's always a lot easier to start counting from zero rather 
than 1, so that "a" is the 0th element, "b" is the 1st element etc. Just 
like a building with 2 floors has a ground floor and a first floor, and if 
you want to find what day of the week it is in 46 days from today you just 
use (today + 46) `mod` 7 instead of (((today - 1) + 46) `mod` 7) + 1


That aside, why not just throw an error when the function is called with an 
index that's out of range?


   getNthElemt _ [] = error "getNthElemt"

Regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] Polymorphic type

2006-06-22 Thread minh thu

2006/6/22, Sara Kenedy <[EMAIL PROTECTED]>:

Hello all,

Now I am trying with the function of polymorphic type: This function
returns the Nth element of list with type a. I try it as below.

getNthElem :: Int -> [a] -> Maybe a
getNthElemt _ []= Nothing
getNthElem 0 _  = Nothing
getNthElem n s
   | n > length s  = Nothing
   | otherwise = Just ((drop (n-1) (take n s))!!0)

>getNthElem 2 ["a","b","c"]
Just "b"

However, I do not satisfy with this function because I want to return
the Nth element of type a, not (Maybe a). For example, I want this
function:
getNthElem :: Int -> [a] ->  a

But, I do not know how to define the empty element of type a.

getNthElemt _ []= 
getNthElem 0 _  =  

 If you have some ideas about this, please give me some clues. Thanks a lot.



hi,
precisely, you want to return an "a" only when there is one
accordingly to your above code. the only way to handle this without
resorting to [] or Nothing to say there is no such value is to use
error or default value.

infact, ask yourself, what do you want ?

getNthElem 5 ["a","b","c"]

or

getNthElem 0 ["a","b","c"]

or

getNthElem (-1) ["a","b","c"]

do you want

"a"
[]
Nothing
"wrong"

or raise an exception (i.e. you use the "error" function) ?

once you know what you want, you can code it.

note, i think your 'take" is unnecessary here

   | otherwise = Just ((drop (n-1) (take n s))!!0)

also
you can use

   | otherwise = Just (n!!some_value) -- :)

this is where you see that the function you're trying to write is
really close of

(!!)


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


Re: [Haskell-cafe] Polymorphic type

2006-06-22 Thread Jared Updike

On 6/22/06, Sara Kenedy <[EMAIL PROTECTED]> wrote:

Hello all,

Now I am trying with the function of polymorphic type: This function
returns the Nth element of list with type a. I try it as below.

getNthElem :: Int -> [a] -> Maybe a
getNthElemt _ []= Nothing
getNthElem 0 _  = Nothing
getNthElem n s
| n > length s  = Nothing
| otherwise = Just ((drop (n-1) (take n s))!!0)

>getNthElem 2 ["a","b","c"]
Just "b"

However, I do not satisfy with this function because I want to return
the Nth element of type a, not (Maybe a). For example, I want this
function:
getNthElem :: Int -> [a] ->  a

But, I do not know how to define the empty element of type a.


Not all types (especially numbers) have an empty element (what does
that even mean?). Suppose you have a list
 [0, 1, -2, -1, 2]
and you try getNthElemt 4 and your program assumes that the empty
element for integers is 0. How can you tell that 0 from the 0 at the
beginning of the list [0, 1, 2]? Think really hard about what you are
asking and you will see why Maybe a takes the type a and extends it,
in a way, with an empty element, Nothing. To convert it from Maybe a
to a, try, e.g.
 fromJust (Just 4)  >  4
(it will give exceptions when Nothing shows up).


getNthElemt _ []= 
getNthElem 0 _  =  


One possiblity is to make a class called empty with a single member:


class Empty a where
  empty :: a
instance Empty [a] where   -- this also makes   "" = empty   for String
  empty = []
instance Empty Maybe a where   -- is this desirable?
  empty = Nothing
instance Integer where -- or this?
  empty = 0
...


and then add the constraint to your function:


getNthElem :: Empty a => Int -> [a] -> a
getNthElem :: Int -> [a] -> Maybe a
getNthElemt _ []= empty
getNthElem 0 _  = empty
getNthElem n s
| n > length s  = empty
| otherwise = ((drop (n-1) (take n s))!!0)



but you need overlapping instances to instantiate [a].  Or you could
use MonadPlus and mzero instead of Empty and empty, but that would
only work for List, Maybe and other monads and not for Integer, etc.

Note that in a dynamic language the same thing happens. In python
  4 + None
raises an exception. I don't think it's possible to get away from this
whole "failure" concept (except silently ignore it---in perl   4+null
yields 4 but is that always the right behavior in all situations? It
makes bugs really hard to find.)

 Jared.
--
http://www.updike.org/~jared/
reverse ")-:"
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Polymorphic type

2006-06-22 Thread Sara Kenedy

Hello all,

Now I am trying with the function of polymorphic type: This function
returns the Nth element of list with type a. I try it as below.

getNthElem :: Int -> [a] -> Maybe a
getNthElemt _ []= Nothing
getNthElem 0 _  = Nothing
getNthElem n s  
| n > length s   = Nothing
| otherwise = Just ((drop (n-1) (take n s))!!0)


getNthElem 2 ["a","b","c"]

Just "b"

However, I do not satisfy with this function because I want to return
the Nth element of type a, not (Maybe a). For example, I want this
function:
getNthElem :: Int -> [a] ->  a

But, I do not know how to define the empty element of type a.

getNthElemt _ []= 
getNthElem 0 _  =  

If you have some ideas about this, please give me some clues. Thanks a lot.

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


Re: [Haskell-cafe] polymorphic type

2005-07-06 Thread Henning Thielemann

On Wed, 6 Jul 2005, wenduan wrote:

> Dear all,
>
> Suppose we have defined two functions as below:
>
> case :: (a -> c,b -> c) -> Either a b -> c
> case (f, g) (Left x) = f x
> case (f, g) (Right x) = g x

It seems to be
  case == uncurry either

Prelude> :info either
-- either is a variable
either :: forall a c b. (a -> c) -> (b -> c) -> Either a b -> c

> plus :: (a -> b, c -> d) -> Either a b -> Either c d
> plus (f, g) = case(Left.f, Right.g)

> of plus should be:
>plus :: (a -> c, b -> d) -> Either a b -> Either c d

That signature looks correct and it is accepted

Prelude> let plus = (\(f,g) -> uncurry either (Left . f, Right . g)) :: 
(a->c,b->d) -> Either a b -> Either c d

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


Re: [Haskell-cafe] polymorphic type

2005-07-06 Thread Stefan Holdermans

Wenduan,

What I thought at first the signature of plus should be: plus :: (a -> 
c, b -> d) -> Either a b -> Either c d?Anyone know where I was wrong?


Your initial thought was right: it should

  (a -> c, b -> d) -> Either a b -> Either c d

Why didn't you just test it by feeding in to a compiler or interpreter; 
these are really useful, you know. ;)


Besides...


case :: (a -> c,b -> c) -> Either a b -> c
case (f, g) (Left x) = f x
case (f, g) (Right x) = g x


You can't name your function case: it's a reserved word.

You might want to check out the standard libraries:

  case' = uncurry either

HTH,

Stefan

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


[Haskell-cafe] polymorphic type

2005-07-06 Thread wenduan

Dear all,

Suppose we have defined two functions as below:

case :: (a -> c,b -> c) -> Either a b -> c
case (f, g) (Left x) = f x
case (f, g) (Right x) = g x

plus :: (a -> b, c -> d) -> Either a b -> Either c d
plus (f, g) = case(Left.f, Right.g)

My question is regarding to the function signature of 'plus' , in its 
signature, does the 'a' in 'a -> b' and in 'Either a b', must be 
instantiated to the same object when the function is applied?E.g.,Either 
a b is instantiated to 'Either Char b', will the  'a' in  'a -> b' be 
instantiated to 'Either Char b'?Furthermore, are the two bs in 'a -> b' 
and 'Either a b' not conflicting?What I thought at first the signature 
of plus should be: plus :: (a -> c, b -> d) -> Either a b -> Either c 
d?Anyone know where I was wrong?


--
X.W.D

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